yaz/commit
first prototype for tag gardening from tag perspective
author | Michiel Hildebrand |
---|---|
Thu Jan 26 15:49:08 2012 +0100 | |
committer | Michiel Hildebrand |
Thu Jan 26 15:49:08 2012 +0100 | |
commit | 262162196ae82457c2a47fd0a262b39bed566224 |
tree | 69f2cf350d573e8103c38a1877ca5ead6734460c |
parent | 20623488be11bb52245b642a41c3a283332bc7ae |
Diff style: patch stat
diff --git a/applications/yaz_tag.pl b/applications/yaz_tag.pl index 0cad6b5..cbd3ef1 100644 --- a/applications/yaz_tag.pl +++ b/applications/yaz_tag.pl @@ -1,5 +1,5 @@ :- module(yaz_tag, - [ http_yaz_tag_edit/1 + [ http_yaz_tag/1 ]). :- use_module(library(http/http_dispatch)). @@ -10,215 +10,182 @@ :- 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(yui3_beta)). :- use_module(library(video_annotation)). -:- use_module(components(label)). :- use_module(components(yaz_page)). :- use_module(api(reconcile)). -:- http_handler(yaz(tagedit), http_yaz_tag_edit, []). -%% http_yaz_tag_edit(+Request) +:- setting(language, atom, dutch, + 'language used for stemming'). +:- setting(max_reconcile, integer, 3, + 'maximum number of concepts used to find related tags'). + +:- http_handler(yaz(tag), http_yaz_tag, []). + +%% http_yaz_tag(+Request) % % Emit an HTML page with gardening options for a tag. -http_yaz_tag_edit(Request) :- +http_yaz_tag(Request) :- http_parameters(Request, - [ entry(Entry, - [description('URL of tag entry')]), - action(Action, - [default(request)]), - 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')]), - format(Format, - [default(page), - oneof([page,form]), - description('Return a complete html page or only the form')]) + [ tag(TagList0, + [zero_or_more]) ]), - update_tag(Action, Entry, Value, Concept, Role), - ( rdf(Entry, rdf:type, pprime:'TagEntry') - -> annotation_value(Entry, _TagId, Label) - ; Label = Entry - ), - %annotation_provenance(Entry, Provenance), - tag_concepts(Label, Concepts), - ( Format = page - -> html_page(Entry, Label, Provenance, Concepts, Concept, Role) - ; html_current_option(content_type(Type)), - phrase(html_form(Entry, Label, Provenance, Concepts, Concept, Role), HTML), - format('Content-type: ~w~n~n', [Type]), - print_html(HTML) - ). + sort(TagList0, TagList), + related_tags(TagList, RelatedTags), + tag_annotations(TagList, Annotations), + %list_limit(Annotations0, 20, Annotations, _), + html_tag_page(TagList, RelatedTags, Annotations). +%% tag_annotations(+Tag, -Annotations) +% +% Shots is a list of Shots annotated with tag. + +tag_annotations(TagList, Annotations) :- + findall(Time-entry(Entry,Video,Value,Process,User,Time), + annotated_shot(TagList, Entry, Value, Video, Process, User, Time), + Entries), + keysort(Entries, TimeSorted0), + pairs_values(TimeSorted0, TimeSorted), + group_entries(TimeSorted, Annotations). + +group_entries([], []). +group_entries([E|Es], [A|As]) :- + E = entry(Entry,Video,Value,_Process,_User,Time), + A = video_annotation(Value, Video, Time, Time, [entry(Entry,Value,Time)]), + group_entries(Es, As). + + +annotated_shot(Tags, Entry, TagTerm, Video, Process, User, Time) :- + member(Tag, Tags), + tag_value(Tag, Value, TagTerm), + value_annotation(Value, Process, User, Video, Entry, Time). + +tag_value(Tag, Value, uri(Value, Tag)) :- + rdf(Value, rdfs:label, literal(Tag)), + rdf(Value, rdf:type, pprime:'Tag'), + !. +tag_value(Tag, literal(Tag), literal(Tag)). -annotation_value(Entry, TagId, Label) :- - rdf(Entry, rdf:value, TagId), - rdf_label(TagId, Lit), - literal_text(Lit, Label). - -tag_concepts(Label, Concepts) :- - rdf_equal(skos:'Concept', Type), - reconcile(Label, 3, Type, [], Hits), - maplist(hit_concept, Hits, Concepts). - -hit_concept(hit(_,URI,_,Label), concept(URI,Label,Alt,Desc)) :- - ( rdf_has(URI, rdfs:label, Lit), - literal_text(Lit, Alt), - \+ Alt == Label - -> true - ; Alt = '' - ), - ( rdf_has(URI,skos:scopeNote,Txt) - -> literal_text(Txt,Desc) - ; rdf_has(URI, skos:definition,Txt) - -> literal_text(Txt,Desc) - ; Desc = '' +%% related_tags(+TagList, -Related) +% +% Related is a list of tags that are related to Tag. +% +% stemming +% subword +% @TBD semantic relations + +related_tags(TagList, RelatedTags) :- + findall(Rel-Value, + ( member(Tag, TagList), + related_tag(Tag, Value, Rel) + ), + RelatedTags0), + sort(RelatedTags0, RelatedTags). + +related_tag(Tag, RelatedTag, Type) :- + setting(language, Lang), + snowball(Lang, Tag, Stem), + rdf(S,P,literal(prefix(Stem), RelatedTag)), + is_tag_label(S,P,literal(RelatedTag)), + ( snowball(Lang, RelatedTag, Stem) + -> Type = stem + ; Type = subword ). - /******************************* - * update * - *******************************/ -% do we need this here? +/* +semantic_related_tag( + concept_synonym(Concept -update_tag(request, _, _, _, _). -update_tag(confirm, _, _, _, _). +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). +*/ + + +is_tag_label(_S,P,_Lit) :- + rdf_equal(pprime:hasAnnotation, P). +is_tag_label(S,_P,_Lit) :- + rdf(S,rdf:type,pprime:'Tag'), + !. /******************************* * HTML * *******************************/ -html_page(Entry, TagLabel, Provenance, Concepts, Concept, Role) :- +html_tag_page(Tag, RelatedTags, Shots) :- + length(Shots, NumberOfShots), reply_html_page(yaz, - [ title(['YAZ - ', Entry]) - ], - [ \html_requires(css('tag.css')), - \html_form(Entry, TagLabel, Provenance, Concepts, Concept, Role) + [title(['YAZ -- ',Tag])], + [\html_requires(css('tag_garden.css')), + div(class(bd), + [ h1(Tag), + div(id(related), + [ h2(['Related tags']), + ul(\html_tags(RelatedTags)) + ]), + div(id(shots), + [ h2([NumberOfShots, + ' shots annotated']), + div(id(frames), []) + ]) + ]), + script(type('text/javascript'), + \yui_script(Tag, RelatedTags, Shots)) ]). -html_form(Entry, TagLabel, _Provenance, Concepts, _Concept, Role) --> - html(%form(action(location_by_id(http_yaz_tag_edit)), - [ input([type(hidden), name(entry), value(Entry)]), - input([type(hidden), name(action), value(confirm)]), - div([class(block), id(edit)], - [ h4('edit tag'), - \html_tag_edit(TagLabel) - ]), - div([class(block), id(concept)], - [ h4('identify tag'), - ul(class(concepts), - \html_concepts(Concepts)) - ]), - div([class(block), id(role)], - [ h4('select role'), - \html_roles(Role) - ]), - /*div([class(block), id(provenance)], - [ h4('history'), - \html_provenance(Provenance) - ]),*/ - div(class(submit), - [ input([id(applyall), type(submit), value('apply to all')]), - input([id(apply), type(submit), value('apply')]) - ]) /*, - script(type('text/javascript'), - \html_video_page_yui(Video, Annotations, StartTime, Options))*/ - ]). - -html_tag_edit(Value) --> - html(input([name(value), id(value), type(text), value(Value)])). - -html_concepts([]) --> !. -html_concepts([concept(URI,Label,_Alt,Desc)|Cs]) --> - html(li(\html_radiobox(concept, URI, false, - [ a(href(URI), Label), - div(class(desc), Desc) - ]))), - html_concepts(Cs). - - -html_roles(Selected) --> - html(ul(class(options), - [ li(\html_radiobox(role, depicted, Selected, 'depicted')), - li(\html_radiobox(role, associated, Selected, 'associacted')) - ])). - -html_radiobox(Group, Value, Selected, Label) --> - { radio_checked(Value, Selected, Checked) - }, - html([input([type(radio), name(Group), value(Value), Checked]), - span(Label) - ]). - -radio_checked(Selected, Selected, checked) :- !. -radio_checked(_, _, ''). - -html_provenance([]) --> !. -html_provenance([action(_,Time,User,_,Action)|T]) --> - html_provenance_action(Action,Time,User), - html_provenance(T). - -html_provenance_action(added(_, _, Value, _PlayHead), Time, User) --> - html(div(class(paction), - [ 'added ', - \html_tag_value(Value), - \html_time_user(Time, User)])). -html_provenance_action(removed(_, _), Time, User) --> - html(div(class(paction), - [ 'removed ', - \html_time_user(Time, User)])). -html_provenance_action(valueChange(_, Value), Time, User) --> - html(div(class(paction), - [ 'changed to ', - \html_tag_value(Value), - \html_time_user(Time, User)])). -html_provenance_action(timeChange(_, PlayHead), Time, User) --> - html(div(class(paction), - [ 'changed time to ', PlayHead, - \html_time_user(Time, User)])). - -html_time_user(Time, _User) --> - html([' at ', \html_time(Time)]). -% ' by ', \html_user(User) ]). - -html_time(Time) --> - { time_format(Time, Formatted) }, - html(Formatted). -html_user(UserURL) --> - { display_label(UserURL, Name) - }, - html(Name). -html_tag_value(literal(Lit)) --> - { literal_text(Lit, L) - }, - html(['"',L,'"']). -html_tag_value(URI) --> - { rdf_label(URI, Lit), - literal_text(Lit, L) - }, - html(['"',L,'"']). - -time_format(TimeStamp, Formatted) :- - catch(format_time(atom(Formatted), '%Y-%m-%d %T', TimeStamp), _, fail), - !. -time_format(Time, Time). - - - - +html_tags([]) --> !. +html_tags([Type-Tag|T]) --> + html(li(class(Type), Tag)), + html_tags(T). +yui_script(_Tag, _RelatedTags, Annotations) --> + { http_location_by_id(serve_video_frame, FrameServer), + http_absolute_location(js('videoframes/videoframes.js'), Videoframes, []), + annotation_to_json(Annotations, JSONAnnotations) + }, + yui3([{modules:{'video-frames':{fullpath:Videoframes}} + } + ], + [node,event,widget,anim, + 'json','jsonp','querystring-stringify-simple',io, + 'video-frames' + ], + [\js_new(videoFrames, + 'Y.mazzle.VideoFrames'({frameServer:FrameServer, + frames:JSONAnnotations, + confirm:symbol(true), + interval:0, + showRelated:symbol(false), + showTime:symbol(true), + disabled:symbol(false), + maxFrames:500 + })), + \yui3_render(videoFrames, #(frames)) + ]). diff --git a/applications/yaz_tag_edit.pl b/applications/yaz_tag_edit.pl new file mode 100644 index 0000000..b55f717 --- /dev/null +++ b/applications/yaz_tag_edit.pl @@ -0,0 +1,217 @@ +:- module(yaz_tag_edit, + [ http_yaz_tag_edit/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(yaz_util)). +:- use_module(library(yui3)). +:- use_module(library(video_annotation)). + +:- use_module(components(label)). +:- use_module(components(yaz_page)). +:- use_module(api(reconcile)). + +:- http_handler(yaz(tagedit), http_yaz_tag_edit, []). + +%% http_yaz_tag_edit(+Request) +% +% Emit an HTML page with gardening options for a tag. + +http_yaz_tag_edit(Request) :- + http_parameters(Request, + [ entry(Entry, + [description('URL of tag entry')]), + action(Action, + [default(request)]), + 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')]), + format(Format, + [default(page), + oneof([page,form]), + description('Return a complete html page or only the form')]) + ]), + update_tag(Action, Entry, Value, Concept, Role), + ( rdf(Entry, rdf:type, pprime:'TagEntry') + -> annotation_value(Entry, _TagId, Label) + ; Label = Entry + ), + %annotation_provenance(Entry, Provenance), + tag_concepts(Label, Concepts), + ( Format = page + -> html_page(Entry, Label, Provenance, Concepts, Concept, Role) + ; html_current_option(content_type(Type)), + phrase(html_form(Entry, Label, Provenance, Concepts, Concept, Role), HTML), + format('Content-type: ~w~n~n', [Type]), + print_html(HTML) + ). + + + +annotation_value(Entry, TagId, Label) :- + rdf(Entry, rdf:value, TagId), + rdf_label(TagId, Lit), + literal_text(Lit, Label). + +tag_concepts(Label, Concepts) :- + rdf_equal(skos:'Concept', Type), + reconcile(Label, 3, Type, [], Hits), + maplist(hit_concept, Hits, Concepts). + +hit_concept(hit(_,URI,_,Label), concept(URI,Label,Alt,Desc)) :- + ( rdf_has(URI, rdfs:label, Lit), + literal_text(Lit, Alt), + \+ Alt == Label + -> true + ; Alt = '' + ), + ( rdf_has(URI,skos:scopeNote,Txt) + -> literal_text(Txt,Desc) + ; rdf_has(URI, skos:definition,Txt) + -> literal_text(Txt,Desc) + ; Desc = '' + ). + + /******************************* + * update * + *******************************/ +% do we need this here? + +update_tag(request, _, _, _, _). +update_tag(confirm, _, _, _, _). + + + /******************************* + * HTML * + *******************************/ + +html_page(Entry, TagLabel, Provenance, Concepts, Concept, Role) :- + reply_html_page(yaz, + [ title(['YAZ - ', Entry]) + ], + [ \html_requires(css('tag.css')), + \html_form(Entry, TagLabel, Provenance, Concepts, Concept, Role) + ]). + +html_form(Entry, TagLabel, _Provenance, Concepts, _Concept, Role) --> + html(%form(action(location_by_id(http_yaz_tag_edit)), + [ input([type(hidden), name(entry), value(Entry)]), + input([type(hidden), name(action), value(confirm)]), + div([class(block), id(edit)], + [ h4('edit tag'), + \html_tag_edit(TagLabel) + ]), + div([class(block), id(concept)], + [ h4('identify tag'), + ul(class(concepts), + \html_concepts(Concepts)) + ]), + div([class(block), id(role)], + [ h4('select role'), + \html_roles(Role) + ]), + /*div([class(block), id(provenance)], + [ h4('history'), + \html_provenance(Provenance) + ]),*/ + div(class(submit), + [ input([id(applyall), type(submit), value('apply to all')]), + input([id(apply), type(submit), value('apply')]) + ]) /*, + script(type('text/javascript'), + \html_video_page_yui(Video, Annotations, StartTime, Options))*/ + ]). + +html_tag_edit(Value) --> + html(input([name(value), id(value), type(text), value(Value)])). + +html_concepts([]) --> !. +html_concepts([concept(URI,Label,_Alt,Desc)|Cs]) --> + html(li(\html_radiobox(concept, URI, false, + [ a(href(URI), Label), + div(class(desc), Desc) + ]))), + html_concepts(Cs). + + +html_roles(Selected) --> + html(ul(class(options), + [ li(\html_radiobox(role, depicted, Selected, 'depicted')), + li(\html_radiobox(role, associated, Selected, 'associacted')) + ])). + +html_radiobox(Group, Value, Selected, Label) --> + { radio_checked(Value, Selected, Checked) + }, + html([input([type(radio), name(Group), value(Value), Checked]), + span(Label) + ]). + +radio_checked(Selected, Selected, checked) :- !. +radio_checked(_, _, ''). + +html_provenance([]) --> !. +html_provenance([action(_,Time,User,_,Action)|T]) --> + html_provenance_action(Action,Time,User), + html_provenance(T). + +html_provenance_action(added(_, _, Value, _PlayHead), Time, User) --> + html(div(class(paction), + [ 'added ', + \html_tag_value(Value), + \html_time_user(Time, User)])). +html_provenance_action(removed(_, _), Time, User) --> + html(div(class(paction), + [ 'removed ', + \html_time_user(Time, User)])). +html_provenance_action(valueChange(_, Value), Time, User) --> + html(div(class(paction), + [ 'changed to ', + \html_tag_value(Value), + \html_time_user(Time, User)])). +html_provenance_action(timeChange(_, PlayHead), Time, User) --> + html(div(class(paction), + [ 'changed time to ', PlayHead, + \html_time_user(Time, User)])). + +html_time_user(Time, _User) --> + html([' at ', \html_time(Time)]). +% ' by ', \html_user(User) ]). + +html_time(Time) --> + { time_format(Time, Formatted) }, + html(Formatted). +html_user(UserURL) --> + { display_label(UserURL, Name) + }, + html(Name). +html_tag_value(literal(Lit)) --> + { literal_text(Lit, L) + }, + html(['"',L,'"']). +html_tag_value(URI) --> + { rdf_label(URI, Lit), + literal_text(Lit, L) + }, + html(['"',L,'"']). + +time_format(TimeStamp, Formatted) :- + catch(format_time(atom(Formatted), '%Y-%m-%d %T', TimeStamp), _, fail), + !. +time_format(Time, Time). diff --git a/lib/video_annotation.pl b/lib/video_annotation.pl index 5227f0b..1c22448 100644 --- a/lib/video_annotation.pl +++ b/lib/video_annotation.pl @@ -1,6 +1,6 @@ :- module(yaz_video_annotation, [ annotation_process/4, % ?User, ?Video, ?Process - value_annotation/4, % +Value, ?Process, +User, -Time + value_annotation/6, % +Value, ?Process, ?User, -Video, -Entry, -Time video_annotations/3, % +Video, -Annotations, +Options video_annotation/5, % +Video, -AnnotationId, -Value, -Time, -Score video_annotation/6, % +Video, -AnnotationId, -Value, -Time, -Score, +Options @@ -90,13 +90,14 @@ has_transaction(Process) :- user_transaction(Process, _User, true, _), !. -%% value_annotation(+Value, ?Process, ?User, -Time) +%% value_annotation(+Value, ?Process, ?User, -Video, +%% -Annotation, -Time) % % True if Time is playHead at which Value has been added. -value_annotation(Value, Process, User, Time) :- +value_annotation(Value, Process, User, Video, Annotation, Time) :- rdf(Annotation, rdf:value, Value, Process), - rdf(_, pprime:hasAnnotation, Annotation), + rdf(Video, pprime:hasAnnotation, Annotation), rdf(Annotation, pprime:creator, User), rdf(Annotation, pprime:videoPlayhead, literal(Time0)), literal_to_number(Time0, Time). @@ -294,10 +295,15 @@ video_fragment_annotation(Video, Start, End, AnnotationId, Value, Time, Options) rdf(AnnotationId, rdf:value, Value), literal_to_number(Time0, Time). -%% video_tag(+Video, -Tag) +%% video_tag(?Video, ?Tag) % % Tag is an annotation of Video. +video_tag(Video, Tag) :- + ground(Tag), + !, + rdf(AnnotationId, rdf:value, Tag), + rdf(Video, pprime:hasAnnotation, AnnotationId). video_tag(Video, Tag) :- rdf(Video, pprime:hasAnnotation, AnnotationId), rdf(AnnotationId, rdf:value, Tag). diff --git a/lib/yaz_util.pl b/lib/yaz_util.pl index 2a2fccc..fca1881 100644 --- a/lib/yaz_util.pl +++ b/lib/yaz_util.pl @@ -363,6 +363,7 @@ http:convert_parameter(jsonresource, Atom, Term) :- annotation(tag:_, startTime:number, endTime:number, annotations:list), annotation(tag:_, startTime:number, endTime:number, annotations:list, score:number), annotation(tag:_, startTime:number, endTime:number, annotations:list, score:number, match:_), + video_annotation(tag:_, video:atom, startTime:number, endTime:number, annotations:list), match(type:atom, score:_), match(type:atom, score:_, uri:_, value:_), concept(uri:_, label:atom, altlabel:atom, desc:atom). diff --git a/web/css/tag_garden.css b/web/css/tag_garden.css new file mode 100644 index 0000000..60b3f10 --- /dev/null +++ b/web/css/tag_garden.css @@ -0,0 +1,71 @@ +/* related */ +#related { + overflow: auto; +} +#related ul { + margin: 0; + padding: 0; +} +#related li { + background-color: #EEEEEE; + border: 1px solid #AAAAAA; + border-radius: 5px 5px 5px 5px; + float: left; + list-style: none outside none; + margin: 0 5px 5px 0; + padding: 3px 5px; +} + +/* video frames */ +.yui3-video-frames { +} +.yui3-video-frames .header { + padding-bottom: 2px; + margin: 12px 0 4px; + font-weight: bold; + border-bottom: 1px solid #CCC; + clear: both; +} +.yui3-video-frames ul.frames-list { + margin: 0; + padding: 0; +} +.yui3-video-frames li { + float: left; + list-style: none; + margin: 0 auto 5px; + border: 4px solid transparent; +} +.yui3-video-frames li.selected { +} +.yui3-video-frames li.hidden { + display: none; +} +.yui3-video-frames .image { + width: 200px; + height: 200px; + background-color: #EEE; +} +.yui3-video-frames img { + width: 200px; + height: 200px; +} +.yui3-video-frames .tag, +.yui3-video-frames .frame-confirm { + text-align: center; + padding: 3px 0; + 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; +} \ No newline at end of file diff --git a/web/js/videoframes/videoframes.js b/web/js/videoframes/videoframes.js index 03208a2..e5e4dd3 100644 --- a/web/js/videoframes/videoframes.js +++ b/web/js/videoframes/videoframes.js @@ -28,9 +28,6 @@ YUI.add('video-frames', function(Y) { frameServer: { value: null }, - dataServer: { - value: null - }, maxFrames: { value: 50 }, @@ -138,7 +135,7 @@ YUI.add('video-frames', function(Y) { if(frames[i]) { var startTime = frames[i].startTime; node.setContent(this.formatFrame(frames[i])); - if(time==0 || startTime>time+interval) { + if(time==0 || interval==0 || startTime>time+interval) { node.removeClass("hidden"); } time = startTime; @@ -151,7 +148,7 @@ YUI.add('video-frames', function(Y) { formatFrame : function(frame) { var frameServer = this.get("frameServer"), - video = this.get("video"), + video = frame.video || this.get("video"), time = frame.startTime/1000, label = frame.tag ? (frame.tag.label ? frame.tag.label : frame.tag.value) : '', role = frame.role ? frame.role : '',