:- module(yaz_edm_export, []). :- use_module(library(http/http_dispatch)). :- 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)). :- use_module(library(rdf_write)). :- use_module(library(semweb/rdf_db)). :- use_module(library(semweb/rdf_label)). :- use_module(library(yui3)). :- 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, []). conv_url('http://prestoprime.joanneum.at/conv/ppenv/vu/documents'). % update_url('https://p4.prestoprime.eu:8443/p4ws/ingest/update/usermd/'). update_url('https://10.2.7.176:8443/p4ws/ingest/update/usermd/'). %% http_yaz_sip_update(+Request) % % Export annotations for Video. http_yaz_sip_update(Request) :- http_parameters(Request, [ video(Video, [description('Current video')]), process(Process, [optional(true), description('Gardening process')]), 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')]) ]), % end TagGarden process ( nonvar(Process) -> end_user_process(Process) ; true ), ( ShotLevel -> video_shot_annotations(Video, Process, Annotations) ; video_annotations(Video, Annotations0, [interval(Interval), confirmed(Confirmed) ]), sort_by_arg(Annotations0, 2, Annotations) ), ( rdf(Video, pprime:slug, Slug) -> literal_text(Slug, Id) ; Id = 'no id' ), length(Annotations, Count), % convert EDM conv_url(SubmitURL), update_url(UpdateURL), edm_triples(Annotations, Video, Triples), new_memory_file(MemFile), open_memory_file(MemFile, write, Stream), rdf_write_xml(Stream, Triples), close(Stream), memory_file_to_atom(MemFile, EDM), http_post(SubmitURL, 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, MPEG), reply_html_page(yaz, [ title(['YAZ - SIP update: ', Id]) ], [ \html_requires(yui3('cssgrids/grids-min.css')), h2('SIP update'), div(class(desc), [Count, ' annotations for ', Id]), div(class('yui3-g fields'), [ div(class('yui3-u-1-2'), [h3('Europeana Data Model'), textarea([id(edm),style('width:100%;height:400px')], EDM) ]), div(class('yui3-u-1-2'), [h3('MPEG-7'), form([method('POST'), action(UpdateURL), enctype('multipart/form-data'), style('padding:0 20px') ], [ input([type(hidden), name(id), value(Id)], []), textarea([id(mpeg),name(file),style('width:100%;height:400px')], MPEG), a(href(DocURL), 'check conversion'), ' :: ', a(href(DocURL+'/result'), 'fetch conversion'), p(input([type(file), name(file)])), p(input([type(submit), value('Submit')])) ]) ]) ]), script(type('text/javascript'), [])%\html_page_yui(Id, DocURL)) ]). html_page_yui(Id, DocURL) --> js_yui3([], [node,event,io ], [ 'var sipID = ', Id, ';', 'var docURL = ', DocURL, ';' ]). /* p([' Go back to ', a(href(location_by_id(http_yaz_home)), 'your videos')]) ]). http_location_by_id(http_yaz_home, Home), throw(http_reply(moved_temporary(Home))). reply_html_page(yaz, [ title(['YAZ - SIP update: ', Video]) ], [ h2('SIP update'), %p(Video), p([Count, ' annotations are added to the collection']), p([' Go back to ', a(href(location_by_id(http_yaz_home)), 'your videos')]) ]). */ %% http_api_annotations(+Request) % % Handler for the annotation API. http_api_edm_export(Request) :- http_parameters(Request, [ video(Video, [description('Current video')]), process(Process, [optional(true), description('Gardening process')]), 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')]), limit(Limit, [default(10000), number, description('limit number of tags shown')]), offset(Offset, [default(0), number, description('first result that is returned')]), format(Format, [default(edm), oneof([json,edm]), description('Format of the output') ]) ]), ( ShotLevel -> video_shot_annotations(Video, Process, Annotations1) ; video_annotations(Video, Annotations0, [interval(Interval), confirmed(Confirmed) ]), sort_by_arg(Annotations0, 2, Annotations1) ), length(Annotations1, Total), list_offset(Annotations1, Offset, Annotations2), list_limit(Annotations2, Limit, Annotations, _), reply_annotations(Format, Annotations, Video, Total, Offset, Limit). reply_annotations(edm, Annotations, Video, _, _, _) :- edm_triples(Annotations, Video, Triples), format('Content-type: application/rdf+xml; charset=UTF-8~n~n'), rdf_write_xml(current_output, Triples). reply_annotations(json, Annotations, Video, Total, Offset, Limit) :- annotation_to_json(Annotations, JSON), reply_json(json([video=Video, totalNumberOfResults=Total, offset=Offset, 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'), rdf(Aggregation, ens:hasView, Source), rdf(Aggregation, dc:creator, pprime:''), rdf(Proxy, rdf:type, ore:'Proxy'), rdf(Proxy, rdf:type, ma:'MediaResource'), rdf(Proxy, ore:proxyIn, Aggregation) ], Triples), prefix_url(Aggregation, 'proxy/', Proxy). annotations_to_edm([], _, _, _, []). annotations_to_edm([A|As], Video, Source, Proxy, Triples) :- A = annotation(Tag, Start, End, _Entries, _Score), !, StartTime is round(Start/1000), EndTime is round(End/1000), fragment_url(Video, StartTime, EndTime, Fragment), fragment_url(Source, StartTime, EndTime, FragmentSource), prefix_url(Fragment, 'proxy/', FragmentProxy), %rdf_bnode(FragmentProxy), prefix_url(Fragment, 'aggregation/', Aggregation), Duration is EndTime-StartTime, rdf_global_term([ rdf(Proxy, ma:hasFragment, FragmentProxy), rdf(Aggregation, rdf:type, ore:'Aggregation'), rdf(Aggregation, ens:hasView, FragmentSource), rdf(FragmentProxy, rdf:type, ore:'Proxy'), rdf(FragmentProxy, rdf:type, ma:'MediaFragment'), rdf(FragmentProxy, ore:proxyIn, Aggregation), rdf(FragmentProxy, dc:subject, literal(Label)),%TagObject), rdf(FragmentProxy, ma:duration, literal(Duration)), rdf(FragmentProxy, ebucore:start, literal(StartTime)) ], Ts), append(Ts, Rest, Triples), annotation_value(Tag, _TagObject, Label), annotations_to_edm(As, Video, Source, Proxy, Rest). annotations_to_edm([A|As], Video, Source, Proxy, Triples) :- A = shot_annotation(Shot, Start, Duration0, Values), !, StartTime is round(Start/1000), Duration is round(Duration0/1000), EndTime is StartTime+Duration, fragment_url(Source, StartTime, EndTime, ShotSource), prefix_url(Shot, 'proxy/', ShotProxy), shot_annotations_to_edm(Values, ShotProxy, Annotations), rdf_global_term([ rdf(Proxy, ma:hasFragment, ShotProxy), rdf(Shot, rdf:type, ore:'Aggregation'), rdf(Shot, ens:hasView, ShotSource), rdf(ShotProxy, rdf:type, ore:'Proxy'), rdf(ShotProxy, rdf:type, ma:'MediaFragment'), rdf(ShotProxy, ore:proxyIn, Shot), rdf(ShotProxy, ma:duration, literal(Duration)), rdf(ShotProxy, ebucore:start, literal(StartTime)) |Annotations ], Ts), append(Ts, Rest, Triples), annotations_to_edm(As, Video, Source, Proxy, Rest). shot_annotations_to_edm([], _, []). shot_annotations_to_edm([concept(URI,Label,_Type)|Vs], Proxy, [rdf(Proxy,dc:subject,literal(Label)), rdf(Proxy,dc:subject,URI) %rdf(URI,rdf:type,Type), %rdf(URI,rdfs:label,Label) |Rest ]) :- shot_annotations_to_edm(Vs, Proxy, Rest). fragment_url(Video, Start, End, Fragment) :- concat_atom([Video, '#t=', Start, ',', End], Fragment). prefix_url(URL, Prefix, NewURL) :- rdf_global_id(NS:Local, URL), atom_concat(Prefix, Local, PLocal), rdf_global_id(NS:PLocal, NewURL). video_source_url(Video, Source) :- rdf(Video, pprime:source, Source), sub_atom(Source, 0, _, _, 'http'). %entry_triple(BNode, i(E,_), rdf(BNode, pprime:tagEntry, E)). annotation_value(uri(V, Label), Value, Label) :- ( rdf(V, rdf:type, pprime:'Tag') -> rdf(V, rdfs:label, literal(Label)), Value = literal(Label) ; format(atom(Value), '~q', V) % hack to get full resources and bypass errors in local names ). annotation_value(literal(Lit), literal(Lit), Label) :- literal_text(Lit, Label). /* metadata conversion */ :- use_module(library(http/http_client)). 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(1), 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).