yaz/commit

integrate search and several options into yaz player

authorMichiel Hildebrand
Wed Mar 9 18:55:35 2011 +0100
committerMichiel Hildebrand
Wed Mar 9 18:55:35 2011 +0100
commit77cd8bcb09e942aad9b3498e5089c7d116c446a8
treea52a9fce8361691facc9eec475f411249c3bc422
parent400697b9b0cd1e9c9b54f613669cadef4e0b0506
Diff style: patch stat
diff --git a/api/video_frames.pl b/api/video_frames.pl
index ef273f1..346ec19 100644
--- a/api/video_frames.pl
+++ b/api/video_frames.pl
@@ -1,7 +1,6 @@
 :- module(video_frames,
 	  [ cache_tag_frames/3,
-	    video_frame_reset/0,
- 	    video_frame/3
+  	    video_frame/3
 	  ]).
 
 :- use_module(library(settings)).
@@ -23,9 +22,6 @@
 :- setting(cache_directory, atom, 'cache/frames',
 	   'Directory for caching video frames').
 
-:- dynamic
-	video_frame_cache/3.		% Video, Time, File
-
 http:location(video, root(video), []).
 user:file_search_path(video, videos).
 
@@ -34,18 +30,34 @@ user:file_search_path(video, videos).
 :- http_handler(root(videoframe), serve_video_frame, []).
 :- http_handler(video(.), serve_video, [spawn(video), prefix]).
 
+%%	serve_video(+Request)
+%
+%	Serve a video.
+%
+%	@TBD How can we know the mimetype
+
 serve_video(Request) :-
 	ensure_logged_on(_),
-	memberchk(path_info(File), Request),
-  	http_reply_file(video(File), [mimetype('video/flv'), unsafe(true)], Request).
-
+	http_parameters(Request,
+			[ t(Time,
+			      [ optional(true), description('URL of the video')])
+ 			]),
+	memberchk(path_info(Video), Request),
+	(   nonvar(Time),
+	    parse_time_param(Time, Start, End)
+	->  video_fragment(Video, Start, End, Fragment)
+	;   Fragment = video(Video)
+	),
+	http_reply_file(Fragment, [mimetype('video/flv'), unsafe(true)], Request).
 
-%%	video_frame_reset is det.
+%%	video_fragment(+VideoFile, +Start, +End -Fragment)
 %
-%	Reset our dynamic data to symplify debugging after an error.
+%	@TBD
+
+video_fragment(Video, _, _, Video).
 
-video_frame_reset :-
-	retractall(video_frame_cache(_,_,_)).
+parse_time_param(S, Start, End) :-
+	concat_atom([Start, End], ',', S).
 
 %%	cache_tag_frames(+Video, +Game, +User)
 %
diff --git a/applications/yaz_player.pl b/applications/yaz_player.pl
index 6f02cea..d6836c2 100644
--- a/applications/yaz_player.pl
+++ b/applications/yaz_player.pl
@@ -25,7 +25,7 @@
 :- use_module(components(yaz_video_item)).
 
 :- http_handler(yaz(player), http_yaz_player, []).
-
+:- http_handler(yaz(data/tags), http_data_tags, []).
 
 %%	http_yaz_player(+Request)
 %
@@ -48,16 +48,26 @@ http_yaz_player(Request) :-
 			  confirmed(Confirmed,
 				    [boolean, default(false),
 				     description('When true only tags that are entered by >1 user are shown')]),
+			  query(Query,
+				[default(''),
+				 description('search string to filter the tags by')]),
 			  limit(Limit,
-				[default(10000), number,
+				[default(1000), number,
 				 description('limit number of tags shown')]),
+			  offset(Offset,
+				 [default(0), number,
+				  description('first result that is returned')]),
 			  start(StartTime,
 				[default(0),description('Start time of the video')])
 			]),
