yaz/commit

final changes MMM2012

authorMichiel Hildebrand
Mon Aug 15 12:23:02 2011 +0200
committerMichiel Hildebrand
Mon Aug 15 12:23:02 2011 +0200
commit5e3414496268ef7be5400413ca740ea68b1fe16b
tree1e6f0ebd1f307a6dfc07fa1d66c5aeb11e5838c8
parenteeeef2aa92f857f1a782e3745963579c26021e78
Diff style: patch stat
diff --git a/applications/yaz_fplayer.pl b/applications/yaz_fplayer.pl
index 50d1af2..e187097 100644
--- a/applications/yaz_fplayer.pl
+++ b/applications/yaz_fplayer.pl
@@ -18,6 +18,7 @@
 :- 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)).
@@ -34,12 +35,16 @@ subject(R) :-
 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, skos:inScheme, gtaa:'Persoonsnamen').
+	rdf(R, rdf:type, 'http://rdf.freebase.com/ns/people.person').
 person(R) :-
-	rdf(R, skos:inScheme, gtaa:'Namen').
+	rdf(R, skos:inScheme, gtaa:'Persoonsnamen').
+%person(R) :-
+	%rdf(R, skos:inScheme, gtaa:'Namen').
 
 
 %%	http_yaz_fplayer(+Request)
@@ -73,28 +78,35 @@ http_yaz_fplayer(Request) :-
 	video_annotations(Video, Annotations, Options),
 	maplist(annotation_pair, Annotations, TagEntries0),
 	merge_entries(TagEntries0, TagEntries),
-	concept_entries(TagEntries, subject, Subjects, Rest0, [stem(true)]),
-	concept_entries(Rest0, location, Locations, Rest, []),
-	concept_entries(Rest, person, Persons, _, []),
+	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, Goal, ConceptEntries, Rest, Options) :-
+concept_entries(TagEntries, Video, Goal, ConceptEntries, Rest, Options) :-
 	option(stem(Stem), Options, false),
-	concept_entries_(TagEntries, Goal, Stem, ConceptEntries0, Rest),
+	concept_entries_(TagEntries, Video, Goal, Stem, ConceptEntries0, Rest),
 	merge_entries(ConceptEntries0, ConceptEntries1),
 	maplist(concept_pair, ConceptEntries1, ConceptEntries).
 
-concept_entries_([], _, _, [], []).
-concept_entries_([Tag-Entries|Ts], Goal, Stem, [Concept-Entries|Cs], Rest) :-
-	tag_concept(Tag, Goal, Stem, Concept),
+concept_entries_([], _, _, _, [], []).
+concept_entries_([Tag-Entries|Ts], Video, Goal, Stem, [Concept-Entries|Cs], Rest) :-
+	tag_concept(Tag, Video, Goal, Stem, Concept),
 	!,
-	concept_entries_(Ts, Goal, Stem, Cs, Rest).
-concept_entries_([Tag-Entries|Ts], Goal, Stem, Cs, [Tag-Entries|Rest]) :-
-	concept_entries_(Ts, Goal, Stem, Cs, Rest).
+	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),
@@ -119,10 +131,11 @@ html_page(Video, Subjects, Locations, Persons, Options) :-
 			[ title(['YAZ - ', Video])
 			],
 			[ \html_requires(css('fplayer.css')),
-			  \html_requires(css('tag.css')),
+			  \html_requires('http://freebaselibs.com/static/suggest/1.3/suggest.min.css'),
 			  \yaz_video_header(Video),
 			  div(id(tags),
-			      [ \tag_facet(person, 'Person/Organization'),
+			      [ div(input([id(tagsearch), autocomplete(false)])),
+				\tag_facet(person, 'Person/Organization'),
 				\tag_facet(location, 'Location'),
 				\tag_facet(subject, 'Subject')
 			      ]),
@@ -130,6 +143,8 @@ html_page(Video, Subjects, Locations, Persons, Options) :-
 			      [ div(id(videoplayer), []),
 				div([id(videoframes)], [])
 			      ]),
+			  div(id(info),
+			      []),
 			  script(type('text/javascript'),
 				\html_video_page_yui(Video, Subjects, Locations, Persons, Options))
 			]).
@@ -161,7 +176,7 @@ html_video_page_yui(Video, Subjects, Locations, Persons, Options) -->
 			  }}
 		],
 		[node,event,widget,anim,
-		 'json','querystring-stringify-simple',io,
+		 'json','jsonp','querystring-stringify-simple',io,
 		 'video-player','video-frames','tag-player',
 		 timeline
 		],
@@ -203,6 +218,7 @@ html_video_page_yui(Video, Subjects, Locations, Persons, Options) -->
 						 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')),
@@ -219,10 +235,11 @@ js_tag_select -->
 	js_function([e],
 		    \[
 '    var tag = e.tag;
-     var entry = tag.annotations[0];console.log(entry);\n',
+     var entry = tag.annotations[0];\n',
 '    var time = (entry.startTime/1000)-3;
      videoPlayer.setTime(time, true);\n',
-'    videoFrames.set("frames", tag.annotations);\n'
+'    videoFrames.set("frames", tag.annotations);
+     fetchFlyout(tag.tag.value);\n'
 		     ]).
 
 js_frame_select -->
@@ -232,6 +249,13 @@ js_frame_select -->
      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);})'
