yaz/commit

put video item presentation in seperate file

authorMichiel Hildebrand
Sat Feb 12 19:37:47 2011 +0100
committerMichiel Hildebrand
Sat Feb 12 19:37:47 2011 +0100
commit593f6c13cc16c4c0a88cc2e1f259d5a31c6653ba
tree5a69e35ccb6dbfc5a6238c4a56a5a9863d11e291
parent549c91b9827170c8014e9696eeee6dd8d17c0fb4
Diff style: patch stat
diff --git a/applications/yaz_video.pl b/applications/yaz_video.pl
new file mode 100644
index 0000000..22d1e3c
--- /dev/null
+++ b/applications/yaz_video.pl
@@ -0,0 +1,87 @@
+:- module(yaz_video,
+	  []).
+
+:- 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(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(components(yaz_page)).
+:- use_module(components(yaz_video_item)).
+:- use_module(components(paginator)).
+
+:- http_handler(yaz(video), http_yaz_video, []).
+
+%%	http_yaz_video(+Request)
+%
+%       Emit a all videos a user has annotated.
+
+http_yaz_video(Request) :-
+	http_parameters(Request,
+			[ video(Video,
+				[description('URL of a video')]),
+			  offset(Offset,
+				[default(0), integer, description('Offset of the result list')]),
+			  limit(Limit,
+				[default(20), integer, description('Limit on the number of results')])
+  			]),
+	findall(process(Process, Time),
+		annotation_process(_, Video, Process, Time),
+		Processes),
+	length(Processes, NumberOfResults),
+  	list_offset(Processes, Offset, OffsetResults),
+	list_limit(OffsetResults, Limit, LimitResults, _),
+ 	html_page(Video, LimitResults, NumberOfResults, Offset, Limit).
+
+%%	html_page(+Video, +Processes, +NumberOfResults, +Offset, +Limit,
+%%	+User, +Annotation)
+%
+%	Emit HTML page with a list of Videos.
+
+html_page(Video, Processes, NumberOfResults, Offset, Limit) :-
+	http_link_to_id(http_yaz_player, [video(Video)], Player),
+	reply_html_page(yaz,
+			[ title(['YAZ - ', Video])
+			],
+			[ \yaz_video_header(Video),
+			  ol(class('result-list'),
+			     \html_process_list(Processes, Player)),
+			   div(class(paginator),
+			       \html_paginator(NumberOfResults, Offset, Limit))
+
+			]).
+
+
+
+%%	html_process_list(+Processes, +VideoURL, +VideoPlayer)
+%
+%	Emit list of processes.
+
+html_process_list([], _) --> !.
+html_process_list([process(Process, Time0)|T], VideoPlayer) -->
+	{ rdf(Process, rdf:type, Type0),
+	  rdf_display_label(Type0, Type),
+	  display_time(Time0, Time),
+	  Players = []
+	},
+	html(li([ div(class('process'),
+		      [Type, ' at ', Time,
+		       ' (', a(href(VideoPlayer+'&process='+Process), play), ')'
+		      ]),
+		  div(class('players'),
+		      \html_players(Players, VideoPlayer))
+		])),
+	html_process_list(T, VideoPlayer).
+
+
+html_players(_, _) --> !.
+
diff --git a/components/yaz_video_item.pl b/components/yaz_video_item.pl
new file mode 100644
index 0000000..37a2c82
--- /dev/null
+++ b/components/yaz_video_item.pl
@@ -0,0 +1,86 @@
+:- module(yaz_video_item,
+	  [yaz_video_header//1,   % +VideoURL
+	   yaz_video_item//1,     % +VideoURL
+	   yaz_video_result//2    % +VideoURL, +Options
+	  ]).
+
+:- 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(user(user_db)).
+:- use_module(library(http/http_wrapper)).
+:- use_module(library(semweb/rdf_db)).
+:- use_module(library(semweb/rdf_label)).
+
+
+%%	yaz_video_header(+VideoURL)
+%
+%	Emit html with info about Video as a page header.
+
+yaz_video_header(Video) -->
+	{ display_label(Video, Title),
+	  video_desc(Video, Desc)
+  	},
+ 	html(div(class('video-header'),
+		 [h2(class(title), Title),
+		  div(class(desc), Desc)
+		 ])).
+
+
+%%	yaz_video_item(+VideoURL)
+%
+%	Emit html with info about a Video.
+
+yaz_video_item(URL) -->
+ 	{ display_label(URL, Title),
+	  video_source(URL, Video),
+	  truncate_atom(Title, 100, ShortTitle),
+	  video_desc(URL, Description)
+ 	},
+	html(div(class('video-item'),
+		 [ div(class('video-thumb'),
+		       \yaz_video_image(Video)),
+ 		   div([class('title'), title(Title)],
+		       ShortTitle),
+		   div(class('desc'),
+		       Description)
+		 ])).
+
+yaz_video_image(Video) -->
+	{ http_link_to_id(serve_video_frame, [url(Video),time(5)], FrameURL)
+	},
+	html(img([width('140px'), alt('no image available'), src(FrameURL)], [])).
+
+
+%%	yaz_video_result(+VideoURL)
+%
+%	Emit html with search result representation of VideoURL.
+
+yaz_video_result(URL, Options) -->
+	{ display_label(URL, Title),
+	  video_source(URL, Video),
+	  truncate_atom(Title, 47, ShortTitle),
+	  (   option(desc(true), Options)
+	  ->  video_desc(URL, Description)
+	  ;   Description = ''
+	  ),
+	  option(frame(Frame), Options, 5),
+	  delete(Options, desc(_), Options1),
+	  http_link_to_id(http_yaz_player, [video(URL)|Options1], Link),
+	  http_link_to_id(serve_video_frame, [url(Video),time(Frame)], FrameURL)
+ 	},
+	html(div(class('video-result'),
+		[ a(href(Link),
+		    [ div(class('video-thumb'),
+			  img([width('140px'), alt('no image available'),
+			       title(Title), src(FrameURL)], [])),
+		      div(class('title'),
+			  a([href(Link),title(Title)],
+			    ShortTitle)),
+		      div([class('desc'), title(Description)],
+			  Description)
+		   ])
+ 		])).