yaz/commit

Several fixes * add pagination * fix caching * fix matched count

authorMichiel Hildebrand
Sat Mar 12 16:21:01 2011 +0100
committerMichiel Hildebrand
Sat Mar 12 16:21:01 2011 +0100
commit6e5f40acce48e14e991d7ef3d88aa7f7651ca390
treee7d6674cb0dcfc539e6d37f14467380c1b046e3b
parentcf1899443f05f607d137f4ce2be6c936bc89861f
Diff style: patch stat
diff --git a/applications/yaz_video_stats.pl b/applications/yaz_video_stats.pl
index 25aa6e7..cb6c0d5 100644
--- a/applications/yaz_video_stats.pl
+++ b/applications/yaz_video_stats.pl
@@ -1,5 +1,6 @@
 :- module(yaz_video_stats,
-	  [ http_yaz_video_stats/1
+	  [ http_yaz_video_stats/1,
+	    flush_stats_cache/0
   	  ]).
 
 :- use_module(library(http/http_dispatch)).
@@ -12,6 +13,8 @@
 :- use_module(library(semweb/rdf_db)).
 :- use_module(library(semweb/rdf_label)).
 :- use_module(user(user_db)).
+:- use_module(library(http/json)).
+:- use_module(library(http/json_convert)).
 
 :- use_module(library(yaz_util)).
 :- use_module(library(user_process)).
@@ -31,27 +34,44 @@
 http_yaz_video_stats(Request) :-
 	http_parameters(Request,
 			[ user(User,
-				[optional(true), description('Current user id')]),
+				[optional(true),
+				 description('Current user id')]),
  			  offset(Offset,
-				[default(0), integer, description('Offset of the result list')]),
+				[default(0), integer,
+				 description('Offset of the result list')]),
 			  limit(Limit,
-				[default(1000), integer, description('Limit on the number of results')])
+				[default(100), integer,
+				 description('Limit on the number of results')]),
+			  sort(SortBy,
+			       [default(tags),
+				description('property to sort by')])
  			]),
-	(   var(User)
-	->  findall(V, (rdf(V, rdf:type, pprime:'Video'),
-		        once(rdf(V, pprime:hasAnnotation, _))), Vs)
-	;   findall(V, (rdf(V, rdf:type, pprime:'Video'),
-		        once(video_process(V, _, User))), Vs)
-	),
-	length(Vs, NumberOfResults),
-  	list_offset(Vs, Offset, OffsetResults),
-	list_limit(OffsetResults, Limit, LimitResults, _),
-	maplist(video_data, LimitResults, Data),
- 	html_page(Data, NumberOfResults, Offset, Limit).
+	video_stats(User, Stats0),
+	length(Stats0, NumberOfResults),
+	sort_stats(Stats0, SortBy, Stats1),
+	list_offset(Stats1, Offset, Stats2),
+	list_limit(Stats2, Limit, Stats, _),
+  	html_page(Stats, NumberOfResults, Offset, Limit).
+
+sort_stats(Stats, SortBy, Sorted) :-
+	stats_arg(SortBy, Arg),
+	sort_by_arg(Stats, Arg, desc, Sorted).
+
+stats_arg(title, 2).
+stats_arg(category, 3).
+stats_arg(games, 4).
+stats_arg(players, 5).
+stats_arg(tags, 6).
+stats_arg(unique_tags, 7).
+stats_arg(matched_tags, 8).
+stats_arg(unique_matched_tags, 9).
 
 :- dynamic
 	video_stats_cache/1.
 
+flush_stats_cache :-
+	retractall(video_stats_cache(_)).
+
 video_stats(User, Stats) :-
 	var(User),
 	video_stats_cache(Stats),
@@ -74,18 +94,11 @@ video_stats(User, Stats) :-
 
 empty_video_stats_cache(assert(_S,P,_O,_DB)) :-
 	rdf_equal(P, pprime:hasAnnotation),
-	retractall(video_stats_cache(_)).
+	flush_stats_cache.
 
 
-video_data(Video, {video:Video,
-		   title:Title,
-		   category:Cat,
-		   games:Gs,
-		   players:Us,
-		   tags:Ts,
-		   unique_tags:UTs,
-		   matched_tags:Ms,
-		   unique_matched_tags:UMs}) :-
+video_data(Video, Stats) :-
+	Stats = stats(Video, Title, Cat, Gs, Us, Ts, UTs, Ms, UMs),
 	rdf_label(Video, Lit),
 	literal_text(Lit, Text),
 	(   Text = ''
@@ -101,11 +114,12 @@ video_data(Video, {video:Video,
 	sort(Users0, Users),
 	length(Games, Gs),
 	length(Users, Us),
-	findall(T-S, (rdf(Video, pprime:hasAnnotation, E),
+	findall(S-T, (rdf(Video, pprime:hasAnnotation, E),
 		      rdf(E, rdf:value, T),
-		      rdf(E, pprime:score, literal(S))
+		      rdf(E, pprime:score, literal(S0)),
+		      atom_number(S0, S)
 		     ), Es),
-	pairs_keys(Es, Tags0),
+	pairs_values(Es, Tags0),
 	sort(Tags0, Tags),
 	length(Tags0, Ts),
 	length(Tags, UTs),
@@ -122,7 +136,7 @@ video_process(Video, Process, User) :-
 
 remove_no_scored([], []).
 remove_no_scored([E|Es], L) :-
-	(   E = _-0
+	(   E = 0-_
 	->  L = L1
 	;   L = [E|L1]
 	),
@@ -158,9 +172,10 @@ video_count(N) -->
 	html([N, ' videos tagged']).
 
 
-html_page_yui(Data) -->
+html_page_yui(Stats) -->
 	{ data_columns(Columns),
-	  http_location_by_id(http_yaz_player, Link)
+	  http_location_by_id(http_yaz_player, Link),
+	  prolog_to_json(Stats, JSONStats)
   	},
   	js_yui3([],
 		[node,event,datatable,'datatable-sort'],
@@ -170,14 +185,17 @@ html_page_yui(Data) -->
 				    o.record.getValue("title")+"</a>"']),
 		  \js_new(statsTable,
 			  'Y.DataTable.Base'({columnset:Columns,
-					      recordset:Data,
+					      recordset:JSONStats,
 					      plugins: [ symbol('Y.Plugin.DataTableSort') ]
 					     })),
 		  \js_call('statsTable.render'('#stats'))
 
   		]).
 
-
+:- json_object
+	stats(video:atom, title:atom, category:atom, games:integer,
+	      players:integer, tags:integer, unique_tags,
+	      matched_tags, unique_matched_tags).