yaz/commit

ADD

authorMichiel Hildebrand
Sun Nov 6 15:48:52 2011 +0100
committerMichiel Hildebrand
Sun Nov 6 15:48:52 2011 +0100
commitd5c47160eca72a3f4113cc95d8059e444fa25b7c
treebb7c6439cc59f5b544f492cf73058ac1b6100a6c
parent804edc5da7160ae02f4e1b6a9e782cd922e46f9d
Diff style: patch stat
diff --git a/api/edm_export.pl b/api/edm_export.pl
index 84f5245..d9b20af 100644
--- a/api/edm_export.pl
+++ b/api/edm_export.pl
@@ -5,6 +5,8 @@
 :- use_module(library(http/http_parameters)).
 :- use_module(library(http/http_path)).
 :- use_module(library(http/http_json)).
+:- use_module(library(http/html_write)).
+:- use_module(library(http/html_head)).
 
 :- use_module(library(yaz_util)).
 :- use_module(library(video_annotation)).
@@ -13,9 +15,59 @@
 :- use_module(library(semweb/rdf_db)).
 :- use_module(library(semweb/rdf_label)).
 
+:- use_module(library(user_process)).
+:- use_module(components(yaz_page)).
 :- use_module(applications(yaz_shot_annotation)). %FIX this! We should not import from applications
 
 :- http_handler(yaz(api/edmexport), http_api_edm_export, []).
+:- http_handler(yaz(sipupdate), http_yaz_sip_update, []).
+
+
+%%	http_yaz_sip_update(+Request)
+%
+%	Export annotations for Video.
+
+http_yaz_sip_update(Request) :-
+	http_parameters(Request,
+			[ video(Video,
+				[description('Current video')]),
+			  shotLevel(ShotLevel,
+				    [boolean, default(true),
+				     description('When set to true only annotations at shot level are returned')
+				    ]),
+			  interval(Interval,
+				   [default(10), 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')])
+			]),
+	(   ShotLevel
+	->  video_shot_annotations(Video, Annotations)
+	;   video_annotations(Video, Annotations0,
+			      [interval(Interval),
+			       confirmed(Confirmed)
+			      ]),
+	    sort_by_arg(Annotations0, 2, Annotations)
+	),
+	%Id = '11111',
+	length(Annotations, Count),
+	%convert_annotations(Annotations, _XMLString),
+	%submit_mpeg(Id, XMLString),
+	% end TagGarden process
+	(   rdf(Process, opmv:used, Video),
+	    rdf(Process, rdf:type, pprime:'TagGarden')
+	->  end_user_process(Process)
+	;   true
+	),
+	reply_html_page(yaz,
+			[ title(['YAZ - SIP update: ', Video])
+			],
+			[ h2('SIP update'),
+			  p(Video),
+			  p([Count, ' annotations are added to the collection'])
+			]).
+
 
 %%	http_api_annotations(+Request)
 %
@@ -47,7 +99,7 @@ http_api_edm_export(Request) :-
 				 ])
 			]),
 	(   ShotLevel
-	->  video_shot_annotations(Video, Annotations)
+	->  video_shot_annotations(Video, Annotations1)
 	;   video_annotations(Video, Annotations0,
 			      [interval(Interval),
 			       confirmed(Confirmed)
@@ -60,10 +112,7 @@ http_api_edm_export(Request) :-
 	reply_annotations(Format, Annotations, Video, Total, Offset, Limit).
 
 reply_annotations(edm, Annotations, Video, _, _, _) :-
-	video_source_url(Video, Source),
-	edm_wrap(Video, Source, Proxy, EDMTriples),
-	annotations_to_edm(Annotations, Video, Source, Proxy, ProxyTriples),
-	append(EDMTriples, ProxyTriples, Triples),
+	edm_triples(Annotations, Video, Triples),
 	format('Content-type: application/rdf+xml; charset=UTF-8~n~n'),
 	rdf_write_xml(current_output, Triples).
 
@@ -75,6 +124,11 @@ reply_annotations(json, Annotations, Video, Total, Offset, Limit) :-
 			 limit=Limit,
 			 annotations=JSON])).
 