+			  ]).
 
 
 
@@ -246,3 +270,40 @@ value_flatten(Key-Lists, Key-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.
+
diff --git a/applications/yaz_garden.pl b/applications/yaz_garden.pl
index e10d123..fc261bb 100644
--- a/applications/yaz_garden.pl
+++ b/applications/yaz_garden.pl
@@ -30,12 +30,6 @@
 :- http_handler(yaz(garden), http_yaz_garden, []).
 :- http_handler(yaz(data/reconcileentries), http_data_reconcile_entries, []).
 
-
-reconcile_source(cornetto,
-		 'Cornetto',
-		 Server,
-		 '&type=http://purl.org/vocabularies/cornetto/Synset') :-
-	http_location_by_id(http_reconcile, Server).
 reconcile_source(gtaa,
 		 'GTAA',
 		 Server,
@@ -43,13 +37,18 @@ reconcile_source(gtaa,
 	http_location_by_id(http_reconcile, Server),
 	www_form_encode('[{"http://www.w3.org/2004/02/skos/core#inScheme":"http://data.beeldengeluid.nl/gtaa/GTAA"}]',Ps),
 	atom_concat('&properties=',Ps,Params).
-reconcile_source(geogname,
-		 'Geonames',
-		 'http://api.kasabi.com/api/reconciliation-api-geonames',
-		'&apikey=908177a484aa25f9b602d3eb76cf057d73e7aa39').
+reconcile_source(cornetto,
+		 'Cornetto',
+		 Server,
+		 '&type=http://purl.org/vocabularies/cornetto/Synset') :-
+	http_location_by_id(http_reconcile, Server).
+%reconcile_source(geonames,
+%		 'Geonames',
+%'http://api.kasabi.com/api/reconciliation-api-geonames',
+%		'&apikey=908177a484aa25f9b602d3eb76cf057d73e7aa39').
 reconcile_source(dbpedia,
 		 'DBPedia',
-		 'http://api.kasabi.com/api/reconciliation-api-dbpedia-36',
+'http://api.kasabi.com/api/reconciliation-api-dbpedia-36',
 		 '&apikey=908177a484aa25f9b602d3eb76cf057d73e7aa39').
 reconcile_source(freebase,
 		 'Freebase',
@@ -57,7 +56,7 @@ reconcile_source(freebase,
 		 '').
 
 
-%%	http_yaz_garden(+Request)
+%%	Http_Yaz_Garden(+Request)
 %
 %	Emit an HTML page to link tags to concepts.
 
@@ -116,25 +115,21 @@ html_page(Video, Annotations, Groups, Sources, Options) :-
 			[ title(['YAZ - ', Video])
 			],
 			[ \html_requires(css('garden.css')),
-			  \html_requires(css('tag.css')),
 			  \yaz_video_header(Video),
 			  div(id(tags),
-			      [	div(id(tagplayer), []),
+			      [	div(id(taglist), []),
 				div(class(box),
 				    [ div(class(hd), 'Reconcile'),
 				      div([class(bd), id(tagreconcile)], [])
 				    ])
 			      ]),
+			  div(id(frames),
+			      [	div(id(videoframes), [])
+			      ]),
 			  div(id(video),
 			      [ div(id(timeline), []),
-				div(id(videoplayer), []),
-				div(id(videoframes), [])
+				div(id(videoplayer), [])
 			      ]),
-			  div(id(resources),
-			      div(class(box),
-				    [ div(class(hd), 'Resources'),
-				      div([class(bd), id(taglinker)], [])
-				    ])),
 			  script(type('text/javascript'),
 				\html_video_page_yui(Video, Annotations, Groups, Sources, Options))
 			]).
@@ -150,42 +145,36 @@ html_video_page_yui(Video, Annotations, Groups, ReconcileSources, Options) -->
 	  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('videoframes/videoframes.js'), Videoframes, []),
+	  http_absolute_location(js('tagplayer/taglist.js'), Taglist, []),
 	  http_absolute_location(js('tagplayer/tagreconcile.js'), Tagreconcile, []),
-	  http_absolute_location(js('tagplayer/taglinker.js'), Taglinker, []),
 	  http_absolute_location(js('timeline/timeline.js'), Timeline, []),
 	  annotation_to_json(Annotations, JSONTags),
 	  annotation_to_json(Groups, JSONTagGroups)
 	},
 	html_requires(js('videoplayer/swfobject.js')),
 	js_yui3([{modules:{'video-player':{fullpath:Videoplayer},
-			   'video-frames':{fullpath:VideoFrames},
-			   'tag-player':{fullpath:Tagplayer},
+			   'video-frames':{fullpath:Videoframes},
+			   'tag-list':{fullpath:Taglist},
 			   'tag-reconcile':{fullpath:Tagreconcile},
-			   'tag-linker':{fullpath:Taglinker},
 			   'timeline':{fullpath:Timeline}
 			  }}
 		],
 		[node,event,widget,anim,
 		 'json','jsonp','querystring-stringify-simple',io,
 		 'video-player','video-frames',timeline,
-		 'tag-player','tag-reconcile','tag-linker'
+		 'tag-list','tag-reconcile'
 		],
-		[ \js_new(tagPlayer,
-			 'Y.mazzle.TagPlayer'({tags:JSONTagGroups,
-					       height:350,
-					       width:200,
-					       topIndent:symbol(false)
-					      })),
+		[ \js_new(tagList,
+			 'Y.mazzle.TagList'({tags:JSONTagGroups,
+					     height:425,
+					     width:200
+					    })),
 		   \js_new(tagReconcile,
 			 'Y.mazzle.TagReconcile'({height:200,
-						  width:200,
-						  sources:ReconcileSources
-					      })),
-		  \js_new(tagLinker,
-			 'Y.mazzle.TagLinker'({height:400,
-					       width:195
+						  width:190,
+						  sources:ReconcileSources,
+						  limit:10
 					      })),
 		  \js_new(videoPlayer,
 			  'Y.mazzle.VideoPlayer'({filepath:FilePath,
@@ -199,12 +188,14 @@ html_video_page_yui(Video, Annotations, Groups, ReconcileSources, Options) -->
 		  \js_new(videoFrames,
 			 'Y.mazzle.VideoFrames'({frameServer:FrameServer,
 						 video:Src,
+						 width:200,
+						 height:425,
 						 duration:Duration,
 						 playerPath:FilePath,
-						 width:560,
-						 confirm:symbol(true),
+						 confirm:symbol(false),
 						 showRelated:symbol(false),
-						 showTime:symbol(true)
+						 showTime:symbol(true),
+						 disabled:symbol(true)
 						})),
 		  \js_new(timeline,
 			  'Y.mazzle.Timeline'({height:20,
@@ -212,43 +203,39 @@ html_video_page_yui(Video, Annotations, Groups, ReconcileSources, Options) -->
 					       duration:Duration,
 					       items:JSONTags
 					      })),
-		  'tagReconcile.set("tags", tagPlayer.get("tags"));',
+		  'tagReconcile.set("tags", tagList.get("tags"));',
 		  \js_yui3_decl(params, json(Options)),
 		  \js_yui3_decl(delayID, -1),
 		  \js_yui3_render(videoFrames, #(videoframes)),
 		  \js_yui3_render(videoPlayer, #(videoplayer)),
 		  \js_yui3_render(timeline, #(timeline)),
-		  \js_yui3_render(tagPlayer, #(tagplayer)),
+		  \js_yui3_render(tagList, #(taglist)),
 		  \js_yui3_render(tagReconcile, #(tagreconcile)),
-		  \js_yui3_render(tagLinker, #(taglinker)),
-		  \js_yui3_on(tagPlayer, itemSelect, \js_tag_select),
+		  %\js_yui3_render(tagLinker, #(taglinker)),
+		  \js_yui3_on(tagList, itemSelect, \js_tag_select),
+		  \js_yui3_on(tagList, reconcileSelect, \js_reconcile_select(Video)),
 		  \js_yui3_on(videoFrames, frameHover, \js_frame_hover),
 		  \js_yui3_on(videoFrames, frameSelect, \js_frame_select),
 		  \js_yui3_on(tagReconcile, reconcileStart, \js_reconcile_start),
-		  \js_yui3_on(tagReconcile, reconcileReturn, \js_reconcile_return),
-		  \js_yui3_on(tagLinker, applySelect, \js_apply_select(Video))
+		  \js_yui3_on(tagReconcile, reconcileReturn, \js_reconcile_return)
 		]).
 
 js_tag_select -->
 	js_function([e],
-		    \['console.log(e);\n',
+		    \[
 '    var tag = e.tag,
-	 uri = tag.tag.value,
          entry = tag.annotations[0],
-         time = (entry.startTime/1000)-3,
-	 reconciled = Y.reconciled;\n',
-'   videoPlayer.setTime(time, true);
-    videoFrames.set("frames", tag.annotations);\n',
-'   Y.currentTagNode = e.li;
-    var items = (reconciled&&reconciled[uri]) ? reconciled[uri].result : [];
-    tagLinker.set("items", items);'
+         time = (entry.startTime/1000)-10;\n',
+'   videoPlayer.pause();
+    videoFrames.set("frames", tag.annotations);
+    videoFrames.set("disabled", false);\n'
 		     ]).
 
 js_frame_select -->
 	js_function([e],
 		    \[
 '    var frame = e.frame;
-     var time = (frame.startTime/1000)-3;
+     var time = (frame.startTime/1000)-8;
      videoPlayer.setTime(time, true);\n'
 		     ]).
 
@@ -258,49 +245,35 @@ js_frame_hover -->
 '   timeline.highlightIndex(e.index);\n'
 		     ]).
 
-js_reconcile_start -->
-	js_function([],
-		    \[
-'    tagPlayer.listNode.all("li .score").setContent("").addClass("hidden");'
-		     ]).
 
-js_reconcile_return -->
-	js_function([o],
-		    \[
-'    Y.reconciled = o.reconciled,
-         tags = tagPlayer.get("tags");\n',
-'    tagPlayer.listNode.all("li").each(function(node, index) {
-	 var tag = tags[index].tag,
-	     r = Y.reconciled[tag.value];
-	 if(r&&r.result.length>0) {node.one(".score").setContent("?").removeClass("hidden")}
-	    })'
-		     ]).
-
-
-js_apply_select(Video) -->
+js_reconcile_select(Video) -->
 	{ http_location_by_id(http_data_reconcile_entries, Server)
 	},
 	js_function([o],
 		    \[
-'    var frames = videoFrames.get("frames"),
-	 selected = videoFrames.get("selected"),
-	 entries = [];\n',
-'    if(o.applyToAll) { for(var i=0;i<frames.length;i++) {entries.push(frames[i].entry) }}
-     else if(selected) { entries[0] = selected.entry }
-     else { entries[0] = frames[0].entry }\n',
 '    Y.io("',Server,'",
 	  { data: {video:"',Video,'",
-	           uri:o.item.id,
-		   entries:entries
+	           uri:o.uri,
+		   tag:o.tag,
+		   index:o.index
 		  },\n',
 '	    on: { success: function(e,o) {
-		   Y.currentTagNode.one(".score").setContent("c");
-		   var annotations = Y.JSON.parse(o.responseText);
-		   videoFrames.set("frames", annotations);
-		}},
+		    Y.log("reconcilation saved as: "+Y.JSON.parse(o.responseText).reconciliation); }
+		},
 	  });\n'
 		     ]).
 
+js_reconcile_start -->
+	js_function([],
+		    \[
+'    tagList.resetReconciled();'
+		     ]).
+
+js_reconcile_return -->
+	js_function([o],
+		    \[
+'    tagList.setReconciled(o.reconciled, o.startIndex, o.endIndex);'
+		     ]).
 
 %%	http_data_reconcile_entries(+Request)
 %
@@ -310,10 +283,12 @@ http_data_reconcile_entries(Request) :-
 	http_parameters(Request,
 			[ video(Video,
 			       [description('video we are updating entries of')]),
-			  entries(Entries,
-				[zero_or_more, description('entries to update')]),
+			  tag(Tag,
+				[escription('tag being reconciled')]),
 			  uri(URI,
-			      [description('Link to a concept')])
+			      [description('Link to a concept')]),
+			  index(Index,
+				[])
 			]),
 	logged_on(User0, anonymous),
 	user_property(User0, url(User)),
@@ -325,17 +300,13 @@ http_data_reconcile_entries(Request) :-
 				       opmv:used=Video
 				      ], _GardenProcess)
 	),
-	rdfh_transaction(reconcile_entries(Entries, URI, Updated)),
-	reply_json(Updated).
-
-reconcile_entries([], _, []).
-reconcile_entries([Entry|Es], URI, [json([entry=Entry, tag=NewTag, startTime=Time])|Rest]) :-
-	reconcile_entry(Entry, URI),
-	NewTag = json([value=URI, label=Label]),
-	rdf(Entry, pprime:videoPlayhead, Time0),
-	literal_to_number(Time0, Time),
-	rdf_display_label(URI, Label),
-	reconcile_entries(Es, URI, Rest).
+	rdfh_transaction(reconcile_tag(Video, Tag, URI, Index, Event)),
+	reply_json(json([reconciliation=Event])).
 
-reconcile_entry(Entry, URI) :-
-	rdf_assert(Entry, pprime:reconciled, URI).
+reconcile_tag(Video, Tag, URI, Index, R) :-
+	rdf_bnode(R),
+	rdfh_assert(R, rdf:type, pprime:'Reconciliation'),
+	rdfh_assert(R, pprime:video, Video),
+	rdfh_assert(R, pprime:tag, Tag),
+	rdfh_assert(R, pprime:concept, URI),
+	rdfh_assert(R, pprime:index, literal(Index)).
diff --git a/applications/yaz_player.pl b/applications/yaz_player.pl
index 567ec28..704f817 100644
--- a/applications/yaz_player.pl
+++ b/applications/yaz_player.pl
@@ -131,13 +131,13 @@ html_page(Video, Annotations, StartTime, Options) :-
 			[ \html_requires(css('player.css')),
 			  \html_requires(css('tag.css')),
 			  \yaz_video_header(Video),
-			  div(class(controls),
+			  div([style('display:none'), class(controls)],
 			      [a([href('javascript:{}'), id(toggleOptions)],
 				 'show options'),
 			       a([href('javascript:{}'), id(toggleFrames)],
 				 'show frames')
 			      ]),
-			  div([id(configuration), class(hidden)],
+			  div([style('display:none'), id(configuration), class(hidden)],
 			      [ \html_tag_options(Options),
 				\html_tag_sliders(Options)
 				%\html_facets(Video, Processes, Users, Options)
diff --git a/lib/find_concept.pl b/lib/find_concept.pl
new file mode 100644
index 0000000..cdac03b
--- /dev/null
+++ b/lib/find_concept.pl
@@ -0,0 +1,101 @@
+:- module(concept_entries,
+	  [ concept_entries/3  % +Video, -Pairs:list(concept-entries), +Options
+	  ]).
+
+:- use_module(library(semweb/rdf_db)).
+:- use_module(library(semweb/rdf_label)).
+:- use_module(library(video_annotation)).
+:- use_module(api(reconcile)).
+
+:- rdf_meta
+	type_scheme(+,r).
+
+type_scheme(subject, gtaa:'Onderwerpen').
+type_scheme(location, gtaa:'GeografischeNamen').
+type_scheme(person, gtaa:'Persoonsnamen').
+type_scheme(person, gtaa:'Namen').
+%type_scheme(person, gtaa:'Maker').
+
+
+concept_entries(Video, ConceptEntries, Options) :-
+	option(max(Max), Options, 3),
+	option(types(Types), Options, [subject,person,location]),
+	video_annotations(Video, Annotations, Options),
+		maplist(annotation_pair, Annotations, TagEntries0),
+	merge_entries(TagEntries0, TagEntries),
+
+concept_entries(TagEntries, Filter, ConceptEntries, Rest) :-
+	concept_entries_(TagEntries, ConceptEntries0m Rest),
+	merge_entries(ConceptEntries0, ConceptEntri
+
+concept_entries_([Tag-Entries|Ts], Filter, [Concept-Entries|Cs], Rest) :-
+	tag_concept(Tag, Filter, Concept),
+	concept_entries_(Ts, Filter, Cs, Rest).
+
+	merge_entries(ConceptEntries0, ConceptEntries1),
+	group_by_type(ConceptEntries1, ConceptEntries).
+
+tag_concept(Tag, Max, Types, Concept, Type) :-
+	tag_value(Tag, Value),
+	%snowball(dutch, Value, Stem0),
+	%downcase_atom(Value, Stem),
+	reconcile(Value, Max, Hits0),
+	one_concept_per_type(Hits0, Types, Hits),
+	member(Type-Concept, Hits).
+
+one_concept_per_type(_, [], []) :- !.
+one_concept_per_type([], _, []) :- !.
+one_concept_per_type([hit(D,R,_,_)|Hs], Types, Cs) :-
+	(   D > 3
+	->  Cs = []
+	;   rdf(R, skos:inScheme, Scheme),
+	    \+ rdf_equal(gtaa:'GTAA', Scheme),
+	    scheme_in_types(Types, Scheme, Type, Types1)
+	->  Cs = [Type-R|Cs1]
+	),
+	one_concept_per_type(Hs, Types1, Cs1).
+one_concept_per_type([_|Hs], Types, Concepts) :-
+	one_concept_per_type(Hs, Types, Concepts).
+
+scheme_in_types([Type|Ts], Scheme, Type, Ts) :-
+	type_scheme(Type, Scheme),
+	!.
+scheme_in_types([Type0|Ts], Scheme, Type, [Type0|Rest]) :-
+	scheme_in_types(Ts, Scheme, Type, Rest).
+
+
+
+
+group_by_type([], []).
+group_by_type([c(Type,C)-Es|T], [Type-Annotations|Rest]) :-
+	same_type([c(Type,C)-Es|T], Type, Annotations, Cs1),
+	group_by_type(Cs1, Rest).
+
+same_type([c(Type,C)-Es|T], Type, [Annotation|Cs], Rest) :-
+	!,
+	Annotation = annotation(uri(C,Label),0,0,Es),
+	rdf_display_label(C, Label),
+	same_type(T, Type, Cs, Rest).
+same_type(T, _, [], T).
+
+
+annotation_pair(annotation(Value,_,_,Es0,_), Value-Es) :-
+	convert_entries(Es0, Value, Es).
+
+convert_entries([], _, []).
+convert_entries([i(URI,Time)|Is], Value,
+		[entry(URI,Value,Time)|Es]) :-
+	convert_entries(Is, Value, Es).
+
+
+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).
diff --git a/lib/lod_load.pl b/lib/lod_load.pl
new file mode 100644
index 0000000..7b7fd21
--- /dev/null
+++ b/lib/lod_load.pl
@@ -0,0 +1,76 @@
+:- module(lod_load,
+	  [ lod_load/1,			% +URL
+	    sindice_query/3		% +Query, +Page, -URL
+	  ]).
+
+:- use_module(library(semweb/rdf_db)).
+:- use_module(library(semweb/rdfs)).
+:- use_module(library(uri)).
+:- use_module(library(semweb/rdf_turtle)).
+:- use_module(library(semweb/rdf_http_plugin)).
+
+/** <module> Simple Linked Open Data query facility
+
+*/
+
+% Common RDF prefixes
+
+:- rdf_register_ns(skos,	  'http://www.w3.org/2004/02/skos/core#').
+:- rdf_register_ns(sindice,	  'http://sindice.com/vocab/search#').
+:- rdf_register_ns(dbpprop,	  'http://dbpedia.org/property/').
+:- rdf_register_ns(dbpedia,	  'http://dbpedia.org/resource/').
+:- rdf_register_ns('dbpedia-owl', 'http://dbpedia.org/ontology/').
+:- rdf_register_ns(dcterms,	  'http://purl.org/dc/terms/').
+:- rdf_register_ns(foaf,	  'http://xmlns.com/foaf/0.1/').
+
+%%	lod_load(+URL) is det.
+%
+%	Cached querying of Linked Open Data. First, we remove a possible
+%	fragment identifier (#fragment), because   fragment  identifiers
+%	are a client-side issue rather than a server-side issue.
+%
+%	@error	domain_error(content_type, 'RDF') is raised if the URL
+%		contains no RDF data.  Note that rdf_load/1 already
+%		raises this error if the MIME-type is incorrect.
+
+lod_load(URI) :-
+	url_sans_fragment(URI, URI2),
+	(   rdf_graph(URI2)
+	->  true
+	;   rdf_load(URI2),
+	    (	rdf_graph(URI2)
+	    ->	true
+	    ;	domain_error(content_type, 'RDF')
+	    )
+	).
+
+url_sans_fragment(URI, URI2) :-
+	uri_components(URI, Components),
+	copy_components([scheme, authority, path, search],
+			Components, Components2),
+	uri_components(URI2, Components2).
+
+copy_components([], _, _).
+copy_components([H|T], In, Out) :-
+	uri_data(H, In, Data),
+	uri_data(H, Out, Data),
+	copy_components(T, In, Out).
+
+
+%%	sindice_query_url(+Query, +Page, -URL)
+%
+%	URL is the URL to send to Sindice  for Query. Query is a Sindice
+%	_term_ query argument.
+
+sindice_query(Query, Page, QueryURL) :-
+	uri_query_components(Search, [q=Query, qt=term, page=Page]),
+	sindice_host(Host),
+	sindice_path(Path),
+	uri_data(scheme, Components, http),
+	uri_data(authority, Components, Host),
+	uri_data(path, Components, Path),
+	uri_data(search, Components, Search),
+	uri_components(QueryURL, Components).
+
+sindice_host('api.sindice.com').
+sindice_path('/v2/search').
diff --git a/web/css/fplayer.css b/web/css/fplayer.css
index 53ee5f7..b15d4be 100644
--- a/web/css/fplayer.css
+++ b/web/css/fplayer.css
@@ -116,3 +116,25 @@
 	background-color: #DDD;
 	cursor: pointer;
 }
+
+
+#info {
+	float: left;
+    font-size: 130%;
+    margin-left: 5px;
+    width: 200px;
+}
+#info #fbs-topic-image {
+	float: none;
+}
+#info p.fbs-flyout-image-true, 
+#info h3.fbs-flyout-image-true,
+#info h1.fbs-flyout-image-true {
+	margin-left: 0;
+}
+
+#tagsearch {
+	width: 100%;
+	padding: 4px 0;
+	background: url("../icons/search_bg.png") no-repeat scroll 98% 60% #FFFFFF;
+}
diff --git a/web/css/garden.css b/web/css/garden.css
index 582e95b..b63fafe 100644
--- a/web/css/garden.css
+++ b/web/css/garden.css
@@ -28,9 +28,9 @@
 }
 #video {
 	float: left;
-	margin: 0 10px;
+	margin-left: 5px;
 }
-#resources {
+#frames {
 	float: left;
 }
 #videoplayer {
