yaz/commit

generate a big table with stats for all videos

authorMichiel Hildebrand
Wed Feb 23 18:04:13 2011 +0100
committerMichiel Hildebrand
Wed Feb 23 18:04:13 2011 +0100
commit4e5932b7001038a6cac9e88e92a6be0111d32624
treed46e6bf9cdc3571b1f9bf31a31b9a67bcf875943
parent455759156d6ac8dd41088cbf21b3d826ba35997e
Diff style: patch stat
diff --git a/applications/yaz_video_stats.pl b/applications/yaz_video_stats.pl
new file mode 100644
index 0000000..25aa6e7
--- /dev/null
+++ b/applications/yaz_video_stats.pl
@@ -0,0 +1,212 @@
+:- module(yaz_video_stats,
+	  [ http_yaz_video_stats/1
+  	  ]).
+
+:- use_module(library(http/http_dispatch)).
+:- use_module(library(http/http_parameters)).
+:- use_module(library(http/html_write)).
+:- use_module(library(http/http_host)).
+:- use_module(library(http/http_path)).
+:- use_module(library(http/html_head)).
+:- use_module(library(http/js_write)).
+:- use_module(library(semweb/rdf_db)).
+:- use_module(library(semweb/rdf_label)).
+:- use_module(user(user_db)).
+
+:- use_module(library(yaz_util)).
+:- use_module(library(user_process)).
+:- use_module(library(video_annotation)).
+:- use_module(library(yui3)).
+:- use_module(components(yaz_page)).
+:- use_module(components(yaz_video_item)).
+:- use_module(components(paginator)).
+
+
+:- http_handler(yaz(stats), http_yaz_video_stats, []).
+
+%%	http_yaz_videos(+Request)
+%
+%       Emit a all videos a user has annotated.
+
+http_yaz_video_stats(Request) :-
+	http_parameters(Request,
+			[ user(User,
+				[optional(true), description('Current user id')]),
+ 			  offset(Offset,
+				[default(0), integer, description('Offset of the result list')]),
+			  limit(Limit,
+				[default(1000), integer, description('Limit on the number of results')])
+ 			]),
+	(   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).
+
+:- dynamic
+	video_stats_cache/1.
+
+video_stats(User, Stats) :-
+	var(User),
+	video_stats_cache(Stats),
+	!.
+video_stats(User, Stats) :-
+	var(User),
+	!,
+	findall(V, (rdf(V, rdf:type, pprime:'Video'),
+		    once(rdf(V, pprime:hasAnnotation, _))),
+		Vs),
+	maplist(video_data, Vs, Stats),
+	assert(video_stats_cache(Stats)).
+video_stats(User, Stats) :-
+	 findall(V, (rdf(V, rdf:type, pprime:'Video'),
+		     once(video_process(V, _, User))),
+		 Vs),
+	 maplist(video_data, Vs, Stats).
+
+:- rdf_monitor(empty_video_stats_cache, [assert]).
+
+empty_video_stats_cache(assert(_S,P,_O,_DB)) :-
+	rdf_equal(P, pprime:hasAnnotation),
+	retractall(video_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}) :-
+	rdf_label(Video, Lit),
+	literal_text(Lit, Text),
+	(   Text = ''
+	->  Title = Video
+	;   Title = Text
+	),
+  	rdf(Video, pprime:category, Cat0),
+	display_label(Cat0, Cat),
+	findall(P-U, video_process(Video, P, U), Pairs),
+	pairs_keys(Pairs, Games0),
+	pairs_values(Pairs, Users0),
+	sort(Games0, Games),
+	sort(Users0, Users),
+	length(Games, Gs),
+	length(Users, Us),
+	findall(T-S, (rdf(Video, pprime:hasAnnotation, E),
+		      rdf(E, rdf:value, T),
+		      rdf(E, pprime:score, literal(S))
+		     ), Es),
+	pairs_keys(Es, Tags0),
+	sort(Tags0, Tags),
+	length(Tags0, Ts),
+	length(Tags, UTs),
+	remove_no_scored(Es, Scored0),
+	pairs_keys(Scored0, ScoredTags),
+ 	sort(ScoredTags, Scored),
+	length(Scored0, Ms),
+	length(Scored, UMs).
+
+video_process(Video, Process, User) :-
+  	rdf(Process, opmv:used, Video),
+	rdf(Process, rdf:type, pprime:'Game'),
+	rdf_has(Process, opmv:wasControlledBy, User).
+
+remove_no_scored([], []).
+remove_no_scored([E|Es], L) :-
+	(   E = _-0
+	->  L = L1
+	;   L = [E|L1]
+	),
+	remove_no_scored(Es, L1).
+
+
+
+%%	html_page(+Videos, +NumberOfResults, +Offset, +Limit)
+%
+%	Emit HTML page with a list of Videos.
+
+html_page(Data, NumberOfResults, Offset, Limit) :-
+ 	reply_html_page(yaz,
+			[ title(['YAZ - sessions'])
+			],
+			[ div(class(topic),
+			      [ div(class(header),
+				    h2(\video_count(NumberOfResults))),
+				div(class(body),
+				    div(id(stats), []))
+ 			      ]),
+			  div(class(footer),
+					div(class(paginator),
+					    \html_paginator(NumberOfResults, Offset, Limit)
+					   )),
+			  script(type('text/javascript'),
+				\html_page_yui(Data))
+			]).
+
+video_count(1) -->
+	html('1 tagged video').
+video_count(N) -->
+	html([N, ' videos tagged']).
+
+
+html_page_yui(Data) -->
+	{ data_columns(Columns),
+	  http_location_by_id(http_yaz_player, Link)
+  	},
+  	js_yui3([],
+		[node,event,datatable,'datatable-sort'],
+		[ \js_function_decl(playerLink, [o],
+				    \['return "<a href=\'',Link,'?video="+
+				    o.record.getValue("video")+"\'>"+
+				    o.record.getValue("title")+"</a>"']),
+		  \js_new(statsTable,
+			  'Y.DataTable.Base'({columnset:Columns,
+					      recordset:Data,
+					      plugins: [ symbol('Y.Plugin.DataTableSort') ]
+					     })),
+		  \js_call('statsTable.render'('#stats'))
+
+  		]).
+
+
+
+
+
+data_columns([{key:title,
+	       formatter:symbol(playerLink),
+	       sortable:symbol(true)
+	      },
+	      {key:category,
+	       sortable:symbol(true)
+	      },
+	      {key:games,
+	       sortable:symbol(true)
+	      },
+	      {key:players,
+	       sortable:symbol(true)
+	      },
+	      {key:tags,
+	       sortable:symbol(true)
+	      },
+	      {key:unique_tags,
+	       label:'unique tags',
+	       sortable:symbol(true)
+	      },
+	      {key:matched_tags,
+	       label:'matched tags',
+	       sortable:symbol(true)
+	      },
+	      {key:unique_matched_tags,
+	       label:'unique matched tags',
+	       sortable:symbol(true)
+	      }]).
+