yaz/commit

gardening with external reconciliation services

authorMichiel Hildebrand
Fri Jul 8 16:22:49 2011 +0200
committerMichiel Hildebrand
Fri Jul 8 16:22:49 2011 +0200
commitcb9bc07417fe60d466c3122fda47b3c19848e315
tree91a056c3179a88f79a63b95662113f6348c399cb
parentda6a133817a627398ec7324820bd8f94bed3e0ce
Diff style: patch stat
diff --git a/api/reconcile.pl b/api/reconcile.pl
index a4b3ac1..f99e16c 100644
--- a/api/reconcile.pl
+++ b/api/reconcile.pl
@@ -23,7 +23,7 @@
 @author	Michiel Hildebrand
 */
 
-:- http_handler(yaz(reconcile), http_reconcile, []).
+:- http_handler(api(reconcile), http_reconcile, []).
 :- http_handler(yaz(savereconcile), http_save_reconcile, []).
 
 :- dynamic
@@ -95,7 +95,8 @@ reply(Callback, JSON) :-
 %	list of hits matching query.
 
 reconcile_list([], _, _, _, []).
-reconcile_list([Key=json([query=Query])|Ts], Max, Type, Properties, [Key=json([result=Results])|Rs]) :-
+reconcile_list([Key=json(Obj)|Ts], Max, Type, Properties, [Key=json([result=Results])|Rs]) :-
+	memberchk([query=Query], Obj),
 	reconcile(Query, Max, Type, Properties, Hits),
 	hits_to_json_results(Hits, Results),
 	reconcile_list(Ts, Max,  Type, Properties, Rs).