-	Options0 = [process(Process),
+	Options0 = [video(Video),
+		    process(Process),
 		    user(User),
 		    interval(Interval),
-		    confirmed(Confirmed)
+		    confirmed(Confirmed),
+		    query(Query),
+		    limit(Limit),
+		    offset(Offset)
  		  ],
 	delete_nonground(Options0, Options),
 	findall(P, video_process(Video, P, User), Processes0),
@@ -85,27 +95,72 @@ video_process(Video, Process, User) :-
 %	Emit an HTML page with a video player and a tag carousel.
 
 html_page(Video, Processes, Users, Annotations, StartTime, Options) :-
-	option(process(Process), Options, -),
-	option(user(User), Options, -),
-	delete(Options, process(_), POptions),
-	delete(Options, user(_), UOptions),
-	http_link_to_id(http_yaz_player, [video(Video)|POptions], PLink),
-	http_link_to_id(http_yaz_player, [video(Video)|UOptions], ULink),
+	option(query(Query), Options, ''),
 	reply_html_page(yaz,
 			[ title(['YAZ - ', Video])
 			],
 			[ \html_requires(css('player.css')),
 			  \yaz_video_header(Video),
- 			  div(id(tagplayer), []),
-			  div(id(videoplayer), []),
-			  div(class(facets),
-			      [ \html_facet(games, \html_process_list(Processes, Process, PLink)),
-				\html_facet(users, \html_user_list(Users, User, ULink))
+			  div([a([href('javascript:{}'), id(showOptions)],
+				 'show options')
+			      ]),
+			  div(id(configuration),
+			      [ \html_tag_options(Options),
+				\html_facets(Video, Processes, Users, Options)
+			      ]),
+			  div(id(tags),
+			      [ input([id(tagsearch), value(Query)]),
+				div(id(tagplayer), [])
+			      ]),
+			  div(id(video),
+			      [ div(id(timeline), []),
+				div(id(videoplayer), [])
 			      ]),
 			  script(type('text/javascript'),
 				\html_video_page_yui(Video, Annotations, StartTime, Options))
 			]).
 
+html_tag_options(Options) -->
+	{ option(confirmed(Confirmed), Options, false),
+	  option(subtitles(Subtitles), Options, true)
+	},
+	html(div(class(options),
+		 [ \html_select(confirmed, 'show only confirmed tags', Confirmed),
+		   \html_select(subtitles, 'remove tags in subtitles', Subtitles)
+		 ])).
+
+html_select(Id, Name, Value) -->
+	{ select_value(Value, Selected)
+	},
+	html(div(class(option),
+		 [input([type(checkbox), name(Id), Selected]),
+		  span(Name)
+		 ])).
+
+select_value(true, checked).
+select_value(false, '').
+
+html_tag_sliders(_Options) -->
+	{ %option(interval(Interval), Options),
+	  %option(occurrence(Occurrence), Options)
+	},
+	html(div(class(sliders),
+		 [])).
+
+html_facets(Video, Processes, Users, Options)  -->
+	{ option(process(Process), Options, -),
+	  option(user(User), Options, -),
+	  delete(Options, process(_), POptions),
+	  delete(Options, user(_), UOptions),
+	  http_link_to_id(http_yaz_player, [video(Video)|POptions], PLink),
+	  http_link_to_id(http_yaz_player, [video(Video)|UOptions], ULink)
+	},
+	html(div(class(facets),
+		 [ \html_facet(games, \html_process_list(Processes, Process, PLink)),
+		   \html_facet(users, \html_user_list(Users, User, ULink))
+		 ])).
+
+
 html_facet(Title, Content) -->
 	html(div(class(facet),
 		 [ h3(class('facet-title'), Title),
@@ -148,40 +203,60 @@ html_user_list([User|T], Selected, VideoPlayer) -->
 
 
 
-html_video_page_yui(Video, Annotations, StartTime, _Options) -->
-	{ video_source(Video, Src),
+html_video_page_yui(Video, Annotations, StartTime, Options) -->
+	{ video_source(Video, Src, Duration),
+	  http_location_by_id(http_data_tags, TagServer),
  	  http_absolute_location(js('videoplayer/'), FilePath, []),
 	  http_absolute_location(js('videoplayer/videoplayer.js'), VideoPlayer, []),
 	  http_absolute_location(js('tagcarousel/tagcarousel.js'), TagCarousel, []),
+	  http_absolute_location(js('timeline/timeline.js'), Timeline, []),
 	  annotation_to_json(Annotations, JSONTags)
    	},
-    html_requires(js('videoplayer/swfobject.js')),
+	html_requires(js('videoplayer/swfobject.js')),
  	js_yui3([{modules:{'video-player':{fullpath:VideoPlayer},
-			   'tag-carousel':{fullpath:TagCarousel}
+			   'tag-carousel':{fullpath:TagCarousel},
+			   'timeline':{fullpath:Timeline}
 			  }}
 		],
 		[node,event,widget,anim,
-  		 'video-player','tag-carousel'
+		 'json','querystring-stringify-simple',io,
+  		 'video-player','tag-carousel',timeline
  		],
 		[ \js_new(videoPlayer,
 			  'Y.mazzle.VideoPlayer'({filepath:FilePath,
  						  src:Src,
-						  width:640,
-						  height:480,
+						  width:540,
+						  height:400,
 						  autoplay:symbol(false),
 						  controls:symbol(true),
- 						  start:StartTime
+ 						  start:StartTime,
+						  duration:Duration
 						 })),
 		  \js_new(tagPlayer,
 			  'Y.mazzle.TagCarousel'({tags:JSONTags,
-						  height:480,
+						  height:400,
 						  width:200
 						 })),
+		  \js_new(timeline,
+			  'Y.mazzle.Timeline'({height:20,
+					       width:540,
+					       duration:Duration,
+					       items:JSONTags
+					      })),
   		  'var oldTime;\n',
+		  \js_yui3_decl(params, json(Options)),
+		  \js_yui3_decl(delayID, -1),
+		  \js_fetch_tags(TagServer),
  		  \js_call('videoPlayer.render'('#videoplayer')),
 		  \js_call('tagPlayer.render'('#tagplayer')),
+		  \js_call('timeline.render'('#timeline')),
   		  \js_yui3_on(videoPlayer, timeChange, \js_video_time_change),
-		  \js_yui3_on(tagPlayer, itemSelect, \js_tag_select)
+		  \js_yui3_on(tagPlayer, itemSelect, \js_tag_select),
+		  \js_yui3_delegate('.option', input, click, \js_option_select, []),
+		  \js_yui3_delegate(symbol('tagPlayer.listNode'), li, mouseover, \js_tag_hover, []),
+		  \js_yui3_on('Y.one("#showOptions")', click,
+			      'function() {Y.one("#configuration").toggleClass("hidden")}'),
+		  \js_yui3_on('Y.one("#tagsearch")', keyup,  \js_search)
   		]).
 
 js_tag_select -->
@@ -193,6 +268,13 @@ js_tag_select -->
      }\n'
 		    ]).
 
+js_tag_hover -->
+	js_function([e],
+		    \[
+'   var index = e.container.all("li").indexOf(e.currentTarget);
+    timeline.highlightIndex(index);\n'
+		     ]).
+
 js_video_time_change -->
 	js_function([e],
 		    \[
@@ -202,3 +284,92 @@ js_video_time_change -->
 	 tagPlayer.focusTime(Math.round(e.time)+1);
      }\n'
 		    ]).
+
+js_option_select -->
+	js_function([e],
+		    \[
+'     var params = Y.params,
+	  target = e.target,
+          param = target.get("name"),
+          value = target.get("checked");
+      params[param] = value;
+      fetchTags(params);\n'
+ 		    ]).
+
+js_fetch_tags(DataServer) -->
+	js_function_decl(syncUI, [e,o],
+			 \[
+'    var tags = Y.JSON.parse(o.responseText).tags;
+     tagPlayer.set("tags", tags);
+     timeline.set("items", tags);\n'
+			  ]),
+
+	js_function_decl(fetchTags, [conf],
+			  \[
+'    var data = Y.params;
+     if(conf) {
+	   for(var key in conf) { data[key] = conf[key] }
+     }\n',
+'    Y.io("',DataServer,'",
+	  { data: data,
+	    on: { success: syncUI },
+	  });\n'
+			   ]).
+
+js_search -->
+	js_function([e],
+		    \[
+'    var delay = 200,
+	 minQueryLength = 3,
+ 	 query = e.currentTarget.get("value");\n',
+'    if(Y.delayID != -1) { clearTimeout(Y.delayID); }
+     Y.params.query = (query.length < minQueryLength) ? "" : query;
+     Y.delayID = setTimeout(fetchTags, delay);\n'
+ 		     ]).
+
+
+
+%%	http_tags(+Request)
+%
+%	Data handler to serve tags for a video.
+
+http_data_tags(Request) :-
+		http_parameters(Request,
+			[ video(Video,
+				[description('Current video')]),
+			  process(Process,
+			       [optional(true),
+				desription('When set only annotations within this process are shown')]),
+			  user(User,
+				[optional(true),
+				 description('When set only annotations from this user are shown')]),
+			  interval(Interval,
+				   [default(10000), number,
+				    description('When set one entry per tag is returned in interval (in milliseconds)')]),
+			  confirmed(Confirmed,
+				    [boolean, default(false),
+				     description('When true only tags that are entered by >1 user are shown')]),
+			  query(Query,
+				[default(''),
+				 description('search string to filter the tags by')]),
+			  limit(Limit,
+				[default(10000), number,
+				 description('limit number of tags shown')]),
+			  offset(Offset,
+				 [default(0), number,
+				  description('first result that is returned')])
+ 			]),
+	Options = [process(Process),
+		   user(User),
+		   interval(Interval),
+		   confirmed(Confirmed),
+		   query(Query)
+		  ],
+  	% annotations
+ 	video_annotations(Video, Annotations0, Options),
+	sort_by_arg(Annotations0, 2, Annotations1),
+	list_offset(Annotations1, Offset, Annotations2),
+	list_limit(Annotations2, Limit, Annotations, _),
+	annotation_to_json(Annotations, JSONTags),
+  	reply_json(json([tags=JSONTags])).
+
diff --git a/components/yaz_page.pl b/components/yaz_page.pl
index df97b26..8780e20 100644
--- a/components/yaz_page.pl
+++ b/components/yaz_page.pl
@@ -66,11 +66,12 @@ cliopatria:search_pattern(Label, Target,
 	rdf(TN, PN, Tag),
 	rdf(Target, P, TN).
 
-cliopatria:format_search_result(R, Graph) -->
-	{ result_frame(R, Graph, Frame)
+cliopatria:format_search_result(R, Query, Graph) -->
+	{ Query = query(Search,_,_,_,_,_,_),
+	  result_frame(R, Graph, Frame)
 	},
 	html(div(class('result-item'),
-		 \yaz_video_result(R, [desc(true), frame(Frame)]))).
+		 \yaz_video_result(R, [desc(true), query(Search), frame(Frame)]))).
 
 cliopatria:facet_weight(P, 0) :-
 	rdf_equal(pprime:hasAnnotation, P).
diff --git a/lib/video_annotation.pl b/lib/video_annotation.pl
index 17d43e6..2cb48ca 100644
--- a/lib/video_annotation.pl
+++ b/lib/video_annotation.pl
@@ -36,6 +36,7 @@
 :- use_module(library(rdf_history)).
 :- use_module(library(user_process)).
 :- use_module(library(yaz_util)).
+:- use_module(library(find_resource)).
 
 /** <module> Handling of time-based video annotations
 
@@ -165,6 +166,30 @@ matching_annotation_value(V, V).
 video_annotation(Video, AnnotationId, Value, Time, Score) :-
 	video_annotation(Video, AnnotationId, Value, Time, Score, []).
 
+video_annotation(Video, AnnotationId, uri(Tag,Label), Time, Score, Options) :-
+	option(query(Query), Options),
+	Query \== '',
+	!,
+	option(process(Process), Options, _),
+	option(user(User), Options, _),
+	option(confirmed(Confirmed), Options, false),
+	find_literal(Query, prefix, Label),
+	rdf(Tag, rdfs:label, literal(Label)),
+	rdf(Tag, rdf:type, pprime:'Tag'),
+ 	rdf(AnnotationId, rdf:value, Tag),
+	annotation_in_process(Process, Video, AnnotationId),
+	rdf(AnnotationId, pprime:creator, User),
+	rdf(AnnotationId, pprime:videoPlayhead, Time0),
+	literal_to_number(Time0, Time),
+	(   rdf(AnnotationId, pprime:score, Score0)
+	->  literal_to_number(Score0, Score)
+	;   Score = 0
+	),
+	(   Confirmed
+	->  Score > 0
+	;   true
+	).
+
 video_annotation(Video, AnnotationId, Value, Time, Score, Options) :-
 	option(process(Process), Options, _),
 	option(user(User), Options, _),
@@ -200,9 +225,10 @@ annotation_in_process(Process, Video, AnnotationId) :-
 annotation_obj(V, Term) :-
 	(   V = literal(_)
 	->  Term = V
-	;   once(rdf_label(V, Lit)),
-	    literal_text(Lit, Label),
+	;   rdf_label(V, Lit)
+	->  literal_text(Lit, Label),
 	    Term = uri(V, Label)
+	;   Term = uri(V, V)
 	).
 
 
diff --git a/lib/yaz_util.pl b/lib/yaz_util.pl
index 44cd3b1..57ab08f 100644
--- a/lib/yaz_util.pl
+++ b/lib/yaz_util.pl
@@ -306,8 +306,9 @@ delete_nonground([_H|T], Rest) :-
 
 video_source(URL, Video, Duration) :-
 	video_source(URL, Video),
-	(   rdf(URL, pprime:duration, literal(Duration))
-	->  true%atom_number(Duration0, Duration)
+	(   rdf(URL, pprime:duration, literal(Duration0))
+	->  atom_number(Duration0, Duration1),
+	    Duration is Duration1*1000
 	;   Duration = 0
 	).
 
diff --git a/web/css/player.css b/web/css/player.css
index acde85c..068f0a2 100644
--- a/web/css/player.css
+++ b/web/css/player.css
@@ -25,19 +25,19 @@
 	color: #CCC;
 }
 #video {
-	overflow: hidden;
 	float: left;
+	margin-left: 10px;
 }
 /* tag list */
 
 /* tag player */
-#videoplayer {
+#tags {
 	float: left;
-	margin: 0 10px;
 }
-#tagplayer {
-	float: left;
+#tags input {
+	width: 98%;
 }
