:- module(yaz_player, [ http_yaz_player/1 ]). :- use_module(library(http/http_dispatch)). :- use_module(library(http/http_parameters)). :- use_module(library(http/http_path)). :- use_module(library(http/html_write)). :- use_module(library(http/html_head)). :- use_module(library(http/http_json)). :- use_module(library(http/js_write)). :- use_module(library(http/json)). :- use_module(library(http/http_session)). :- use_module(user(user_db)). :- use_module(library(semweb/rdf_db)). :- use_module(library(semweb/rdfs)). :- use_module(library(semweb/rdf_label)). :- use_module(library(settings)). :- use_module(library(yaz_util)). :- use_module(library(yui3)). :- use_module(library(video_annotation)). :- use_module(applications(yaz_tag_edit)). :- use_module(components(label)). :- use_module(components(yaz_page)). :- use_module(components(yaz_video_item)). :- use_module(library(rdf_history)). :- use_module(library(user_process)). :- use_module(library(videos)). :- http_handler(yaz(player), http_yaz_player, []). :- http_handler(yaz(data/tags), http_data_tags, []). :- http_handler(yaz(data/relatedtags), http_data_related_tags, []). :- http_handler(yaz(data/updateentries), http_data_update_entries, []). :- setting(player_type, oneof([auto,html,flash,silverlight,npo]), auto, 'The type of player that is used. When not defined we guess the required player based on the extension of the video stream.'). %% http_yaz_player(+Request) % % Emit the a video player with a tag carousel running along side % of it. http_yaz_player(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(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')]), query(Query, [default(''), description('search string to filter the tags by')]), type(Type, [default(false), description('filter tags by type')]), role(Role, [default(false), description('filter tags by role')]), limit(Limit, [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 = [video(Video), process(Process), user(User), confirmed(Confirmed), interval(Interval), query(Query), type(Type), role(Role), limit(Limit), offset(Offset) ], delete_nonground(Options0, Options), %findall(P, video_process(Video, P, User), Processes0), %findall(U, video_process(Video, Process, U), Users0), %sort(Processes0, Processes), %sort(Users0, Users), % annotations video_annotations(Video, Annotations0, Options), sort_by_arg(Annotations0, 2, Annotations1), list_limit(Annotations1, Limit, Annotations, _), html_page(Video, Annotations, StartTime, Options). %% video_process(+Video, -Process, -User) % % Process has used Video. video_process(Video, Process, User) :- rdf(Process, opmv:used, Video), rdf(Process, rdf:type, pprime:'Game'), rdf_has(Process, opmv:wasControlledBy, User). type_option(false, 'filter by type'). type_option(person, person). type_option(location, location). type_option(subject, subject). role_option(false, 'filter by role'). role_option(depicted, depicted). role_option(associated, associated). %% html_page(+Video, +Annotations, +StartTime, %% +Options) % % Emit an HTML page with a video player and a tag carousel. html_page(Video, Annotations, StartTime, Options) :- option(query(Query), Options, ''), %option(type(Type), Options, 'filter by type'), %findall(option(V, typefilter, N), type_option(V, N), TypeOptions), %option(role(Role), Options, 'filter by role'), %findall(option(V, rolefilter, N), role_option(V, N), RoleOptions), reply_html_page(yaz, [ title(['YAZ player - ', Video]) ], [ \html_requires(css('player.css')), \html_requires(css('tag.css')), \html_video_status(Video), \yaz_video_header(Video), div([style('display:none'), class(controls)], [a([href('javascript:{}'), id(toggleOptions)], 'show options'), a([href('javascript:{}'), id(toggleFrames)], 'show frames') ]), div([style('display:none'), id(configuration), class(hidden)], [ \html_tag_options(Options), \html_tag_sliders(Options) %\html_facets(Video, Processes, Users, Options) ]), div(id(tags), [ /*div(select([id(tagtype), name(type), value(Type)], \html_select_options(TypeOptions))), div(select([id(tagrole), name(role), value(Role)], \html_select_options(RoleOptions))),*/ div(input([id(tagsearch), autocomplete(false), value(Query)])), div(id(tagplayer), []) ]), div(id(video), [ div(id(timeline), []), div(id(videoplayer), []), div([id(videoframes), class(hidden)], []) ]), div([id(tagEdit), class(hidden)], []), script(type('text/javascript'), \html_video_page_yui(Video, Annotations, StartTime, Options)) ]). html_video_status(Video) --> { moderated_video(User, Video, _Process, StartTime, EndTime) }, !, html(div(class(status), ['This video was moderated by ', User, ' from ', StartTime, ' to ', EndTime])). html_video_status(Video) --> { active_video(User, Video, _Process, StartTime), logged_on(User0, false), user_property(User0, url(User)), http_link_to_id(http_yaz_shot, [video(Video)], ShotAnnotation), http_link_to_id(http_yaz_garden, [video(Video)], TagGarden) }, !, html(div(class(status), ['You started moderation of this video at ', StartTime, ul([li(['Continue tag gardening I:', a(href(TagGarden), ' cleanup tags')]), li(['Continue tag gardening II:', a(href(ShotAnnotation), ' annotate video shots')]) ]) ])). html_video_status(Video) --> { active_video(User, Video, _Process, StartTime) }, !, html(div(class(status), ['This video is under moderation by ', User, ' from ', StartTime ])). html_video_status(Video) --> { http_link_to_id(http_yaz_garden_accept, [video(Video)], HREF) }, html(div(class(status), ['This video is not yet under moderation', div(a(href(HREF), 'accept moderation')) ])). html_select_options([]) --> !. html_select_options([option(Value, Name, Label)|Ts]) --> html(option([value(Value), name(Name)], Label)), html_select_options(Ts). html_tag_options(Options) --> { option(confirmed(Confirmed), Options, false), option(subtitles(Subtitles), Options, true) }, html(div(class(options), [ \html_select(confirmed, 'remove tags without score', 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), [ div([class(control), id(interval)], []) ])). 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), div(class('facet-content'), Content) ])). html_process_list([], _, _) --> !. html_process_list([Process|T], Selected, VideoPlayer) --> { rdf(Process, opmv:wasStartedAt, L), literal_text(L, Time0), display_time(Time0, Time), ( Process == Selected -> Class = selected, Link = VideoPlayer ; Class = item, Link = VideoPlayer+'&process='+Process ) }, html(li(class(Class), a(href(Link), [Time]))), html_process_list(T, Selected, VideoPlayer). html_user_list([], _, _) --> !. html_user_list([User|T], Selected, VideoPlayer) --> { rdf_display_label(User, Label), ( User == Selected -> Class = selected, Link = VideoPlayer ; Class = item, Link = VideoPlayer+'&user='+User ) }, html(li(class(Class), a(href(Link), [Label]))), html_user_list(T, Selected, VideoPlayer). html_video_page_yui(Video, Annotations, StartTime, Options) --> { option(query(Query), Options, ''), setting(player_type, PlayerType), video_source(Video, Src, Duration), option(interval(Interval), Options, 0), http_location_by_id(serve_video_frame, FrameServer), http_absolute_location(js('videoplayer/'), FilePath, []), http_absolute_location(js('videoplayer/videoplayer.js'), Videoplayer, []), http_absolute_location(js('videoframes/videoframes.js'), VideoFrames, []), http_absolute_location(js('tagplayer/tagplayer.js'), Tagplayer, []), http_absolute_location(js('timeline/timeline.js'), Timeline, []), http_absolute_location(js('valueslider/valueslider.js'), Valueslider, []), annotation_freq(Annotations, Annotations1), annotation_to_json(Annotations1, JSONTags), list_limit(JSONTags, 50, JSONFrames, _) }, html_requires(js('videoplayer/swfobject.js')), js_yui3([{modules:{'video-player':{fullpath:Videoplayer}, 'video-frames':{fullpath:VideoFrames}, 'tag-player':{fullpath:Tagplayer}, 'timeline':{fullpath:Timeline}, 'value-slider':{fullpath:Valueslider} }} ], [node,event,widget,anim,slider, 'json','querystring-stringify-simple',io, 'video-player','video-frames','tag-player', timeline,'value-slider' ], [ \js_new(videoPlayer, 'Y.mazzle.VideoPlayer'({filepath:FilePath, src:Src, width:560, height:400, autoplay:symbol(false), controls:symbol(true), start:StartTime, duration:Duration, playerType:PlayerType })), \js_new(videoFrames, 'Y.mazzle.VideoFrames'({frameServer:FrameServer, frames:JSONFrames, video:Src, duration:Duration, playerPath:FilePath, width:560, confirm:symbol(true) })), \js_new(tagPlayer, 'Y.mazzle.TagPlayer'({tags:JSONTags, height:380, width:200, edit:symbol(true) })), \js_new(timeline, 'Y.mazzle.Timeline'({height:20, width:560, duration:Duration, items:JSONTags })), \js_new(intervalSlider, 'Y.mazzle.ValueSlider'({node:symbol('Y.one("#interval")'), name:interval, label:'group same tags in interval:', min:0, max:60, value:Interval })), 'var oldTime;\n', \js_yui3_decl(params, json(Options)), \js_yui3_decl(delayID, -1), \js_fetch_tags, \js_fetch_tag_frames, \js_fetch_tag_info, \js_update_entries(Video), \js_call('videoPlayer.render'('#videoplayer')), \js_call('videoFrames.render'('#videoframes')), \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(intervalSlider, valueUpdate, \js_slider_select), \js_yui3_delegate('.option', input, click, \js_option_select, []), \js_yui3_on(tagPlayer, itemHover, \js_tag_hover), \js_yui3_on(videoFrames, frameHover, \js_tag_hover), \js_yui3_on(videoFrames, roleSelect, \js_role_select(Video)), \js_yui3_on('Y.one("#toggleOptions")', click, \js_toggle_options), \js_yui3_on('Y.one("#toggleFrames")', click, \js_toggle_frames), \js_yui3_on('Y.one("#tagsearch")', keyup, \js_search), \js_yui3_on('Y.one("#tagtype")', change, \js_filter), \js_yui3_on('Y.one("#tagrole")', change, \js_filter), \js_call(fetchTagInfo(Query)) ]). annotation_freq([], []). annotation_freq([annotation(V,S,E,Es,_)|T], [annotation(V,S,E,Es,Count)|Rest]) :- length(Es, Count), annotation_freq(T, Rest). js_toggle_options --> js_function([e], \[ ' Y.one("#configuration").toggleClass("hidden");\n' ]). js_toggle_frames --> js_function([e], \[ ' var frames = Y.one("#videoframes") video = Y.one("#videoplayer");\n', ' if(frames.hasClass("hidden")) { e.target.setContent("show video"); videoPlayer.pause(); video.addClass("hidden"); frames.removeClass("hidden"); Y.one("#tagEdit").removeClass("hidden"); }\n', ' else { e.target.setContent("show frames"); frames.addClass("hidden"); video.removeClass("hidden"); Y.one("#tagEdit").addClass("hidden"); }\n' ]). js_fetch_tags --> { http_location_by_id(http_data_tags, Server) }, js_function_decl(syncUI, [e,o], \[ ' var tags = Y.JSON.parse(o.responseText).tags; tagPlayer.set("tags", tags); videoFrames.set("frames", tags); videoFrames.set("related", []); timeline.set("items", tags); if(Y.params.query) {fetchTagInfo(Y.params.query);}\n' ]), js_function_decl(fetchTags, [conf], \[ ' var data = Y.params; if(conf) { for(var key in conf) { data[key] = conf[key] } }\n', ' Y.io("',Server,'", { data: data, on: { success: syncUI }, });\n' ]), js_function_decl(updateTags, [], \[ ' Y.io("',Server,'", { data: Y.params, on: { success: function(e,o) { var tags = Y.JSON.parse(o.responseText).tags; tagPlayer.set("tags", tags);}}, });\n' ]). js_fetch_tag_frames --> { http_location_by_id(http_data_related_tags, Server) }, js_function_decl(setFrames, [e,o], \[ ' var r = Y.JSON.parse(o.responseText); videoFrames.set("related", r.related); videoFrames.set("frames", r.frames);\n' ]), js_function_decl(fetchTagFrames, [entry], \[ ' var data = Y.params; data.entry = entry; Y.io("',Server,'", { data: data, on: { success: setFrames }})\n' ]). js_fetch_tag_info --> { http_location_by_id(http_yaz_tag_edit, Server) }, js_function_decl(setTagInfo, [e,o], \[ ' Y.one("#tagEdit").setContent(o.responseText); Y.one("#apply").on("click", function() {updateEntries()}); Y.one("#applyall").on("click", function() {updateEntries(true)});\n' ]), js_function_decl(fetchTagInfo, [entry], \[ ' if(entry) { Y.io("',Server,'", { data: {entry:entry, format:"form"}, on: { success: setTagInfo }}) };\n' ]). js_tag_select --> js_function([e], \[ ' Y.tag = e.tag; var data = Y.params; var entry = e.tag.annotations[0].uri;\n', % hack, there can be multiple entries grouped in one tag ' if(e.tag.startTime&&!Y.one("#videoplayer").hasClass("hidden")) { var time = (e.tag.startTime/1000)-2; videoPlayer.setTime(time, true); }\n', ' if(!Y.one("#videoframes").hasClass("hidden")) { fetchTagFrames(entry); }\n', ' fetchTagInfo(entry);\n' ]). js_tag_hover --> js_function([e], \[ ' timeline.highlightIndex(e.index);\n' ]). js_video_time_change --> js_function([e], \[ ' var time = Math.round(e.time); if(time!==oldTime) { oldTime = time; 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_slider_select --> js_function([e], \[ ' var params = Y.params; params[e.name] = e.value; fetchTags(params);\n' ]). js_search --> js_function([e], \[ ' var delay = 200, minQueryLength = 2, 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' ]). js_filter --> js_function([e], \[ ' var filter = e.target.get("name"); e.target.get("options").each( function() { if(this.get("selected")&&this.get("value")) { var conf = {}; if(this.get("value")) {conf[filter] = this.get("value")} fetchTags(conf) }});\n' ]). js_update_entries(Video) --> { http_location_by_id(http_data_update_entries, Server) }, js_function_decl(updateEntries, [all], \[ ' var entry = Y.tag ? Y.tag.annotations[0].uri : Y.params.query, entries = [], as = videoFrames.get("frames"), rs = videoFrames.get("related");\n', ' if(Y.tag) { entries.push(Y.tag.annotations[0].uri) } else { for(var i=0; i { http_location_by_id(http_data_update_entries, Server) }, js_function([o], \[ ' var entries = []; if(o.frame.annotations) { for(var j=0;j1 user are shown')]), query(Query, [default(''), description('search string to filter the tags by')]), type(Type, [default(false), description('filter tags by type')]), role(Role, [default(false), description('filter tags by role')]), 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), type(Type), role(Role) ], % 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])). %% http_data_related_tags(+Request) % % Emit a JSON object with all frames for a given tag and video. http_data_related_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 created by this user are shown')]), entry(Entry, [optional(true), jsonresource, description('tag entry to find related tags for')]), limit(Limit, [default(50), number, description('limit number of tags shown')]), offset(Offset, [default(0), number, description('first result that is returned')]) ]), Options = [process(Process), user(User) ], rdf(Entry, rdf:value, Tag), Obj = Time-json([entry=Id, tag=json([uri=Tag, label=Label]), startTime=Time, role=R]), findall(Obj, (video_annotation(Video, Id, uri(Tag,Label), Time, _, Options), tag_role(Id, R) ), Entries0), keysort(Entries0, Entries1), list_offset(Entries1, Offset, Entries2), list_limit(Entries2, Limit, Entries, _), pairs_values(Entries, Related0), select(json([entry=Entry|F]), Related0, Related), reply_json(json([frames=[json([entry=Entry|F])], related=Related])). tag_role(Entry, Role) :- rdf(Entry, pprime:role, literal(Role)), !. tag_role(_Entry, false). %% http_data_update_entries(+Request) % % Emit an HTML page with gardening options for a tag. http_data_update_entries(Request) :- http_parameters(Request, [ video(Video, [description('video we are updating entries of')]), entries(Entries, [zero_or_more, description('entries to update')]), value(Value, [optional(true), description('text value')]), concept(Concept, [optional(true), description('Link to a concept')]), role(Role, [default(false), description('role of the tag')]) ]), logged_on(User0, anonymous), user_property(User0, url(User)), ( current_user_process(Process), rdf(Process, rdf:type, pprime:'TagGarden'), rdf(Process, opmv:used, Video) -> true ; create_user_process(User, [rdf:type=pprime:'TagGarden', opmv:used=Video ], _GardenProcess) ), rdfh_transaction(update_entries(Entries, Value, Concept, Role, Updated)), reply_json(Updated). update_entries([], _, _, _, []). update_entries([Entry|Es], Value, Concept, Role, [json([entry=Entry, tag=NewTag, role=Role])|Rest]) :- update_value(Entry, Concept, Value, NewTag), update_role(Entry, Role), update_entries(Es, Value, Concept, Role, Rest). update_value(E, Concept, _Value, Concept) :- nonvar(Concept), !, rdf(E, rdf:value, Tag), rdfh_update(E, rdf:value, Tag->Concept). update_value(E, _Concept, Value, Tag) :- nonvar(Value), !, rdf(E, rdf:value, Tag0), rdf(Tag0, rdf:type, pprime:'Tag'), ( rdf(Tag0, rdfs:label, literal(Value)) -> Tag = Tag0 ; rdf(Tag, rdfs:label, literal(Value)) -> rdfh_update(E, rdf:value, Tag0->Tag) ; new_tag(Value), rdfh_update(E, rdf:value, Tag0->Tag) ). update_value(_, _, _, unknown). update_role(E, Role) :- nonvar(Role), !, %rdf_global_id(pprime:role, URL), rdfh_retractall(E, pprime:role, _), ( Role == rejected -> rdfh_retractall(_, pprime:hasAnnotation, E) ; rdfh_assert(E, pprime:role, literal(Role)) ). update_role(_, _). new_tag(Value) :- rdf_bnode(Tag), rdfh_assert(Tag, rdf:type, pprime:'Tag'), rdfh_assert(Tag, rdfs:label, literal(Value)).