vumix/commit

make p0 fully functional

authorMichiel Hildebrand
Mon Apr 23 15:02:45 2012 +0200
committerMichiel Hildebrand
Mon Apr 23 15:02:45 2012 +0200
commit697d20b2b0a245e51de38e69923e63c9111fcfb9
tree0f516c8ec2956467f799514d4e285de8f7ed6f8d
parent88c92881b58480d3ba17db49428330247032dcc8
Diff style: patch stat
diff --git a/applications/p1.pl b/applications/p1.pl
index 0315588..46e7adc 100644
--- a/applications/p1.pl
+++ b/applications/p1.pl
@@ -24,6 +24,10 @@
 :- use_module(api(annotation)).
 :- use_module(library(user_process)).
 
+:- use_module(api(reconcile)).
+:- use_module(library(video_annotation)).
+:- use_module(library(yaz_util)).
+
 
 /***************************************************
 * http handlers
@@ -69,7 +73,11 @@ http_vumix_p1(Request) :-
 	;   logged_on(User, anonymous)
         ),
 	user_process(User, Target, _),
-	html_page(Target, Fields).
+	video_annotations(Target, As, [interval(10)]),
+	sort_by_arg(As, 2, Annotations),
+	video_scenes(Target, Scenes),
+	scene_annotations(Scenes, Annotations, SceneAnnotations),
+	html_page(Target, SceneAnnotations).
 
 user_process(User, Target, Process) :-
 	(   current_user_process(Process),
@@ -82,16 +90,69 @@ user_process(User, Target, Process) :-
 	),
 	start_user_process(Process).
 
+%%	video_scenes(+Target, -Scenes)
+%
+%	Scenes is a list of video scenes in Target.
+%	Currently this simply sets a scenes every 10 seconds.
+
+video_scenes(Target, Scenes) :-
+	mbh_video_source(Target, Source),
+	rdf(Target, pprime:duration, literal(DA)),
+	atom_number(DA, Duration),
+	!,
+	scene_list(1000, Duration, 10000, Source, Scenes).
+video_scenes(_, []).
+
+scene_list(Time, Duration, _, _, []) :-
+	Time > Duration,
+	!.
+scene_list(Start, Duration, Interval, Source, [Scene|Rest]) :-
+	Scene = scene(Start, End, KeyFrame),
+	End is Start+Interval,
+	KeyFrame is Start+(Interval/2),
+	scene_list(End, Duration, Interval, Source, Rest).
+
+%%	scene_annotations(+SceneList, +Annotations, -SceneAnnotations)
+%
+%	SceneAnnotations contains all scenes from SceneList
+%	with the annotations.
+
+scene_annotations([], _, []).
+scene_annotations([scene(Start,End,Key)|T], Annotations, [scene(Start,End,Key,As)|Rest]) :-
+	annotations_in_scene(Annotations, Start, End, As, AnnotationsRest),
+	scene_annotations(T, AnnotationsRest, Rest).
+
+
+annotations_in_scene([], _, _, [], []).
+annotations_in_scene([A|As], Start, End, AsInScene, Rest) :-
+	A = annotation(_Value,Time,_End,_Entries,_Score),
+	(   Time < Start
+	->  annotations_in_scene(As, Start, End, AsInScene, Rest)
+	;   Time < End
+	->  AsInScene = [A|AsInScene0],
+	    annotations_in_scene(As, Start, End, AsInScene0, Rest)
+	;   Rest = [A|As]
+	).
+
+
+% hack for mbh demo
+mbh_video_source(R, Video) :-
+	rdf_has(R, dc:id, literal(FragmentId)),
+	!,
+	concat_atom(['http://eculture2.cs.vu.nl/pprime/videos/',FragmentId,'.mp4'], Video).
+mbh_video_source(_R, @null).
+
 
 /***************************************************
 * annotation page
 ***************************************************/
 
-%%	html_page(+Target, +Fields)
+%%	html_page(+Target, +Scenes)
 %
 %	HTML page
 
