yaz/commit

specific tag gardening application for tag agreement

authorMichiel Hildebrand
Sun Jan 30 17:34:13 2011 +0100
committerMichiel Hildebrand
Sun Jan 30 17:34:13 2011 +0100
commit7152bc8b346601d69cba4c54a2bc5c1c125ff34a
tree47c6703fec054386604f15990a486d55c6b20b59
parent91892ea994256f0dad52f49da39e31c8b672cd58
Diff style: patch stat
diff --git a/applications/yaz_tag_agreement.pl b/applications/yaz_tag_agreement.pl
new file mode 100644
index 0000000..e5b787c
--- /dev/null
+++ b/applications/yaz_tag_agreement.pl
@@ -0,0 +1,362 @@
+:- module(yaz_tag_agreement,
+	  [
+ 	  ]).
+
+:- 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/json_convert)).
+:- 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(user_process)).
+:- use_module(library(video_annotation)).
+:- use_module(library(tag_match)).
+%:- use_module(library(reconcile)).
+
+:- use_module(components(label)).
+:- use_module(components(yaz_page)).
+
+:- use_module(api(video_frames)).
+
+:- setting(reconcile_server, atom,
+	   'http://standard-reconcile.freebaseapps.com/reconcile',
+	   'URL of a reconcile server, use "local" for built-in service of this server').
+
+:- http_handler(yaz(tagagreement), http_yaz_tag_agreement, []).
+:- http_handler(yaz('data/frames'), http_data_frames, []).
+
+http_yaz_tag_agreement(Request) :-
+	ensure_logged_on(_),
+	http_parameters(Request,
+			[ video(Video,
+				[description('Current video')]),
+ 			  limit(_Limit,
+				[default(1000), number,
+				 description('limit number of tags shown')])
+			]),
+ 	create_user_process([rdf:type=pprime:'TagGarden',
+			     opmv:used=Video
+			    ], _Process),
+	findall(Tag, video_tag(Video, literal(Tag)), Tags0),
+	sort(Tags0, Tags),
+	concept_candidates(Tags, Pairs),
+	tag_clusters(Pairs, TagClusters),
+	maplist(cluster_annotation(Video), TagClusters, Annotations0),
+	sort_by_arg(Annotations0, 3, Annotations1),
+	reverse(Annotations1, Annotations),
+  	html_garden_page(Video, Annotations, []).
+
+cluster_annotation(Video, Tags, annotation(Label, Ts, Count)) :-
+ 	findall(literal(Tag), (member(Tag-_, Tags),
+		      video_tag(Video, literal(Tag))
+		     ),
+		Ts0),
+	sort(Ts0, Ts),
+	% get most occuring tag
+	Ts0 = [Label|_],
+	length(Ts0, Count).
+
+concept_candidates([], []).
+concept_candidates([Tag|Ts], [Tag-Cs|Rest]) :-
+	findall(C, find_tag_concept(Tag, C, _), Cs),
+	concept_candidates(Ts, Rest).
+
+
+tag_clusters([], []).
+tag_clusters([Tag|T0], [[Tag|Tags]|T]) :-
+	similar_tags(T0, Tag, Tags0, Rest0),
+	extend_cluster(Tags0, Rest0, Tags, Rest),
+	tag_clusters(Rest, T).
+
+similar_tags([], _, [], []).
+similar_tags([Tag|T], Tag0, [Tag|Tags], Rest) :-
+	my_tag_match(Tag, Tag0),
+	!,
+	similar_tags(T, Tag0, Tags, Rest).
+similar_tags([Tag|T], Tag0, Tags, [Tag|Rest]) :-
+	similar_tags(T, Tag0, Tags, Rest).
+
+extend_cluster([], Rest, [], Rest).
+extend_cluster([Tag|Ts], Tags, Extend, Rest) :-
+	append(Extend0, [Tag|Extend1], Extend),
+	similar_tags(Tags, Tag, Extend0, Rest0),
+	extend_cluster(Ts, Rest0, Extend1, Rest).
+
+my_tag_match(T1-_, T2-_) :-
+	snowball(english, T1, T1S0),
+	snowball(english, T2, T2S0),
+	downcase_atom(T1S0, T1S),
+	downcase_atom(T2S0, T1S).
+my_tag_match(_T1-Cs1, _T2-Cs2) :-
+	member(C1, Cs1),
+	member(C2, Cs2),
+	tag_concept_match(C1, C2, _).
+
+tag_concept_match(R, R, synonym) :- !.
+tag_concept_match(R1, R2, specific) :-
+ 	parent_of(R1, R2),
+	!.
+tag_concept_match(R1, R2, generic) :-
+ 	parent_of(R2, R1),
+	!.
+
+%%	parent_of(+R, +Ancestor)
+%
+%	True if Parent is related to R by skos:broader.
+
+parent_of(R, A) :-
+	rdf_has(R, skos:broader, A).
+parent_of(R, A) :-
+	rdf_has(A, skos:broader, R).
+
+
+%%	http_data_frames(+Request)
+%
+%       Emit a JSON object with all frames for a given tag and video.
+
+http_data_frames(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')]),
+			  limit(_Limit,
+				[default(1000), number,
+				 description('limit number of tags shown')]),
+			  tag(Tags,
+			      [jsonresource, description('Tag assinged to the video')])
+			]),
+	Options = [process(Process),
+		   user(User)
+ 		  ],
+ 	Obj = Time-json([tag=Label, entry=Id, time=Time]),
+	findall(Obj, (member(T,Tags),
+		      tag_term_label(T,_,Label),
+		      video_annotation(Video, Id, T, Time, Options)), TagEntries0),
+	keysort(TagEntries0, TagEntries),
+	pairs_values(TagEntries, Fragments),
+ 	reply_json(json([fragments=Fragments])).
+
+
+		 /*******************************
+		 *               HTML		*
+		 *******************************/
+
+%%	html_garden_page(+Video, +Annotations,  +Options)
+%
+%	Emit an HTML page for tag gardening.
+
+html_garden_page(Video, Annotations, Options) :-
+	reply_html_page(yaz,
+			[ title(['YAZ - ', Video])
+			],
+			[ \html_requires(css('garden.css')),
+ 			  div(class('yui3-skin-sam'),
+			      \html_page_layout(Video)),
+			  script(type('text/javascript'),
+				 \html_page_yui(Video, Annotations, Options))
+			]).
+
+html_page_layout(Video) -->
+	{ display_label(Video, Title)
+ 	},
+	html([ h2(Title),
+	       div(id(tags),
+		   [ %h4('Tags'),
+		     div(id(taglist), [])
+		   ]),
+	       div(id(main),
+		   [ div([id(concepts), class(hidden)],
+			 [ div(id(tagReconcile), [])
+			 ]),
+		     %h4('Fragments'),
+ 		     div(id(frames), [])
+		   ]),
+	       div([id(suggest), class(hidden)],
+		   [ input([type(text), id(taginput)]),
+		     div(id(suggestResults), [])
+ 		   ])
+ 	     ]).
+
+		 /*******************************
+		 *               JS		*
+		 *******************************/
+
+:- json_object
+     i(uri:atom, time:number),
+     uri(value:uri) + [type=uri],
+     literal(lang:atom, value:_) + [type=literal],
+     literal(type:atom, value:_) + [type=literal],
+     literal(value:atom) + [type=literal],
+     annotation(tag:_, count:number),
+     annotation(tag:_, tags:_, count:number).
+
+%%	html_page_yui(+Video, +Annotations, +Options)
+%
+%	Emit JavaScript for the tag gardening page.
+
+html_page_yui(Video, Annotations, _Options) -->
+	{ video_source(Video, Src, Duration),
+ 	  http_absolute_location(js('videoplayer/'), PlayerPath, []),
+	  http_absolute_location(js('videoplayer/videoplayer.js'), VideoPlayer, []),
+	  http_absolute_location(js('tagcarousel/tagcarousel.js'), TagCarousel, []),
+	  http_absolute_location(js('videoframes/videoframes.js'), VideoFrames, []),
+	  http_absolute_location(js('timeline/timeline.js'), Timeline, []),
+	  http_location_by_id(serve_video_frame, FrameServer),
+	  http_location_by_id(http_data_frames, DataServer),
+	  (   setting(reconcile_server, local)
+	  ->  http_location_by_id(http_reconcile, ReconcileServer)
+	  ;   setting(reconcile_server, ReconcileServer)
+	  ),
+  	  prolog_to_json(Annotations, JSONTags)
+  	},
+	html_requires(js('videoplayer/swfobject.js')),
+		html_requires(yui3('yui/yui-min.js')),
+ 	js_yui3([{modules:{'video-player':{fullpath:VideoPlayer},
+			   'tag-carousel':{fullpath:TagCarousel},
+			   'video-frames':{fullpath:VideoFrames},
+			   'timeline':{fullpath:Timeline}
+			  }}
+		],
+		[node,event,widget,anim,slider,'align-plugin',
+		 'querystring-stringify-simple','io','jsonp','json',
+  		 'video-player','tag-carousel','timeline',
+		 'video-frames'
+		],
+		[\js_new(tagList,
+			 'Y.mazzle.TagCarousel'({topIndent:symbol(false),
+						 tags:JSONTags,
+						 height:500,
+						 width:200,
+						 edit:true,
+						 suggest:symbol('Y.one("#suggest")')
+						})),
+		 \js_new(videoFrames,
+			 'Y.mazzle.VideoFrames'({frameServer:FrameServer,
+						 dataServer:DataServer,
+						 video:Src,
+						 duration:Duration,
+						 playerPath:PlayerPath
+ 						})),
+		 'Y.one("#suggest").plug(Y.Plugin.Align);\n',
+ 		 \js_call('tagList.render'('#taglist')),
+		 \js_call('videoFrames.render'('#frames')),
+ 		 \js_yui3_on(tagList, itemSelect, \js_tag_select(Video)),
+ 		 \js_yui3_on(videoFrames, confirmSelect, \js_confirm_select),
+		 %\js_call('videoFrames.fetchData'),
+		 \js_freebase_suggest
+ 		]).
+
+
+js_tag_select(Video) -->
+ 	js_function([e],
+		    [ '	var tag = Y.JSON.stringify(e.tag.tags);
+			videoFrames.set("confirm", true);
+		        videoFrames.fetchData({video:"',Video,'", tag:tag});\n'
+		    ]).
+
+js_concept_select -->
+	js_function([e],
+		    [ 'videoFrames.set("concept", e.concept);\n'
+		    ]).
+
+js_confirm_select -->
+	{ http_location_by_id(http_confirm_fragment, Path)
+ 	},
+	js_function([e],
+		    [ 'var f = e.frame;
+		       var tag = e.concept ? e.concept.name : f.tag;
+		       var uri = e.concept ? e.concept.id : null;\n',
+		      \js_call('Y.io'(Path,
+				      {data: {type:symbol('e.type'),
+					      video:symbol('f.video'),
+					      starttime:symbol('f.time'),
+					      tag:symbol(tag),
+					      uri:symbol(uri)}
+  				      }))
+		    ]).
+
+js_freebase_suggest -->
+	html_requires('http://freebaselibs.com/static/suggest/1.2.1/suggest.min.css'),
+	html_requires(js('jquery/jquery-1.4.2.min.js')),
+   	html_requires('http://freebaselibs.com/static/suggest/1.2.1/suggest.min.js'),
+ 	html(\[
+'$("#taginput").suggest({parent:"#suggestResults",
+			 soft:true,
+			 required:true,
+  			 flyout:true})\n'
+	      ]).
+
+
+:- http_handler(yaz(confirm), http_confirm_fragment, []).
+
+%%	http_confirm_fragment(+Request)
+%
+%	Handler for confirmation of video fragment
+
+http_confirm_fragment(Request) :-
+	http_in_session(SessionID),
+	logged_on(User, SessionID),
+	http_parameters(Request,
+			[ video(Video,
+				[description('URL of video')]),
+			  starttime(StartTime,
+			       [number, description('StartTime of fragment')]),
+			  endtime(EndTime,
+				  [number, optional(true), description('EndTime of fragment')]),
+			  type(RoleType,
+			       [optional(true), description('Role of the tag')]),
+			  tag(Tag,
+			      [description('Tag being confirmed')]),
+  			  uri(URI,
+ 			      [optional(true), description('URI of confirmed concept')])
+			]),
+	(   var(EndTime0)
+	->  EndTime is StartTime + 10000
+	;   EndTime = EndTime0
+	),
+ 	rdf_transaction(assert_confirm_event(Video, StartTime, EndTime, Tag, URI, RoleType, User)),
+	reply_json(json([success='confirmation saved',
+ 			 user=User,
+			 video=Video,
+			 starttime=StartTime,
+			 endtime=EndTime,
+			 tag=Tag,
+			 uri=URI
+			])).
+
+assert_confirm_event(Video, StartTime, EndTime, Tag, URI, RoleType, User) :-
+	rdf_bnode(CE),
+  	rdf_assert(CE, rdf:type, pprime:'ConfirmEvent', User),
+	rdf_assert(CE, sem:involves, Video, User),
+ 	rdf_assert(CE, sem:hasActor, User, User),
+
+	rdf_bnode(FA),
+	rdf_assert(FA, rdf:type, pprime:'FragmentAnnotation', User),
+	rdf_assert(FA, sem:subEventOf, CE, User),
+	rdf_assert(FA, sem:hasBeginTimeStamp, literal(StartTime), User),
+	rdf_assert(FA, sem:hasEndTimeStamp, literal(EndTime), User),
+ 	rdf_assert(FA, sem:involves, literal(Tag), User),
+	(   var(URI); URI==null
+	->  URI = null
+	;   rdf_assert(FA, sem:involves, URI, User)
+ 	),
+	(   var(Type)
+	->  Type = null
+	;   rdf_assert(FA, pprime:role, RoleType, User)
+	).
+
+
diff --git a/applications/yaz_tag_garden.pl b/applications/yaz_tag_garden.pl
index b1c97b7..bfad1e3 100644
--- a/applications/yaz_tag_garden.pl
+++ b/applications/yaz_tag_garden.pl
@@ -41,65 +41,41 @@ http_yaz_tag_garden(Request) :-
 	http_parameters(Request,
 			[ video(Video,
 				[description('Current video')]),
- 			  limit(_Limit,
+			  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')]),
+			  interval(Interval,
+				   [default(0), 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(1000), number,
 				 description('limit number of tags shown')])
 			]),
- 	create_user_process([rdf:type=pprime:'TagGarden',
+	Options = [process(Process),
+		   user(User),
+		   interval(Interval),
+		   confirmed(Confirmed)
+		  ],
+	create_user_process([rdf:type=pprime:'TagGarden',
 			     opmv:used=Video
 			    ], _Process),
-	findall(Tag, video_tag(Video, literal(Tag)), Tags0),
-	sort(Tags0, Tags),
-	concept_candidates(Tags, Pairs),
-	tag_clusters(Pairs, TagClusters),
-	maplist(cluster_annotation(Video), TagClusters, Annotations0),
-	sort_by_arg(Annotations0, 2, Annotations1),
-	reverse(Annotations1, Annotations),
-  	html_garden_page(Video, Annotations, []).
-
-cluster_annotation(Video, Tags, annotation(Ts, Count)) :-
-	findall(literal(Tag), (member(Tag-_, Tags),
-		      video_tag(Video, literal(Tag))
-		     ),
-		Ts0),
-	sort(Ts0, Ts),
-	length(Ts0, Count).
-
-concept_candidates([], []).
-concept_candidates([Tag|Ts], [Tag-Cs|Rest]) :-
-	findall(C, find_tag_concept(Tag, C, _), Cs),
-	concept_candidates(Ts, Rest).
-
-
-tag_clusters([], []).
-tag_clusters([Tag|T0], [[Tag|Tags]|T]) :-
-	similar_tags(T0, Tag, Tags0, Rest0),
-	extend_cluster(Tags0, Rest0, Tags, Rest),
-	tag_clusters(Rest, T).
-
-similar_tags([], _, [], []).
-similar_tags([Tag|T], Tag0, [Tag|Tags], Rest) :-
-	my_tag_match(Tag, Tag0),
-	!,
-	similar_tags(T, Tag0, Tags, Rest).
-similar_tags([Tag|T], Tag0, Tags, [Tag|Rest]) :-
-	similar_tags(T, Tag0, Tags, Rest).
-
-extend_cluster([], Rest, [], Rest).
-extend_cluster([Tag|Ts], Tags, Extend, Rest) :-
-	append(Extend0, [Tag|Extend1], Extend),
-	similar_tags(Tags, Tag, Extend0, Rest0),
-	extend_cluster(Ts, Rest0, Extend1, Rest).
-
-my_tag_match(T1-_, T2-_) :-
-	snowball(english, T1, T),
-	snowball(english, T2, T).
-my_tag_match(_T1-Cs1, _T2-Cs2) :-
-	member(C, Cs1),
-	member(C, Cs2).
-	% tag_match:tag_concept_match(C1, C2, _).
+	video_annotations(Video, Annotations, Options),
+	group_annotations(Annotations, AnnotationGroups),
+ 	html_garden_page(Video, AnnotationGroups, Options).
 
 
+group_annotations(Annotations, AnnotationGroups) :-
+	group_by_arg(Annotations, 1, Groups0),
+	maplist(group_to_annotation, Groups0, Groups1),
+	sort_by_arg(Groups1, 2, Groups),
+	reverse(Groups, AnnotationGroups).
+
+group_to_annotation(Value-Annotations, annotation(Value, Count)) :-
+	length(Annotations, Count).
 
 
 %%	http_data_frames(+Request)
@@ -117,16 +93,15 @@ http_data_frames(Request) :-
 			  limit(_Limit,
 				[default(1000), number,
 				 description('limit number of tags shown')]),
-			  tag(Tags,
+			  tag(Tag,
 			      [jsonresource, description('Tag assinged to the video')])
 			]),
 	Options = [process(Process),
 		   user(User)
  		  ],
- 	Obj = Time-json([tag=Label, entry=Id, time=Time]),
-	findall(Obj, (member(T,Tags),
-		      tag_term_label(T,_,Label),
-		      video_annotation(Video, Id, T, Time, Options)), TagEntries0),
+	tag_term_label(Tag, _, Label),
+	Obj = Time-json([tag=Label, entry=Id, time=Time]),
+	findall(Obj, video_annotation(Video, Id, Tag, Time, Options), TagEntries0),
 	keysort(TagEntries0, TagEntries),
 	pairs_values(TagEntries, Fragments),
  	reply_json(json([fragments=Fragments])).
diff --git a/lib/video_annotation.pl b/lib/video_annotation.pl
index 81a5ff9..3d06095 100644
--- a/lib/video_annotation.pl
+++ b/lib/video_annotation.pl
@@ -157,6 +157,16 @@ video_annotation(Video, AnnotationId, Value, Time, Options) :-
 	rdf(AnnotationId, pprime:videoPlayhead, Time0),
 	literal_to_number(Time0, Time).
 
+
+video_fragment_annotation(Video, Start, End, AnnotationId, Value, Time, Options) :-
+	option(process(Process), Options, _),
+	option(user(User), Options, _),
+ 	rdf(Video, pprime:hasAnnotation, AnnotationId, Process),
+	rdf(AnnotationId, pprime:videoPlayhead, literal(between(Start,End),Time0)),
+	once(rdf(AnnotationId, pprime:creator, User)),
+ 	rdf(AnnotationId, rdf:value, Value),
+	literal_to_number(Time0, Time).
+
 %%	video_tag(+Video, -Tag)
 %
 %	Tag is an annotation of Video.
diff --git a/web/css/garden.css b/web/css/garden.css
index 0d5ae82..c63011e 100644
--- a/web/css/garden.css
+++ b/web/css/garden.css
@@ -32,11 +32,16 @@ h4 {
 .yui3-video-frames-content {
 	overflow: hidden;
 }
+.yui3-video-frames .header {
+	padding: 4px;
+	margin: 2px 0;
+	background-color: #333;
+	color: white;
+	clear: both;
+}
 .yui3-video-frames ul.frames-list {
 	margin: 0;
 	padding: 0;
-	overflow: auto;
-	height: 500px;
 }
 .yui3-video-frames li {
 	width: 175px;
diff --git a/web/js/tagcarousel/tagcarousel.js b/web/js/tagcarousel/tagcarousel.js
index 4fa635d..812ada7 100644
--- a/web/js/tagcarousel/tagcarousel.js
+++ b/web/js/tagcarousel/tagcarousel.js
@@ -105,7 +105,6 @@ YUI.add('tag-carousel', function(Y) {
 		formatItem : function(item) { 
 			var tag = item.tag,
 				html;
-			console.log(tag,Lang.isArray(tag));	
 			if(Lang.isArray(tag)) {
 				html = '<div class="label">';
 				for (var i=0; i < tag.length; i++) {
diff --git a/web/js/videoframes/videoframes.js b/web/js/videoframes/videoframes.js
index c5be26f..e7de428 100644
--- a/web/js/videoframes/videoframes.js
+++ b/web/js/videoframes/videoframes.js
@@ -53,10 +53,10 @@ YUI.add('video-frames', function(Y) {
 			value: null
 		},
 		interval: {
-			value: 0
+			value: 10
 		},
 		users: {
-			value: 1
+			value: 2
 		}
 	};
 
@@ -115,8 +115,7 @@ YUI.add('video-frames', function(Y) {
 			this._renderFrames(frames);
 			this.timeline.set("items", frames);
 			if(frames.length>0&&interval>0) {
-				var groups = this._groupFrames(frames, interval, userLimit);
-				this.timeline.updateToInterval(groups, interval);
+				this._filterFrames();
 			}		
 		},
 		
@@ -195,13 +194,18 @@ YUI.add('video-frames', function(Y) {
 		},
 		
 		_renderFrameList : function(node) {
-			list = node.appendChild(Node.create(VideoFrames.LIST_TEMPLATE))
+			var list = node.appendChild(Node.create(VideoFrames.LIST_TEMPLATE));
 			// create list elements
 			var maxFrames = this.get("maxFrames");
 			for(var i=0; i < maxFrames; i++) {
 				list.append('<li class="frame hidden"></li>');
 			}
 			this.listNode = list;
+			
+			var tag = "";
+			// render suggestion list
+			node.appendChild('<div class="header"><span class="tagTitle">'+tag+'</span> might also describe:</div>');
+			this.suggestList = node.appendChild(Node.create(VideoFrames.LIST_TEMPLATE));
 		},
 		
 		_renderFrames : function(frames) {
@@ -318,7 +322,8 @@ YUI.add('video-frames', function(Y) {
 				groups = {};
 			
 			if(interval>0) {	
-				groups = this._groupFrames(frames, interval, userLimit);
+				groups = this._groupFrames(frames, interval);
+				this._updateFrames(groups, userLimit);
 			} else {
 				this.listNode.all("li").each(function(node, i) {
 					if(frames[i]) {
@@ -327,6 +332,7 @@ YUI.add('video-frames', function(Y) {
 					}
 				})
 			}
+			this._updateSuggestFrames(groups, userLimit);
 			this.timeline.updateToInterval(groups, interval);
 		},
 		
@@ -349,22 +355,17 @@ YUI.add('video-frames', function(Y) {
 					groups[group] = [frame];
 				}
 			}
-			
-			// remove groups bellow user limit
-			for(var key in groups) {
-				var userCount = groups[key].length;
-				if(userCount<userLimit) {
-					delete groups[key];
-				}
-			}
-			
+			return groups;
+		},
+		
+		_updateFrames: function(groups, userLimit) {
 			// The grouped frames are visualized by showing only the first frame
 			// of the group and hiding the next ones.
 			// In addition we show the number of unique users in the first frame.
 			// TBD use unique users instead of the number of tag entries, 
 			// which may contain the same user multiple times)
 			this.listNode.all("li").each(function(node, i) {
-				if(groups[i]) {
+				if(groups[i]&&groups[i].length>=userLimit) {
 					node.removeClass("hidden");
 					node.one(".users")
 						.setContent("<span>"+groups[i].length+"</span>")
@@ -373,8 +374,19 @@ YUI.add('video-frames', function(Y) {
 					node.addClass("hidden");
 				}
 			})
-			
-			return groups;
+		},
+		
+		_updateSuggestFrames: function(groups, userLimit) {
+			var list = this.suggestList;
+			this.suggestList.setContent("");
+			for(key in groups) {
+				var frames = groups[key];
+				if(frames&&frames.length<userLimit) {
+					var node = list.appendChild(Node.create('<li class="frame"></li>'));
+					node.setContent(this.formatFrame(frames[0]));
+					//node.prepend('<div class="users hidden"></div>');
+				}
+			}
 		}
 		
 	});