@@ -38,51 +38,54 @@
 }
 
 /* tag player */
-.yui3-tag-player {
+.yui3-tag-list {
 	background: transparent;
 	overflow: auto;
 	border: 1px solid #CCCCCC;
 	margin-bottom: 5px;
 }	
-.yui3-tag-player ul {
+.yui3-tag-list ul {
 	margin: 0;
 	padding: 0;
 }
-.yui3-tag-player li {
+.yui3-tag-list li {
 	overflow: hidden;
 	list-style: none;
 	margin: 1px 0;
 	padding: 4px 8px;
 }
-.yui3-tag-player li:nth-child(even) {
+.yui3-tag-list li:nth-child(even) {
 	background-color: #EEE;
 }
-.yui3-tag-player li.focus .label {
+.yui3-tag-list li.focus .label {
     font-size: 150%;
 }
-.yui3-tag-player li .hidden {
-	display: none;
-}
-.yui3-tag-player li .label {
+.yui3-tag-list li .label {
 	cursor: pointer;
-	float: left;
 }
-.yui3-tag-player li .score {
-	float: right;
-	color: #222;
-	padding: 1px 3px 1px 2px;
-	border: 2px solid #999;
-	-moz-border-radius: 6px;
-	border-radius: 6px;
-	font-weight: bold;
-	font-size: 90%;
+.yui3-tag-list li .label.concept {
+	color: #0033CC;
+}
+.yui3-tag-list li.reconciled .label {
+	background: url("sprite.png") no-repeat scroll 115% -400px;
+}
+.yui3-tag-list li.reconciled.closed .label {
+	background: url("sprite.png") no-repeat scroll 115% -350px;
+}
+.yui3-tag-list li.closed .reconcile-list {
+	display: none;
 }
 
 
 /* video frames */
 .yui3-video-frames {
+	overflow: auto;
+	border-width: 1px 1px 1px 0;
+	border-style: solid;
+	border-color: #CCCCCC;
 } 
-.yui3-video-frames-content {
+.yui3-video-frames-disabled {
+	display: none;
 }
 .yui3-video-frames .header {
 	padding-bottom: 2px;
@@ -96,15 +99,15 @@
 	padding: 0;
 }
 .yui3-video-frames li {
-	width: 175px;
-	float: left;
 	overflow: hidden;
 	list-style: none;
-	margin: 0 1px 10px;
+	margin: 0 auto 5px;
 	border: 4px solid transparent;
 }
 .yui3-video-frames li.selected {
-	border-color: #0033CC;
+}
+.yui3-video-frames li.hidden {
+	display: none;
 }
 .yui3-video-frames img {
 	width: 100%;
@@ -122,6 +125,18 @@
 	background-color: #DDD;
 	cursor: pointer;
 }
+.yui3-video-frames .frame-confirm.depicted {
+	background-color: green;
+	color: white;
+}
+.yui3-video-frames .frame-confirm.associated {
+	background-color: blue;
+	color: white;
+}
+.yui3-video-frames .frame-confirm.rejected  {
+	background-color: red;
+	color: white;
+}
 
 /* timeline */
 .yui3-timeline {
@@ -147,38 +162,26 @@
 	background-color:red;
 }
 
-/* yui3-tag-linker */
-.yui3-tag-linker ul {
-	margin: 0;
-	padding: 0;
-}
-.yui3-tag-linker li {
-	overflow: hidden;
-	list-style: none;
-	padding: 2px 0;
+/* reconcile items */
+.reconcile-item  {
+	padding-left: 14px;
 }
-.yui3-tag-linker li .name {
-	padding-left: 2px;
+.reconcile-item .radio {
+	margin-left: -16px;
 }
-.yui3-tag-linker li .types {
-	padding-left: 20px;
+.reconcile-item .types {
 	font-size: 95%;
-	font-style: italic;
-	color: #888;
 }
-.yui3-tag-linker li .type {
-	padding: 0 2px;
+.reconcile-item .type {
 }
-.yui3-tag-linker li .desc {
-	padding-left: 20px;
+.reconcile-item .desc {
 	font-size: 95%;
 	color: #888;
 }
-.yui3-tag-linker .controls {
-	border-top: 1px solid #CCCCCC;
-	padding-top: 2px;
-    text-align: right;
-}
-.yui3-tag-linker .controls.hidden {
-	display: none;
+
+/* reconciler */
+.yui3-tag-reconcile .status {
+	color: #666;
+	font-style: italic;
+	padding-left: 10px;
 }
diff --git a/web/css/sprite.png b/web/css/sprite.png
new file mode 100644
index 0000000..afd65e0
Binary files /dev/null and b/web/css/sprite.png differ
diff --git a/web/js/tagplayer/tagReconcile.js b/web/js/tagplayer/tagReconcile.js
index 535dd81..6b610b3 100644
--- a/web/js/tagplayer/tagReconcile.js
+++ b/web/js/tagplayer/tagReconcile.js
@@ -33,6 +33,9 @@ YUI.add('tag-reconcile', function(Y) {
 		},
 		tagsPerRequest: {
 			value:5
+		},
+		limit: {
+			value:3
 		}
 	};
 
@@ -56,7 +59,7 @@ YUI.add('tag-reconcile', function(Y) {
 				sourceSelect.append('<option value="'+key+'">'+sources[key].label+'</option>');
 			}
 			this.button = content.appendChild('<button>Go</button>');
-			this.loading = content.appendChild('<span></span>');
+			this.status = content.appendChild('<span class="status"></span>');
 			this.sourceSelect = sourceSelect;
 		},
 
@@ -85,6 +88,7 @@ YUI.add('tag-reconcile', function(Y) {
 			var oSelf = this,
 				tags = this.get("tags"),
 				n = this.get("tagsPerRequest"),
+				limit = this.get("limit"),
 				start = index,
 	 			last = Math.min(index+n,tags.length),
 	 			queries = {};
@@ -92,13 +96,19 @@ YUI.add('tag-reconcile', function(Y) {
 			//build the query object
 			for(index;index<last;index++) {
             	var tag = tags[index].tag;
-	    		queries[tag.value] = {query:tag.label,limit:5};
+	    		queries[tag.value] = {query:tag.label,limit:limit};
      		};
-			var request = url+"&queries="+Y.JSON.stringify(queries);
+			var request = url+"&limit="+limit+"&queries="+Y.JSON.stringify(queries);
+			
+			// some feedbak to the user
+			this.status.setContent("...reconciling "+start+"/"+tags.length);
+			
 			Y.log("reconcile "+index);
 			Y.jsonp(request, function(response) {
 	    		if(index<tags.length) {
 					oSelf.reconcile(url,index);
+				} else {
+					oSelf.status.setContent("done");
 				}
 				oSelf.reconciled = Y.merge(oSelf.reconciled,response);
 				oSelf.fire("reconcileReturn",
diff --git a/web/js/tagplayer/taglist.js b/web/js/tagplayer/taglist.js
new file mode 100644
index 0000000..a89dba8
--- /dev/null
+++ b/web/js/tagplayer/taglist.js
@@ -0,0 +1,202 @@
+YUI.add('tag-list', function(Y) {
+
+	var Lang = Y.Lang,
+		Widget = Y.Widget,
+		Node = Y.Node;
+
+	var NS = Y.namespace('mazzle');	
+	NS.TagList = TagList;
+	
+	/* TagList class constructor */
+	function TagList(config) {
+		TagList.superclass.constructor.apply(this, arguments);
+	}
+
+	/* 
+	 * Required NAME static field, to identify the Widget class and 
+	 * used as an event prefix, to generate class names etc. (set to the 
+	 * class name in camel case). 
+	 */
+	TagList.NAME = "tag-list";
+
+	/*
+	 * The attribute configuration for the TagList widget. Attributes can be
+	 * defined with default values, get/set functions and validator functions
+	 * as with any other class extending Base.
+	 */
+	TagList.ATTRS = {
+		tags: {
+			value: []
+		},
+		active: {
+			value: true
+		}
+	};
+
+	/* Static constants used to define the markup templates used to create TagList DOM elements */
+	TagList.LIST_CLASS = 'tag-list';
+	TagList.LIST_TEMPLATE = '<ul class="'+TagList.LIST_CLASS+'"></ul>';
+
+	/* TagList extends the base Widget class */
+	Y.extend(TagList, Widget, {
+
+		initializer: function() {
+		},
+
+		destructor : function() {
+		},
+
+		renderUI : function() {
+			var content = this.get("contentBox"),
+				height = this.get("height");
+						
+			// tag list
+			content.setStyle("position", "relative");
+			if(this.get("topIndent")) {
+				content.setStyle("top", height/2+"px");
+			}
+			this.listNode = content.appendChild(Node.create(TagList.LIST_TEMPLATE));
+		},
+
+		bindUI : function() {
+			this.after("tagsChange", this.syncUI);
+			Y.delegate("click", this._itemSelect, this.listNode, "li .label", this);
+			Y.delegate("mouseover", this._itemHover, this.listNode, "li", this);
+			Y.delegate("click", this._reconcileSelect, this.listNode, ".reconcile-item input", this);
+		},
+
+		syncUI : function() {
+			this._renderItems();
+		},
+
+		_renderItems : function() {
+			var tags = this.get("tags");
+			
+			this.listNode.setContent("");
+			// format the items
+			for(var i=0; i < tags.length; i++) {
+				this.listNode.append('<li>'+this.formatItem(tags[i])+'</li>');	
+			}
+		},
+	
+		formatItem : function(item) { 
+			var tag = item.tag,
+				label = tag.label ? tag.label : tag.value;
+ 
+			var html = '<div class="label">'+label+'</div>';				
+			if(item.uri) {
+				html += '<a href="javascript:{}">'+html+'</a>';
+			}
+			html += '<div class="reconcile-list"></div>';
+			return html
+			
+		},
+		
+		_itemSelect : function(e) {
+			// item click
+			var node = e.currentTarget.get("parentNode"),
+				index = e.container.all("li").indexOf(node),
+				item = this.get("tags")[index],
+				arg = {li:node, index:index, tag:item};
+				
+			this.set("active", arg);
+			Y.log('clicked tag '+item.tag.value+' at index '+index);	
+			this._highlight(index);
+			if(node.hasClass("reconciled")) {
+				node.toggleClass("closed");
+			}
+	        this.fire("itemSelect", arg);
+		},
+		
+		_itemHover : function(e) {
+			var node = e.currentTarget,
+				index = e.container.all("li").indexOf(node),
+				item = this.get("tags")[index],
+				arg = {li:node, index:index, tag:item};
+	        this.fire("itemHover", arg);
+		},
+		
+		_highlight : function(index) {
+			var items = this.listNode.all("li");
+			// removeFocus from other items
+			items.removeClass('focus');
+			// add focus class to current item
+			items.item(index).addClass('focus');
+		},
+		
+		setReconciled : function(reconciled, start, end) {
+			var nodes = this.listNode.all("li"),
+				tags = this.get("tags");
+				
+			for (var i=start; i < end; i++) {
+				var node = nodes.item(i),
+					tagValue = tags[i].tag.value,
+					r = reconciled[tagValue];
+
+				node.addClass("closed");
+				if(r&&r.result.length>0) {
+					node.addClass("reconciled");
+					node.one('.reconcile-list')
+					.setContent(this.formatReconciled(tagValue, r.result));
+				} else {
+					node.removeClass("reconciled");
+					node.one('.reconcile-list').setContent('');
+				}
+			}
+		},
+		resetReconciled : function() {
+			this.listNode.all("li")
+			.removeClass("reconciled")
+			.addClass("closed");
+			
+			this.listNode.all("li .label").removeClass("concept");
+		},
+		
+		formatReconciled : function(tag, r) {
+			var html = "";
+			for (var i=0; i < r.length; i++) {		  			
+				html += "<div class='reconcile-item'>"+this.formatReconcileItem(tag, r[i])+"</div>";
+			}
+			return html;
+		},
+		
+		formatReconcileItem : function(tag, item) {
+			var id = item.id,
+				name = item.name,
+				types = item.type||[];
+				
+			var html = "<input class='radio' type='radio' value='"+id+"' name='"+tag+"'>";
+			html += "<a href='javascript:{}' class='name'>"+name+"</a>";
+			html += "<div class='types'>";
+			for (var i=0; i < types.length; i++) {
+				html += "<span class='type'>"+types[i].name+"</span>";
+				if(i<types.length-1) {
+					html += ', ';
+				}
+			}
+			html +=	"</div>";
+			if(item.desc) { 
+				html += "<div class='desc'>"+item.desc+"</div>";
+			}
+			return html;
+		},
+		
+		_reconcileSelect : function(e) {
+			var option = e.currentTarget,
+				reconcileNode = option.get("parentNode"),
+				optionIndex = reconcileNode.get("parentNode").all(".reconcile-item")
+					.indexOf(reconcileNode),
+				tagNode = reconcileNode.get("parentNode").get("parentNode"),
+				uri = option.get("value"),
+				label = reconcileNode.one(".name").getContent(),
+				index = e.container.all("li").indexOf(tagNode),
+				tag = this.get("tags")[index].tag.value;
+				
+			tagNode.one(".label").addClass("concept");
+			tagNode.addClass('closed');
+			this.fire("reconcileSelect", {index:optionIndex, tag:tag, uri:uri, label:label});
+		}
+
+	});
+	  
+}, 'gallery-2010.03.02-18' ,{requires:['node','event','widget']});
\ No newline at end of file