:- module(yaz_fplayer,
	  []).
:- 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(yaz_util)).
:- use_module(library(yui3)).
:- use_module(library(video_annotation)).
:- use_module(library(lod_load)).
:- use_module(components(label)).
:- use_module(components(yaz_page)).
:- use_module(components(yaz_video_item)).
:- use_module(api(reconcile)).
:- http_handler(yaz(fplayer), http_yaz_fplayer, []).
subject(R) :-
	rdf(R, skos:inScheme, gtaa:'Onderwerpen').
subject(R) :-
	rdf(R, skos:inScheme, 'http://purl.org/vocabularies/cornetto'),
	\+ rdf(R, cornetto:domain, wn20i:'domain-geography').
location(R) :-
	rdf(R, rdf:type, 'http://rdf.freebase.com/ns/location.location').
location(R) :-
	rdf(R, skos:inScheme, gtaa:'GeografischeNamen').
person(R) :-
	rdf(R, rdf:type, 'http://rdf.freebase.com/ns/people.person').
person(R) :-
	rdf(R, skos:inScheme, gtaa:'Persoonsnamen').
%person(R) :-
	%rdf(R, skos:inScheme, gtaa:'Namen').
%%	http_yaz_fplayer(+Request)
%
%	Emit an HTML page to link tags to concepts.
http_yaz_fplayer(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')])
			]),
	Options0 = [video(Video),
		    process(Process),
		    user(User),
		    confirmed(Confirmed),
		    interval(Interval)
		  ],
	delete_nonground(Options0, Options),
	video_annotations(Video, Annotations, Options),
	maplist(annotation_pair, Annotations, TagEntries0),
	merge_entries(TagEntries0, TagEntries),
	concept_entries(TagEntries, Video, subject, Subjects, Rest0, [stem(true)]),
	concept_entries(Rest0, Video, location, Locations, Rest, []),
	concept_entries(Rest, Video, person, Persons, _, []),
	html_page(Video, Subjects, Locations, Persons, Options).
annotation_pair(annotation(Value,_,_,[E0|_],_), Value-E1) :-
	E0 = i(URI, Time),
	E1 = entry(URI,Value,Time).
concept_entries(TagEntries, Video, Goal, ConceptEntries, Rest, Options) :-
	option(stem(Stem), Options, false),
	concept_entries_(TagEntries, Video, Goal, Stem, ConceptEntries0, Rest),
	merge_entries(ConceptEntries0, ConceptEntries1),
	maplist(concept_pair, ConceptEntries1, ConceptEntries).
concept_entries_([], _, _, _, [], []).
concept_entries_([Tag-Entries|Ts], Video, Goal, Stem, [Concept-Entries|Cs], Rest) :-
	tag_concept(Tag, Video, Goal, Stem, Concept),
	!,
	concept_entries_(Ts, Video, Goal, Stem, Cs, Rest).
concept_entries_([Tag-Entries|Ts], Video, Goal, Stem, Cs, [Tag-Entries|Rest]) :-
	concept_entries_(Ts, Video, Goal, Stem, Cs, Rest).
tag_concept(Tag, Video, Goal, _, Concept) :-
	tag_uri(Tag, URI),
	rdf(Reconcile, pprime:tag, URI),
	rdf(Reconcile, pprime:video, Video),
	rdf(Reconcile, pprime:concept, Concept),
	call(Goal, Concept).
tag_concept(Tag, Goal, Stem, Concept) :-
	tag_value(Tag, Value0),
	stem(Stem, Value0, Value),
	reconcile(Value, 3, Hits),
	member(hit(_,Concept,_,_), Hits),
	call(Goal, Concept).
stem(_, V, V).
stem(true, V, Stem) :-
	snowball(dutch, V, Stem).
concept_pair(Concept-Es, annotation(uri(Concept,Label), 0, 0, Es)) :-
	rdf_display_label(Concept, Label).
%%	html_page(+Video, +Concepts, +Options)
%
%	Emit an HTML page for concept gardening
html_page(Video, Subjects, Locations, Persons, Options) :-
	reply_html_page(yaz,
			[ title(['YAZ - ', Video])
			],
			[ \html_requires(css('fplayer.css')),
			  \html_requires('http://freebaselibs.com/static/suggest/1.3/suggest.min.css'),
			  \yaz_video_header(Video),
			  div(id(tags),
			      [ div(input([id(tagsearch), autocomplete(false)])),
				\tag_facet(person, 'Person/Organization'),
				\tag_facet(location, 'Location'),
				\tag_facet(subject, 'Subject')
			      ]),
			  div(id(video),
			      [ div(id(videoplayer), []),
				div([id(videoframes)], [])
			      ]),
			  div(id(info),
			      []),
			  script(type('text/javascript'),
				\html_video_page_yui(Video, Subjects, Locations, Persons, Options))
			]).
tag_facet(Id, Label) -->
	html(div(class(tagfacet),
		 [ div(class(hd), Label),
		   div(class(bd),
		       div(id(Id), []))
		 ])).