+
 #tagplayer.hidden {
 	display: none;
 }
@@ -230,15 +230,25 @@ ul.game-players {
 	float: right;
 }
 
+/* options */
+#configuration {
+	margin: 0 0 10px 10px;
+}	
+#configuration.hidden {
+	display: none;
+}
+
+.options {
+}
+
 /* facets */
 .facets {
-	overflow: hidden;
-	margin-bottom: 10px;
+	display: none;
 }
 .facet {
+	width: 100%;
 	font-size: 0.9em;
-    margin-bottom: 10px;
-    width: 100%;
+	margin-right: 10px;
 }
 .facet h3 {
    border-bottom: 1px solid #CCCCCC;
@@ -262,4 +272,29 @@ ul.game-players {
 }
 .facet li.selected a {
 	color: white;
+}
+
+/* timeline */
+.yui3-timeline {
+	background-color:#CCCCCC;
+	height:15px;
+	margin-bottom:5px;
+	width:100%;
+}
+.yui3-timeline ul {
+	margin: 0;
+	padding: 0;
+}
+.yui3-timeline li {
+	list-style: none;
+	position: absolute;
+	margin: 1px 0;
+	height: 18px;
+	background-color:yellow;
+}
+.yui3-timeline li.hidden {
+	display: none;
+}
+.yui3-timeline li.highlight {
+	background-color:red;
 }
\ No newline at end of file
diff --git a/web/js/timeline/timeline.js b/web/js/timeline/timeline.js
index cff7dcc..361a215 100644
--- a/web/js/timeline/timeline.js
+++ b/web/js/timeline/timeline.js
@@ -78,7 +78,6 @@ YUI.add('timeline', function(Y) {
 			var width = this.get("contentBox").get("offsetWidth"),
 				itemWidth = this.get("itemWidth"),
 				duration = this.get("duration");
-
 			if(duration) {
 				this._timePointDuration = (width/itemWidth)/duration;
 			}
@@ -89,14 +88,12 @@ YUI.add('timeline', function(Y) {
 				itemWidth = this.get("itemWidth"),
 				timePoints = {},
 				timePointDuration = this._timePointDuration;	
-			
 			this._listNode.setContent("");
-			
 			if(items&&timePointDuration) {
 				for(var i=0; i < items.length; i++) {
 					var item = items[i],
 						tag = item.tag,
-						time = item.time;
+						time = item.time||item.startTime;
 					
 					// The timepoint to which an item is added 
 					// depends on the duration of individual time points.