diff --git a/applications/yaz_garden.pl b/applications/yaz_garden.pl
new file mode 100644
index 0000000..5f5ad0a
--- /dev/null
+++ b/applications/yaz_garden.pl
@@ -0,0 +1,259 @@
+:- module(yaz_garden,
+	  []).
+
+:- 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(applications(yaz_tag)).
+:- 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)).
+
+:- http_handler(yaz(garden), http_yaz_garden, []).
+
+reconcile_source(cornetto,
+		 'Cornetto',
+		 Server,
+		 '') :-
+	http_location_by_id(http_reconcile, Server).
+reconcile_source(geogname,
+		 'Geonames',
+		 'http://api.kasabi.com/api/reconciliation-api-geonames',
+		'&apikey=908177a484aa25f9b602d3eb76cf057d73e7aa39').
+reconcile_source(dbpedia,
+		 'DBPedia',
+		 'http://api.kasabi.com/api/reconciliation-api-dbpedia-36',
+		 '&apikey=908177a484aa25f9b602d3eb76cf057d73e7aa39').
+reconcile_source(freebase,
+		 'Freebase',
+		 'http://standard-reconcile.freebaseapps.com/reconcile',
+		 '').
+
+
+%%	http_yaz_garden(+Request)
+%
+%	Emit an HTML page to link tags to concepts.
+
+http_yaz_garden(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, As0, Options),
+	sort_by_arg(As0, 2, Annotations),
+	sort_by_arg(As0, 1, As1),
+	merge_entries(As1, TagEntries0),
+	sort_by_arg_count(TagEntries0, 2, TagEntries, desc),
+	findall(Id=json([label=Label,url=URL,parameters=Parameters]),
+		reconcile_source(Id,Label,URL,Parameters), Sources),
+	html_page(Video, Annotations, TagEntries, json(Sources), Options).
+
+merge_entries([], []).
+merge_entries([A0|T], [A|As]) :-
+	      A0 = annotation(Value,_,_,_,_),
+	      A  = annotation(Value,Entries),
+	      same_entries([A0|T], Value, Entries0, Rest),
+	      sort_by_arg(Entries0, 3, Entries),
+	      merge_entries(Rest, As).
+
+same_entries([annotation(V,_,_,[i(URI,Time)|_],_)|As], V,
+	     [entry(URI,V,Time)|Es], Rest) :-
+	same_entries(As, V, Es, Rest).
+same_entries(As, _, [], As).
+
+%%	html_page(+Video, +Annotations, +Options)
+%
+%	Emit an HTML page for concept gardening
+
+html_page(Video, Annotations, Groups, Sources, Options) :-
+	reply_html_page(yaz,
+			[ title(['YAZ - ', Video])
+			],
+			[ \html_requires(css('garden.css')),
+			  \html_requires(css('tag.css')),
+			  \yaz_video_header(Video),
+			  div(id(tags),
+			      [	div(id(tagplayer), []),
+				div(class(box),
+				    [ div(class(hd), 'Reconcile'),
+				      div([class(bd), id(tagreconcile)], [])
+				    ])
+			      ]),
+			  div(id(video),
+			      [ div(id(timeline), []),
+				div(id(videoplayer), []),
+				div(id(videoframes), [])
+			      ]),
+			  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))
+			]).
+
+source_options([]) --> !.
+source_options([Label-Value|Ls]) -->
+	html(option(value(Value), Label)),
+	source_options(Ls).
+
+
+html_video_page_yui(Video, Annotations, Groups, ReconcileSources, 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('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},
+			   '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'
+		],
+		[ \js_new(tagPlayer,
+			 'Y.mazzle.TagPlayer'({tags:JSONTagGroups,
+					       height:350,
+					       width:200,
+					       topIndent:symbol(false)
+					      })),
+		   \js_new(tagReconcile,
+			 'Y.mazzle.TagReconcile'({height:200,
+						  width:200,
+						  sources:ReconcileSources
+					      })),
+		  \js_new(tagLinker,
+			 'Y.mazzle.TagLinker'({height:400,
+					       width:195
+					      })),
+		  \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(true),
+						 showRelated:symbol(false),
+						 showTime:symbol(true)
+						})),
+		  \js_new(timeline,
+			  'Y.mazzle.Timeline'({height:20,
+					       width:560,
+					       duration:Duration,
+					       items:JSONTags
+					      })),
+		  'tagReconcile.set("tags", tagPlayer.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(tagReconcile, #(tagreconcile)),
+		  \js_yui3_render(tagLinker, #(taglinker)),
+		  \js_yui3_on(tagPlayer, itemSelect, \js_tag_select),
+		  \js_yui3_on(videoFrames, frameHover, \js_frame_hover),
+		  \js_yui3_on(videoFrames, frameSelect, \js_frame_select),
+		  \js_yui3_on(tagReconcile, reconcileReturn, \js_reconcile_return)
+		]).
+
+js_tag_select -->
+	js_function([e],
+		    \[
+'    var tag = e.tag,
+         entry = tag.annotations[0],
+         time = (entry.startTime/1000)-3;\n',
+'   videoPlayer.setTime(time, true);
+    videoFrames.set("frames", tag.annotations);
+    tagLinker.set("tag", tag);\n'
+		     ]).
+
+js_frame_select -->
+	js_function([e],
+		    \[
+'    var frame = e.frame;
+     var time = (frame.startTime/1000)-3;
+     videoPlayer.setTime(time, true);\n'
+		     ]).
+
+js_frame_hover -->
+	js_function([e],
+		    \[
+'   timeline.highlightIndex(e.index);\n'
+		     ]).
+
+js_reconcile_return -->
+	js_function([o],
+		    \[
+'    var reconciled = o.reconciled,
+         tags = tagPlayer.get("tags");\n',
+'    tagLinker.set("reconciled", reconciled);\n',
+'    tagPlayer.listNode.all("li").each(function(node, index) {
+	 var tag = tags[index].tag,
+	     r = reconciled[tag.value];
+	 if(r&&r.result.length>0) {node.one(".score").setContent("?").removeClass("hidden")} else {node.addClass("hidden")};
+	    })'
+		     ]).
+
+
diff --git a/config-available/yaz.pl b/config-available/yaz.pl
index f4b6b64..8a879fc 100644
--- a/config-available/yaz.pl
+++ b/config-available/yaz.pl
@@ -18,6 +18,13 @@
 :- rdf_register_ns(ore, 'http://www.openarchives.org/ore/terms/').
 :- rdf_register_ns(ens, 'http://www.europeana.eu/schemas/edm/').
 
+:- rdf_register_ns(gtaa, 'http://data.beeldengeluid.nl/gtaa/').
+:- rdf_register_ns(cornetto, 'http://purl.org/vocabularies/cornetto/').
+:- rdf_register_ns(wn20i, 'http://www.w3.org/2006/03/wn/wn20/instances/').
+
+
+
+
 :- use_module(api(annotations)).
 
 % yaz applications (or actually the different pages)