-html_page(Target, Fields) :-
+html_page(Target, Scenes) :-
+	mbh_video_source(Target, Source),
 	rdf_global_id(_:Id, Target),
 	reply_html_page(
 	    [ title(['Annotate -- ', Id])
@@ -102,10 +163,10 @@ html_page(Target, Fields) :-
 	      div(class('yui3-skin-sam yui-skin-sam'),
 		  [ div(id(hd), []),
 		    div(id(bd),
-			div([id(layout), class('yui3-g')],
+			div([id(layout)],
 			    [ div(id(title), []),
-			      div(id(frames),
-				  \html_frames(Target))
+			      div(id(scenes),
+				  \html_scenes(Scenes, Source))
 			    ])
 		       ),
 		    div(id(ft), [])
@@ -114,36 +175,34 @@ html_page(Target, Fields) :-
 		    [])% \yui_script(Target, Fields))
 	    ]).
 
-html_frames(Target) -->
-	{ video_source(Target, Source),
-	  rdf(Target, pprime:duration, literal(DA)),
-	  atom_number(DA, Duration)
-	},
-	!,
-	html_frame_list(1000, Duration, 10000, Source).
-html_frames(_) --> !.
-
-html_frame_list(Time, Duration, _, _) -->
-	{ Time > Duration },
-	!.
-html_frame_list(Time, Duration, Interval, Source) -->
-	{ Next is Time+Interval,
-	  http_link_to_id(serve_video_frame, [url(Source),time(Time)], Link)
+html_scenes([], _) --> !.
+html_scenes([scene(Start, End, KeyFrame0, As)|T], Source) -->
+	{ KeyFrame is KeyFrame0/1000,
+	  http_link_to_id(serve_video_frame, [url(Source),time(KeyFrame)], Thumb)
 	},
-	html(div(class(frame),
-	     [ div(class(thumb),
-		   img([src(Link)])),
-	       div(class(tags), [])
+	html(div([class('yui3-g frame'), style('margin-bottom:15px')],
+	     [ div(class('yui3-u-1-2'),
+		   [ div(class(thumb),
+			 img([src(Thumb)])),
+		     div(class(time),
+			 [Start, ' -- ', End])
+		   ]),
+	       div(class('yui3-u-1-2 tags'),
+		  ul(\html_scene_annotations(As)))
 	     ])),
-	html_frame_list(Next, Duration, Interval, Source).
-
-% hack for mbh demo
-video_source(R, Video) :-
-	rdf_has(R, dc:id, literal(FragmentId)),
-	!,
-	concat_atom(['http://eculture2.cs.vu.nl/pprime/videos/',FragmentId,'.mp4'], Video).
-video_source(_R, @null).
-
+	html_scenes(T, Source).
+
+html_scene_annotations([]) --> !.
+html_scene_annotations([A|As]) -->
+	{ A = annotation(Value,_S,_E,Entries,_Score),
+	  (   Value = literal(_)
+	  ->  literal_text(Value, Label)
+	  ;   rdf_label(Value, Label)
+	  ),
+	  length(Entries, Count)
+	},
+	html(li([Label, ' (', Count,')'])),
+	html_scene_annotations(As).
 
 
 
diff --git a/applications/vumix.pl b/applications/vumix.pl
index c5940fd..5d50b25 100644
--- a/applications/vumix.pl
+++ b/applications/vumix.pl
@@ -23,6 +23,7 @@
 
 :- use_module(api(annotation)).
 :- use_module(library(user_process)).
+:- use_module(library(yaz_util)).
 
 
 /***************************************************
@@ -184,11 +185,11 @@ html_page(Target, Fields) :-
 	    ]).
 
 % hack for mbh demo
-video_source(R, Video) :-
+mbh_video_source(R, Video) :-
 	rdf_has(R, dc:id, literal(FragmentId)),
 	!,
 	concat_atom(['http://eculture2.cs.vu.nl/pprime/videos/',FragmentId,'.mp4'], Video).
-video_source(_R, @null).
+mbh_video_source(_R, @null).
 
 %%	html_annotation_fields(+FieldURIs)
 %
@@ -267,7 +268,7 @@ js_module('annotation', json([fullpath(Path),
 
 js_video_frames(Target) -->
 	{ http_location_by_id(serve_video_frame, FrameServer),
-	  video_source(Target, Src)
+	  mbh_video_source(Target, Src)
 	},
 	yui3_new(videoFrames,
 		 'Y.VideoFrames',
@@ -305,6 +306,7 @@ js_video(Target) -->
 		 'Y.VideoPlayer',
 		 {filepath:FilePath,
 		  src:Src,
+		  playerType:npo,
 		  width:730,
 		  height:460,
 		  autoplay:symbol(false),
diff --git a/applications/vumix_p0.pl b/applications/vumix_p0.pl
index 1826a70..c1ba98d 100644
--- a/applications/vumix_p0.pl
+++ b/applications/vumix_p0.pl
@@ -27,13 +27,15 @@
 :- use_module(api(reconcile)).
 :- use_module(library(video_annotation)).
 :- use_module(library(yaz_util)).
-
+:- use_module(library(stop_words)).
+:- use_module(library(tfidf)).
 
 /***************************************************
 * http handlers
 ***************************************************/
 
 :- http_handler(cliopatria(vumix/p0), http_vumix_p0, []).
+:- http_handler(cliopatria(vumix/p0/session/finish), http_vumix_p0_finish, []).
 
 
 /***************************************************
@@ -49,6 +51,52 @@
 * http replies
 ***************************************************/
 
+http_vumix_p0_finish(Request) :-
+	http_parameters(Request,
+		[ target(Target,
+			 [uri,
+			  description('URI of the object to be annotated')
+			 ]),
+		  'http://semanticweb.cs.vu.nl/prestoprime/personAnnotation'(Persons,
+									      [zero_or_more]),
+		  'http://semanticweb.cs.vu.nl/prestoprime/placeAnnotation'(Places,
+									      [zero_or_more]),
+		  'http://semanticweb.cs.vu.nl/prestoprime/nameAnnotation'(Names,
+									      [zero_or_more]),
+		  'http://semanticweb.cs.vu.nl/prestoprime/subjectAnnotation'(Subjects,
+									      [zero_or_more])
+		]),
+	(   setting(login, true)
+        ->  ensure_logged_on(User)
+        ;   logged_on(User, anonymous)
+        ),
+	gv_resource_commit(Target, User,
+			   save_annotations(['http://semanticweb.cs.vu.nl/prestoprime/personAnnotation'-Persons,
+					     'http://semanticweb.cs.vu.nl/prestoprime/placeAnnotation'-Places,
+					     'http://semanticweb.cs.vu.nl/prestoprime/nameAnnotation'-Names,
+					     'http://semanticweb.cs.vu.nl/prestoprime/subjectAnnotation'-Subjects
+					    ], Target, User, Graph),
+			   _Head,
+			   Graph),
+	(   current_user_process(Process)
+	->  end_user_process(Process)
+	;   true
+	),
+	http_redirect(see_other, location_by_id(http_vumix), Request).
+
+
+save_annotations([], _, _, _).
+save_annotations([Field-Values|Ts], Target, User, Graph) :-
+	rdf_field_annotations(Values, Field, Graph, User, Target),
+	save_annotations(Ts, Target, User, Graph).
+
+rdf_field_annotations([], _, _, _, _).
+rdf_field_annotations([Value|Vs], Field, Graph, User, Target) :-
+	rdf_label(Value, Label),
+	rdf_add_annotation(Graph, User, Target, Field, Value, Label, _),
+	rdf_field_annotations(Vs, Field, Graph, User, Target).
+
+
 %%	http_vumix_p0(+Request)
 %
 %	Generate page to annotate a vumix.
@@ -77,13 +125,48 @@ http_vumix_p0(Request) :-
 	;   logged_on(User, anonymous)
         ),
 	user_process(User, Target, _),
-	video_annotations(Target, Tags, [interval(10)]),
+	tag_rank(Target, Tags0),
+	remove_stop_words(Tags0, dutch, Tags),
+	link_tags_to_concepts(Tags, Concepts0),
+	keysort(Concepts0, Concepts1),
+	group_pairs_by_key(Concepts1, Concepts2),
+	pairs_sort_by_value_sum(Concepts2, Concepts),
+	html_page(Target, Fields, Concepts).
+
+%%	link_tags_to_concepts(+Tags, -Concepts)
+%
+%	Add candidate concepts.
+
+link_tags_to_concepts([], []).
+link_tags_to_concepts([Score-Tag|As], [Concept-Score|Rest]) :-
+	rdf_has(Concept,rdfs:label,literal(exact(Tag),_)),
+	!,
+	link_tags_to_concepts(As, Rest).
+link_tags_to_concepts([_|As],  Rest) :-
+	link_tags_to_concepts(As, Rest).
+
+
+/*
+	video_annotations(Target, Tags0, [interval(10)]),
+	remove_stop_words(Tags0, dutch, Tags),
 	rdf_equal(skos:'Concept', SKOSConcept),
 	link_tags_to_concepts(Tags, SKOSConcept, Concepts0),
 	keysort(Concepts0, Concepts1),
-	group_pairs_by_key(Concepts1, Concepts2),
-	pairs_sort_by_value_count(Concepts2, Concepts),
+	group_pairs_by_key(Concepts1, Concepts),
+	%pairs_sort_by_value_count(Concepts2, Concepts),
 	html_page(Target, Fields, Concepts).
+*/
+
+remove_stop_words([], _, []).
+remove_stop_words([_Rank-Tag0|Tags], Lang, Filtered) :-
+	downcase_atom(Tag0, Tag),
+	stop_word(Lang, Tag),
+	!,
+	remove_stop_words(Tags, Lang, Filtered).
+remove_stop_words([Tag|Tags], Lang, [Tag|Filtered]) :-
+	remove_stop_words(Tags, Lang, Filtered).
+
+/*
 
 %%	link_tags_to_concepts(+Annotations, -Annotations1)
 %
@@ -119,7 +202,7 @@ hit_concept(hit(_,URI,_,Label), concept(URI,Label,Alt,Desc)) :-
 	;   Desc = ''
 	).
 
-
+*/
 
 user_process(User, Target, Process) :-
 	(   current_user_process(Process),
@@ -154,11 +237,14 @@ html_page(Target, Fields, Concepts) :-
 		    div(id(bd),
 			div([id(layout), class('yui3-g')],
 			    [ div([id(fields), class('yui3-u')],
-				  [ div(class(bd),
-					\html_suggestion_fields(Fields, Concepts)),
-				    div(class(ft),
-					a(href(location_by_id(http_vumix_finish)), done))
-				  ]),
+				  form(action(location_by_id(http_vumix_p0_finish)),
+				       [ input([type(hidden), name(target), value(Target)]),
+					 div(class(bd),
+					     \html_suggestion_fields(Fields, Concepts)),
+					 div(class(ft),
+					     input([type(submit), value(submit)]))
+				       ])
+				  ),
 			      div([id(media), class('yui3-u')],
 				  [ div(id(title), []),
 				    div(id(video), []),
@@ -208,7 +294,7 @@ html_annotation_field(Field, Concepts) -->
 	     ]).
 
 field_suggestions([], _, []).
-field_suggestions([Count-Concept|Cs], Scheme, [Count-Concept|Rest]) :-
+field_suggestions([Rank-Concept|Cs], Scheme, [Rank-Concept|Rest]) :-
 	rdf(Concept, skos:inScheme, Scheme),
 	!,
 	field_suggestions(Cs, Scheme, Rest).
@@ -216,17 +302,38 @@ field_suggestions([_Concept|Cs], Scheme, Rest) :-
 	field_suggestions(Cs, Scheme, Rest).
 
 html_suggestions([], _) --> !.
-html_suggestions([Count-Concept|T], Field) -->
+html_suggestions([_Rank-Concept|T], Field) -->
 	{ rdf_label(Concept, Label)
+	  %Score is round(Rank)
 	},
 	html(li([input([name(Field),type(checkbox),value(Concept)]),
-		 Label,
-		 Count
+		 Label
+		 %' (',Score,')'
 		])),
 	html_suggestions(T, Field).
 
+/*
+html_suggestions([], _) --> !.
+html_suggestions([Concept-Entries|T], Field) -->
+	{ rdf_label(Concept, Label)
+	},
+	html(li([input([name(Field),type(checkbox),value(Concept)]),
+		 Label,
+		 \html_tag_entries(Entries)
+		])),
+	html_suggestions(T, Field).
 
-
+html_tag_entries([]) --> !.
+html_tag_entries([Entries|Es]) -->
+	html(ul(\html_entries(Entries))),
+	html_tag_entries(Es).
+
+html_entries([]) --> !.
+html_entries([i(Entry,Time)|Es]) -->
+	{ rdf(Entry,rdf:value,literal(V)) },
+	html(li([V, ' ', Time])),
+	html_entries(Es).
+*/
 html_annotation_field_desc(URI) -->
 	{ rdf(URI, dc:comment, D),
 	  literal_text(D, Desc)
@@ -245,7 +352,7 @@ html_annotation_field_desc(_URI) --> !.
 %
 %	Emit YUI object.
 
-yui_script(Target, Fields) -->
+yui_script(Target, _Fields) -->
 	{ findall(M-C, js_module(M,C), Modules),
 	  pairs_keys(Modules, Includes)
 	},
@@ -314,14 +421,15 @@ js_title_edit(Target) -->
 
 js_video(Target) -->
 	{ http_absolute_location(js('vuplayer/'), FilePath, []),
-	  mbh_video_source(Target, Src)
+	  video_source(Target, Src)
 	},
 	yui3_new(videoPlayer,
 		 'Y.VideoPlayer',
 		 {filepath:FilePath,
+		  playerType:npo,
 		  src:Src,
-		  width:730,
-		  height:460,
+		  width:700,
+		  height:400,
 		  autoplay:symbol(false),
 		  controls:symbol(true)
 		 }),
@@ -358,3 +466,6 @@ js_annotation_field(FieldURI, Target) -->
 		   resultTextLocator: label,
 		   resultHighlighter: phraseMatch}).
 
+
+
+
diff --git a/lib/tfidf.pl b/lib/tfidf.pl
index 00d0a21..ed10ef5 100644
--- a/lib/tfidf.pl
+++ b/lib/tfidf.pl
@@ -1,20 +1,32 @@
 :- module(tfidf,
-	  [tag_rank/2,
+	  [flush_tag_rank/1,
+	   tag_rank/2,
 	   documents/1,
 	   tf/3,
-	   idf/3
+	   idf/3,
+	   link_tags_to_concepts/3
 	  ]).
 
 :- use_module(library(csv)).
 :- use_module(library(semweb/rdf_db)).
 
+:- dynamic
+	tag_rank_cache/2.
+
+flush_tag_rank(Video) :-
+	retractall(tag_rank_cache(Video, _)).
+
+tag_rank(Video, RankedTagList) :-
+	tag_rank_cache(Video, RankedTagList),
+	!.
 tag_rank(Video, RankedTagList) :-
 	documents(Videos),
 	findall(T, document_term(Video, T), Ts0),
 	sort(Ts0, Ts),
 	maplist(tag_score(Video, Videos), Ts, Scored),
 	keysort(Scored, Sorted),
-	reverse(Sorted, RankedTagList).
+	reverse(Sorted, RankedTagList),
+	assert(tag_rank_cache(Video, RankedTagList)).
 
 tag_score(D, Collection, Tag, Score-Tag) :-
 	tf(Tag, D, TF),
@@ -67,3 +79,14 @@ video_tags([Video|Vs], [row(Id,TagA)|Rs]) :-
 	video_tags(Vs, Rs).
 
 
+
+
+link_tags_to_concepts([], _, []).
+link_tags_to_concepts([Score-Tag|As], Type, [Score-Concept|Rest]) :-
+	rdf_has(Concept,rdfs:label,literal(exact(Tag),_)),
+	%reconcile(Value, 1, Type, [], [hit(D,Concept,_,_)]),
+	%D < 10,
+	!,
+	link_tags_to_concepts(As, Type, Rest).
+link_tags_to_concepts([_|As], Type, Rest) :-
+	link_tags_to_concepts(As, Type, Rest).
diff --git a/web/css/vumix.css b/web/css/vumix.css
index 048e452..e64d349 100644
--- a/web/css/vumix.css
+++ b/web/css/vumix.css
@@ -3,7 +3,7 @@
 	height: 100%;
 }
 #fields .bd {
-	height: 490px;
+	height: 560px;
 }
 #fields .ft {
 	border-top: 2px solid white;
@@ -18,8 +18,9 @@
 	
 }
 .suggest {
-	height: 100px;
+	height: 105px;
 	overflow: auto;
+	background-color: white;
 }
 .suggest ul {
 	padding: 0;