+edm_triples(Annotations, Video, Triples) :-
+	video_source_url(Video, Source),
+	edm_wrap(Video, Source, Proxy, EDMTriples),
+	annotations_to_edm(Annotations, Video, Source, Proxy, ProxyTriples),
+	append(EDMTriples, ProxyTriples, Triples).
 
 edm_wrap(Aggregation, Source, Proxy, Triples) :-
 	rdf_global_term([ rdf(Aggregation, rdf:type, ore:'Aggregation'),
@@ -166,3 +220,58 @@ annotation_value(uri(V, Label), Value, Label) :-
 	).
 annotation_value(literal(Lit), literal(Lit), Label) :-
 	literal_text(Lit, Label).
+
+
+/* metadata conversion */
+
+
+:- use_module(library(http/http_client)).
+
+conv_url('http://prestoprime.joanneum.at/conv/ppenv/vu/documents').
+update_url('https://p4.prestoprime.eu:8443/p4ws/ingest/update/usermd/').
+
+submit_mpeg(Id, XMLString) :-
+	update_url(URL),
+	atom_concat(URL, Id, UpdateURL),
+	http_post(UpdateURL, string('application/xml', XMLString), Out, []),
+	format('~w',Out).
+
+convert_annotations(Annotations, Result) :-
+	conv_url(URL),
+	edm_triples(Annotations, Video, Triples),
+	debug(edm_convert, 'submit annotations for ~w', [Video]),
+	new_memory_file(MemFile),
+	open_memory_file(MemFile, write, Stream),
+	rdf_write_xml(Stream, Triples),
+	close(Stream),
+	http_post(URL, memory_file('application/xml', MemFile), DocURL, []),
+	free_memory_file(MemFile),
+	debug(edm_convert, 'convert ~w', DocURL),
+	atom_concat(DocURL, '/startConversion', ConvertURL),
+	http_get(ConvertURL, _, []),
+	get_result(DocURL, Result).
+
+get_result(DocURL, Result) :-
+	http_get(DocURL, DataAtom, []),
+	debug(edm_convert, 'status:~w', DataAtom),
+	atom_to_pairs(DataAtom, Pairs),
+	memberchk(status=Status, Pairs),
+	(   Status = 'PENDING'
+	->  %memberchk(retryafter=Wait, Pairs),
+	    sleep(2),
+	    get_result(DocURL, Result)
+	;   Status = 'COMPLETED'
+	->  atom_concat(DocURL, '/result', ResultURL),
+	    http_get(ResultURL, Result, [])
+	    %http_delete(DocURL, _, [])
+	;   Result = ''
+	).
+
+atom_to_pairs(Atom, Pairs) :-
+	concat_atom(Data, '\n', Atom),
+	maplist(atom_to_pair, Data, Pairs).
+
+atom_to_pair(A, K=V) :-
+	concat_atom([K,V], '=', A),
+	!.
+atom_to_pair(A, A).
diff --git a/applications/yaz_shot_annotation.pl b/applications/yaz_shot_annotation.pl
index 2db6241..d8d3c84 100644
--- a/applications/yaz_shot_annotation.pl
+++ b/applications/yaz_shot_annotation.pl
@@ -30,6 +30,8 @@
 :- use_module(library(rdf_history)).
 :- use_module(library(user_process)).
 
+:- use_module(api(edm_export)).
+
 /*
 reconcile_source(person,
 		 'Person',
@@ -83,6 +85,7 @@ http_yaz_shot(Request) :-
 %	Emit an HTML page for concept gardening
 
 html_page(Video, Shots, Sources) :-
+	http_link_to_id(http_yaz_sip_update, [video(Video)], Update),
 	reply_html_page(yaz,
 			[ title(['YAZ - ', Video])
 			],
@@ -92,7 +95,9 @@ html_page(Video, Shots, Sources) :-
 			  div(class('yui3-g'),
 			      [ div([class('yui3-u'), id(nav)],
 				    [ div(class(hd), '1. Select shot'),
-				      div(id(videoframes), [])
+				      div(id(videoframes), []),
+				      div(a(href(Update),
+					    'Finish moderation'))
 				    ]),
 				div([class('yui3-u'), id(main)],
 				    [ div(class(hd), '2. View content'),
@@ -236,6 +241,9 @@ js_concept_select(Video) -->
 		     ]).
 
 
+
+
+
 		 /*******************************
 		 *	    DATA APIs		*
 		 *******************************/
diff --git a/lib/user_process.pl b/lib/user_process.pl
index f081ce6..ac9b7ca 100644
--- a/lib/user_process.pl
+++ b/lib/user_process.pl
@@ -107,8 +107,7 @@ end_user_process(Process) :-
 	rdfs_individual_of(Process, opmv:'Process'),
 	get_time(EndTime0),
 	format_iso_dateTime(EndTime0, EndTime),
-	rdf_transaction((rdf_assert(Process, opmv:wasEndedAt, literal(type(xsd:date, EndTime), Process), Process)
-			)),
+	rdf_transaction(rdf_assert(Process, opmv:wasEndedAt, literal(type(xsd:date, EndTime)), Process)),
 	debug(user_process, 'Process ~w ended at ~w', [Process, EndTime]).
 
 %%	join_user_process(+Process, +User)
diff --git a/lib/videos.pl b/lib/videos.pl
index e3fc01a..40f73ea 100644
--- a/lib/videos.pl
+++ b/lib/videos.pl
@@ -122,7 +122,7 @@ active_video(User, Video, Process, Time) :-
 	rdf(Process, opmv:wasControlledBy, User),
 	rdf(Process, rdf:type, pprime:'TagGarden'),
 	rdf(Process, opmv:wasStartedAt, literal(Time)),
-	\+ rdf(Process, opmv:wasEndAt, _).
+	\+ rdf(Process, opmv:wasEndedAt, _).
 
 %%	moderated_video(?User, ?Video, ?Process, -StartTime, -EndTime)
 %
@@ -133,7 +133,7 @@ moderated_video(User, Video, Process, StartTime, EndTime) :-
 	rdf(Process, opmv:wasControlledBy, User),
 	rdf(Process, rdf:type, pprime:'TagGarden'),
 	rdf(Process, opmv:wasStartedAt, literal(StartTime)),
-	rdf(Process, opmv:wasEndAt, literal(EndTime)).
+	rdf(Process, opmv:wasEndedAt, literal(EndTime)).
 
 %%	suggested_video(?User, ?Video, ?Process)
 %