diff --git a/lib/yaz_util.pl b/lib/yaz_util.pl
index 3d1d482..14862f3 100644
--- a/lib/yaz_util.pl
+++ b/lib/yaz_util.pl
@@ -6,6 +6,7 @@
 	    arg_key/3,
 	    sort_by_arg/3,
 	    sort_by_arg/4,
+	    sort_by_arg_count/4,
 	    group_by_arg/3,
 	    display_label/2,
 	    tag_label/2,
@@ -136,6 +137,16 @@ sort_by_arg(List, Arg, Direction, Sorted) :-
 	;   Sorted = Sorted0
 	).
 
+sort_by_arg_count(List, Arg, Sorted, Direction) :-
+	maplist(arg_key_count(Arg), List, Pairs),
+	keysort(Pairs, SortedPairs),
+	pairs_values(SortedPairs, Sorted0),
+	(   Direction == desc
+	->  reverse(Sorted0, Sorted)
+	;   Sorted = Sorted0
+	).
+
+
 %%	group_by_arg(+ListOfTerms, +Arg, -GroupedList)
 %
 %	GroupedList contains the Terms from ListOfTerms grouped by their
@@ -153,6 +164,11 @@ arg_key(Args, Term, Keys-Term) :-
 arg_key(Arg, Term, Key-Term) :-
 	arg(Arg, Term, Key).
 
+arg_key_count(Arg, Term, Key-Term) :-
+	arg(Arg, Term, List),
+	is_list(List),
+	length(List, Key).
+
 args([A], Term, [Key]) :- !,
 	arg(A, Term, Key).
 args([A|As], Term, [Key|Ks]) :-
@@ -338,6 +354,7 @@ http:convert_parameter(jsonresource, Atom, Term) :-
     literal(value:_) + [type=literal],
     i(uri:atom, time:number),
     entry(entry:atom, tag:_, startTime:number),
+    annotation(tag:_, annotations:list),
     annotation(tag:_, count:number),
     annotation(tag:_, tags:list, count:number),
     annotation(tag:_, startTime:number, endTime:number, annotations:list),
diff --git a/web/css/garden.css b/web/css/garden.css
index c63011e..5761bd9 100644
--- a/web/css/garden.css
+++ b/web/css/garden.css
@@ -2,41 +2,93 @@
 	margin: 0 auto;
 }
 
-/* page layout */
-#main {
-    padding-left: 225px;
+/* header and description */
+.video-results h2 {
+	margin-bottom: 0;
+}
+.video-results .desc {
+	margin-bottom: 15px;
+	max-height: 2em;
+	color: #888;
+	font-size: 95%;
+	clear: both;
+}
+
+/* general page elements */
+.box .hd {
+	padding: 4px 0 0;
+	font-weight: bold;
+	border-bottom:1px solid #CCC;
 }
+
+/* main layout */
+
 #tags {
 	float: left;
-	width: 200px;
-	height: 600px;
-}
-#frames {
 }
 #video {
+	float: left;
+	margin: 0 10px;
+}
+#resources {
+	float: left;
+}
+#videoplayer {
+	margin: 5px 0;
 }
 
-/* element style */
-
-h4 {
+/* tag player */
+.yui3-tag-player {
+	background: transparent;
+	overflow: auto;
+	border: 1px solid #CCCCCC;
+	margin-bottom: 5px;
+}	
+.yui3-tag-player ul {
 	margin: 0;
-	padding-bottom: 2px;
-	border-color: #BBB;
-	border-style: solid;
-	border-width: 0 0 1px;
-	font-weight: normal;
-	font-size: 130%;
+	padding: 0;
+}
+.yui3-tag-player li {
+	overflow: hidden;
+	list-style: none;
+	margin: 1px 0;
+	padding: 4px 8px;
+}
+.yui3-tag-player li:nth-child(even) {
+	background-color: #EEE;
+}
+.yui3-tag-player li.focus .label {
+    font-size: 150%;
+}
+.yui3-tag-player li .hidden {
+	display: none;
+}
+.yui3-tag-player 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%;
 }
 
+
 /* video frames */
