:- 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).