html_video_page_yui(Video, Subjects, Locations, Persons, Options) -->
	{ video_source(Video, Src, Duration),
	  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, []),
	  annotation_to_json(Persons, JSONPersons),
	  annotation_to_json(Locations, JSONLocations),
	  annotation_to_json(Subjects, JSONSubjects)
	},
	html_requires(js('videoplayer/swfobject.js')),
	js_yui3([{modules:{'video-player':{fullpath:Videoplayer},
			   'video-frames':{fullpath:VideoFrames},
			   'tag-player':{fullpath:Tagplayer},
			   'timeline':{fullpath:Timeline}
			  }}
		],
		[node,event,widget,anim,
		 'json','jsonp','querystring-stringify-simple',io,
		 'video-player','video-frames','tag-player',
		 timeline
		],
		[ \js_new(person,
			 'Y.mazzle.TagPlayer'({tags:JSONPersons,
					       height:150,
					       width:200,
					       topIndent:symbol(false)
					      })),
		  \js_new(location,
			  'Y.mazzle.TagPlayer'({tags:JSONLocations,
						height:150,
						width:200,
						topIndent:symbol(false)
					       })),
		  \js_new(subject,
			 'Y.mazzle.TagPlayer'({tags:JSONSubjects,
					       height:150,
					       width:200,
					       topIndent:symbol(false)
					      })),
		  \js_new(videoPlayer,
			  'Y.mazzle.VideoPlayer'({filepath:FilePath,
						  src:Src,
						  width:560,
						  height:400,
						  autoplay:symbol(false),
						  controls:symbol(true),
						  duration:Duration
						 })),
		  \js_new(videoFrames,
			 'Y.mazzle.VideoFrames'({frameServer:FrameServer,
						 video:Src,
						 duration:Duration,
						 playerPath:FilePath,
						 width:560,
						 confirm:symbol(false),
						 showRelated:symbol(false),
						 showTime:symbol(true)
						})),
		  \js_yui3_decl(params, json(Options)),
		  \js_flyout,
		  \js_call('videoPlayer.render'('#videoplayer')),
		  \js_call('videoFrames.render'('#videoframes')),
		  \js_call('person.render'('#person')),
		  \js_call('location.render'('#location')),
		  \js_call('subject.render'('#subject')),
		  \js_yui3_on(person, itemSelect, \js_tag_select),
		  \js_yui3_on(location, itemSelect, \js_tag_select),
		  \js_yui3_on(subject, itemSelect, \js_tag_select),
		  \js_yui3_on(videoFrames, frameSelect, \js_frame_select)
		]).
js_tag_select -->
	js_function([e],
		    \[
'    var tag = e.tag;
     var entry = tag.annotations[0];\n',
'    var time = (entry.startTime/1000)-3;
     videoPlayer.setTime(time, true);\n',
'    videoFrames.set("frames", tag.annotations);
     fetchFlyout(tag.tag.value);\n'
		     ]).
js_frame_select -->
	js_function([e],
		    \[
'    var frame = e.frame;
     var time = (frame.startTime/1000)-3;
     videoPlayer.setTime(time, true);\n'
		     ]).
js_flyout -->
	js_function_decl(fetchFlyout, [uri],
			 \[
'   var id = uri.substring(29);
    var request = "http://www.freebase.com/private/flyout?callback={callback}&id=/m/"+id;
    Y.jsonp(request, function(response) { console.log(response);Y.one("#info").setContent(response.html);})'
			  ]).
merge_entries(Pairs, Merged) :-
	keysort(Pairs, Sorted),
	group_pairs_by_key(Sorted, Grouped),
	maplist(value_flatten, Grouped, Merged).
value_flatten(Key-Lists, Key-List) :-
	flatten(Lists, List).
tag_value(literal(Tag), Tag).
tag_value(uri(_URI,Tag), Tag).
tag_uri(uri(URI,_), URI).
freebase_base('http://rdf.freebase.com/rdf/m.').
freebase_uri_base('http://rdf.freebase.com/ns/m.').
freebase_ids(IDs) :-
	findall(ID, ( rdf(_,pprime:concept,MID),
		      atom_concat('/m/', ID, MID)
		    ),
		IDs0),
	sort(IDs0, IDs).
freebase_fetch([]).
freebase_fetch([ID|IDs]) :-
	freebase_base(Base),
	atom_concat(Base, ID, URI),
	debug(freebase_fetch, 'fetch ~w~n', URI),
	catch(lod_load(URI), _E, true),
	freebase_fetch(IDs).
freebase_id_to_uri([]).
freebase_id_to_uri([ID|IDs]) :-
	freebase_uri_base(Base),
	atom_concat(Base, ID, URI),
	atom_concat('/m/',ID, MID),
	rdf_transaction(forall(rdf(S,P,MID),
			       (   rdf_retractall(S,P,MID),
				   rdf_assert(S,P,URI)
			       ))),
	freebase_id_to_uri(IDs).
:- multifile
	label_property/1.