+.yui3-video-frames {
+} 
 .yui3-video-frames-content {
-	overflow: hidden;
 }
 .yui3-video-frames .header {
-	padding: 4px;
-	margin: 2px 0;
-	background-color: #333;
-	color: white;
+	padding-bottom: 2px;
+	margin: 12px 0 4px;
+	font-weight: bold;
+	border-bottom: 1px solid #CCC;
 	clear: both;
 }
 .yui3-video-frames ul.frames-list {
@@ -53,148 +105,24 @@ h4 {
 .yui3-video-frames img {
 	width: 100%;
 }
-.yui3-video-frames .frame-confirm {
-	text-align: center;
-	color: white;
-	background-color: #222;
-	padding: 3px 0;
-}
-.yui3-video-frames .tag {
-	text-align: center;
-	padding: 3px 0;
-	background-color: #DDD;
-}
-.yui3-video-frames li.hidden {
-	display: none;
-}
-.yui3-video-frames .frame-confirm.depicted {
-	background-color: green;
-}
-.yui3-video-frames .frame-confirm.associated {
-	background-color: blue;
-}
-.yui3-video-frames .frame-confirm.rejected  {
-	background-color: red;
-}
-.yui3-video-frames .users {
-	z-index:4;
-	width: 20px;
-	height: 20px;
-	position:relative;
-	margin-bottom: -20px;
-	background-color:white;
-	-moz-border-radius: 0 0 20px 0;
-	border-radius: 0 0 20px 0;
-}
 .yui3-video-frames .image {
 	position: relative;
 	z-index: 2;
 	height: 98px;
 	overflow: hidden;
 }
-.yui3-video-frames .users.hidden {
-	display: none;
-}
-
-/* videoplayer */
-.yui3-videoplayer {
-	position: absolute;
-	padding-left: -1px;
-	z-index:3;
-}
-.yui3-videoplayer-hidden {
-	display:none;
-}
-
-/* tag list */
-.yui3-tag-carousel-content {
-	overflow:auto;
-}
-.yui3-tag-carousel ul {
-	margin: 0;
-	padding: 0;
-}
-.yui3-tag-carousel li {
-	overflow: hidden;
-	list-style: none;
-	margin: 1px 0;
-	padding: 4px 8px;
-}
-.yui3-tag-carousel li .label {
+.yui3-video-frames .tag,
+.yui3-video-frames .frame-confirm {
+	text-align: center;
+	padding: 3px 0;
+	background-color: #DDD;
 	cursor: pointer;
-	float: left;
-}
-.yui3-tag-carousel li .count {
-	float: right;
-	background-color:#CCCCCC;
-	color:white;
-	padding: 1px 2px;
-	-moz-border-radius: 6px;
-	border-radius: 6px;
-}
-.yui3-tag-carousel li.focus,
-.yui3-tag-carousel li.focus .count,
-.yui3-tag-carousel li.focus a {
-	background-color: #1057AE;
-	color: #FFF;
-}
-.yui3-tag-carousel li .edit,
-.yui3-tag-carousel li .remove {
-	float: right;
-	padding: 0 4px;
-}
-.yui3-tag-carousel li .edit a,
-.yui3-tag-carousel li .remove a {
-	color: #AAA;
-}
-.yui3-tag-carousel li .edit a:hover,
-.yui3-tag-carousel li .remove a:hover {
-	color: red;
-}
-
-.yui3-tag-carousel li .label input {
-	width: 120px;
-}
-
-
-/* tabview */
-.yui3-tabview-list {
-	margin: 0;
-	padding: 0 0 2px;
-	border-color: #BBB;
-	border-style: solid;
-	border-width: 0 0 1px;
-}
-.yui3-tab a:link {
-	font-size: 130%;
-	padding: 0 10px 2px 0;
-}
-.yui3-tab-selected a:link {
-	text-decoration: underline;
-}
-
-.controls {
-	clear: both;
-	overflow: hidden;
-}
-.controls .control {
-	float: left;
-	margin-right: 20px;
-}
-.controls input {
-	width: 2em;
-	margin: 0 5px;
-	padding: 0;
-}
-.controls label {
-	padding-right: 5px;
 }
 
 /* timeline */
 .yui3-timeline {
 	background-color:#CCCCCC;
 	height:15px;
-	margin-bottom:5px;
 	width:100%;
 }
 .yui3-timeline ul {
@@ -215,24 +143,33 @@ h4 {
 	background-color:red;
 }
 
-/* concept browser */
-.yui3-columnbrowser .hd {
-	display: none;
+/* yui3-tag-linker */
+.yui3-tag-linker ul {
+	margin: 0;
+	padding: 0;
 }
-
-/* suggest */
-.fbs-reset {
-	text-align: left;
-	z-index: 99;
+.yui3-tag-linker li {
+	overflow: hidden;
+	list-style: none;
+	padding: 2px 0;
 }
-#suggest {
-	margin: -3px 0 0 -3px;
-	position: absolute;
-	z-index: 99;
+.yui3-tag-linker li .name {
+	padding-left: 2px;
 }
-#suggest input {
-	width: 125px;
+.yui3-tag-linker li .types {
+	padding-left: 20px;
+	font-size: 95%;
+	font-style: italic;
+	color: #888;
 }
-#suggest.hidden {
+.yui3-tag-linker li .type {
+	padding: 0 2px;
+}
+.yui3-tag-linker .controls {
+	border-top: 1px solid #CCCCCC;
+	padding-top: 2px;
+    text-align: right;
+}
+.yui3-tag-linker .controls.hidden {
 	display: none;
-}
\ No newline at end of file
+}
diff --git a/web/js/tagplayer/tagLinker.js b/web/js/tagplayer/tagLinker.js
new file mode 100644
index 0000000..ae65a74
--- /dev/null
+++ b/web/js/tagplayer/tagLinker.js
@@ -0,0 +1,110 @@
+YUI.add('tag-linker', function(Y) {
+
+	var Lang = Y.Lang,
+		Widget = Y.Widget,
+		Node = Y.Node;
+
+	var NS = Y.namespace('mazzle');	
+	NS.TagLinker = TagLinker;
+	
+	/* TagLinker class constructor */
+	function TagLinker(config) {
+		TagLinker.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). 
+	 */
+	TagLinker.NAME = "tag-linker";
+
+	/*
+	 * The attribute configuration for the TagLinker widget. Attributes can be
+	 * defined with default values, get/set functions and validator functions
+	 * as with any other class extending Base.
+	 */
+	TagLinker.ATTRS = {
+		reconciled: {
+			value: {}
+		},
+		tag: {
+			value: null
+		}
+	};
+
+	/* Static constants used to define the markup templates used to create TagLinker DOM elements */
+	TagLinker.LIST_CLASS = 'tag-list';
+	TagLinker.LIST_TEMPLATE = '<ul class="'+TagLinker.LIST_CLASS+'"></ul>';
+
+	/* TagLinker extends the base Widget class */
+	Y.extend(TagLinker, Widget, {
+
+		initializer: function() {
+			this.reconciled = {};
+		},
+
+		destructor : function() {
+		},
+
+		renderUI : function() {
+			var content = this.get("contentBox");
+			this.listNode = content.appendChild(Node.create(TagLinker.LIST_TEMPLATE));
+			var controls = content.appendChild('<div class="controls hidden"></div>');
+			this.applyButton = controls.appendChild('<button>apply</button>');
+			this.applyAllButton = controls.appendChild('<button>apply to all</button>');
+			this.controls = controls;
+		},
+
+		bindUI : function() {
+			this.after("tagChange", this.syncUI);
+			this.applyButton.on("click", this._applySelect, this);
+			this.applyAllButton.on("click", this._applySelect, this, true);
+		},
+
+		syncUI : function() {
+			this._renderItems();
+		},
+		
+		_applySelect : function() {
+			var selectedNode = this.listNode.one("li input:checked");
+			if(selectedNode) {
+				var selected = selectedNode.get("value");
+				console.log(selected);
+			}
+			
+		},
+		
+		_renderItems : function() {
+			var tag = this.get("tag"),
+				reconciled = this.get("reconciled"),
+				list = this.listNode;
+			list.setContent("");
+			if(tag&&tag.tag.value&&reconciled[tag.tag.value]) {
+				var items = reconciled[tag.tag.value].result;
+				for (var i=0; i < items.length; i++) {
+		  			list.append("<li>"+this.formatItem(items[i])+"</li>");
+				}
+				this.controls.removeClass("hidden");
+			} else {
+				this.controls.addClass("hidden");
+			}
+		},
+		
+		formatItem : function(item) {
+			var id = item.id,
+				name = item.name,
+				types = item.type||[];
+				
+			var html = "<input type=radio value="+id+">";
+			html += "<span class='name'>"+name+"</span>";
+			html += "<div class='types'>";
+			for (var i=0; i < types.length; i++) {
+				html += "<span class='type'>"+types[i].name+"</span>";
+			};
+			html +=	"</div>";
+			return html;
+		}
+	})
+	  
+}, 'gallery-2010.03.02-18' ,{requires:['node','event','widget','json']});
\ No newline at end of file
diff --git a/web/js/tagplayer/tagReconcile.js b/web/js/tagplayer/tagReconcile.js
new file mode 100644
index 0000000..68969f2
--- /dev/null
+++ b/web/js/tagplayer/tagReconcile.js
@@ -0,0 +1,104 @@
+YUI.add('tag-reconcile', function(Y) {
+
+	var Lang = Y.Lang,
+		Widget = Y.Widget,
+		Node = Y.Node;
+
+	var NS = Y.namespace('mazzle');	
+	NS.TagReconcile = TagReconcile;
+	
+	/* TagReconcile class constructor */
+	function TagReconcile(config) {
+		TagReconcile.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). 
+	 */
+	TagReconcile.NAME = "tag-reconcile";
+
+	/*
+	 * The attribute configuration for the TagReconcile widget. Attributes can be
+	 * defined with default values, get/set functions and validator functions
+	 * as with any other class extending Base.
+	 */
+	TagReconcile.ATTRS = {
+		sources: {
+			value: {}
+		},
+		tags: {
+			value: []
+		}
+	};
+
+	/* TagReconcile extends the base Widget class */
+	Y.extend(TagReconcile, Widget, {
+
+		initializer: function() {
+			this.reconciled = {};
+		},
+
+		destructor : function() {
+		},
+
+		renderUI : function() {
+			var sources = this.get("sources"),
+				content = this.get("contentBox");
+			
+			content.append('<span>select a source: <span>');
+			var sourceSelect = content.appendChild('<select></select>');
+			for (var key in sources) {
+				sourceSelect.append('<option value="'+key+'">'+sources[key].label+'</option>');
+			}
+			this.button = content.appendChild('<button>Go</button>');
+			this.loading = content.appendChild('<span></span>');
+			this.sourceSelect = sourceSelect;
+		},
+
+		bindUI : function() {
+			var select = this.sourceSelect,
+				sources = this.get("sources");
+	
+			this.button.on("click", function(e) {
+				this.reconciled = {};
+				var index = select.get("selectedIndex"),
+					source = sources[select.get("options").item(index).get("value")],
+					url = source.url
+						+ "?callback={callback}"
+						+ source.parameters;
+				Y.log('reconcile against '+source.label);
+				this.reconcile(url, 0);
+			}, this);
+		},
+
+		syncUI : function() {
+		},
+
+		reconcile : function(url, index) {
+			var oSelf = this,
+				tags = this.get("tags"),
+				start = index,
+	 			last = Math.min(index+5,tags.length),
+	 			queries = {};
+     		
+			//build the query object
+			for(index;index<last;index++) {
+            	var tag = tags[index].tag;
+	    		queries[tag.value] = {query:tag.label,limit:5};
+     		};
+			var request = url+"&queries="+Y.JSON.stringify(queries);
+			Y.log("reconcile "+index);
+			Y.jsonp(request, function(response) {
+	    		if(index<tags.length) {
+					oSelf.reconcile(url,index);
+				}
+				oSelf.reconciled = Y.merge(oSelf.reconciled,response);
+				oSelf.fire("reconcileReturn",
+					{startIndex:start, endIndex:index, reconciled:oSelf.reconciled});
+	    	});
+		}
+	})
+	  
+}, 'gallery-2010.03.02-18' ,{requires:['node','event','widget','json','jsonp']});
\ No newline at end of file
diff --git a/web/js/videoframes/videoframes.js b/web/js/videoframes/videoframes.js
index 833202e..9c2ec3f 100644
--- a/web/js/videoframes/videoframes.js
+++ b/web/js/videoframes/videoframes.js
@@ -172,6 +172,8 @@ YUI.add('video-frames', function(Y) {
 				var seconds = Math.floor(totalSeconds % 60);
 				var spacer = (seconds<10) ? 0 : '';
 			 	return '<span class="time">'+minutes+':'+spacer+seconds+'</span>';
+			} else {
+				return '';
 			}	
 		},