view cpack/dml/api/vis2.pl @ 0:718306e29690 tip

commiting public release
author Daniel Wolff
date Tue, 09 Feb 2016 21:05:06 +0100
parents
children
line wrap: on
line source
/* Part of DML (Digital Music Laboratory)
	Copyright 2014-2015 Samer Abdallah, University of London
	 
	This program is free software; you can redistribute it and/or
	modify it under the terms of the GNU General Public License
	as published by the Free Software Foundation; either version 2
	of the License, or (at your option) any later version.

	This program is distributed in the hope that it will be useful,
	but WITHOUT ANY WARRANTY; without even the implied warranty of
	MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
	GNU General Public License for more details.

	You should have received a copy of the GNU General Public
	License along with this library; if not, write to the Free Software
	Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA  02110-1301  USA
*/

:- module(vis2, []).

/** <module> DML Visualisation web service
 */


:- use_module(library(http/html_write)).
:- use_module(library(http/html_head)).
:- use_module(library(http/http_dispatch)).
:- use_module(library(http/http_parameters)).
:- use_module(library(http/http_json)).
:- use_module(library(http/json)).
:- use_module(library(thread_pool)).
:- use_module(library(sandbox)).
:- use_module(library(dcg_core)).
:- use_module(library(dcg_codes)).
:- use_module(library(dcg_macros)).
:- use_module(library(fileutils)).
:- use_module(library(swipe)).
:- use_module(library(memo)).
:- use_module(library(rdfutils)).
:- use_module(library(httpfiles)).
:- use_module(library(dataset)).
:- use_module(library(insist)).
:- use_module(library(lambda)).
:- use_module(library(dcg/basics), [string_without//2, integer//1]).
:- use_module(library(solution_sequences)).

:- set_prolog_flag(double_quotes,codes).
:- set_prolog_flag(back_quotes,string).

http:location(v2,api(v2),[]).

:- http_handler(v2(dataset), list_datasets, []).
:- http_handler(v2(dataset/define), define_dataset, []).
:- http_handler(v2(view/dataset/index), dataset_views, []).
:- http_handler(v2(view/dataset/items), dataset_items, []).
:- http_handler(v2(view/dataset/summary), dataset_summary, []).
:- http_handler(v2(view/recording/index), recording_views, []).
:- http_handler(v2(view/recording/properties), recording_properties, []).

:- initialization 
      current_thread_pool(dmlvis), !;
      thread_pool_create(vis, 8, [backlog(100)]).

% ------------------------------------------------------------------------------------
% Handlers with documentation

%% list_datasets(+Request) is det.
%  Lists previously defined datsets and the Prolog queries that define them.
list_datasets(R) :- vis(list_datasets,R).

%% define_dataset(+Request) is det.
%  Define a dataset satisfying given search terms. Result is a dataset
%  ID, which may be the same as a previously defined dataset if it consists
%  of the same items.
define_dataset(R) :- vis(define_dataset,R).

%% dataset_views(+Request) is det.
%  Lists available views for datasets.
dataset_views(R) :- vis(list_views(dataset),R).

%% dataset_items(+Request) is det.
%  Lists items in a given dataset specified by its ID..
dataset_items(R) :- vis(dataset_items,R).

%% dataset_summary(+Request) is det.
%  Returns some summary information about a dataset.
dataset_summary(R) :- vis(dataset_summary,R).

%% recording_views(+Request) is det.
%  Lists available views for recordings.
recording_views(R) :- vis(list_views(recording),R).

%% recording_properties(+Request) is det.
%  Returns all the properties currently held in the RDF graph about a given recording.
recording_properties(R) :- vis(recording_properties,R).


% ------------------------------------------------------------------------------------

%% vis(+Method,+Request) is det.
%
%  Top level predicate for implementing VIS API. Handles common tasks
%  like determining the reply format, handling errors, and formatting the reply.
vis(Method,Request) :-
   method_params_goal(Method,Params,Goal),
   vis(Params,Goal,Request).

vis(Params,Goal,Request) :-
   http_parameters(Request, [format(Format), callback(Callback) | Params], 
                            [attribute_declarations(param)]), 
   (Format=jsonp -> Fmt=jsonp(Callback); Fmt=json),
   member(request_uri(Query),Request),
   catch( insist(call(Goal,Result,Status)),
          Ex, (error_result(Ex,Result), Status=error)), 
   result_response(Fmt,Query,Result,Status,Response),
   write(Response).

result_response(Fmt,Q,Result,Status,Response) :- 
   with_output_to(string(Response),
      reply_as(Fmt,Status,_{ query:Q, result: Result})).

reply_as(json,Status,Dict) :- 
   write_headers([Status,type(json)]),
   json_write_dict(current_output, Dict).
reply_as(jsonp(Cb),Status,Dict) :- 
   write_headers([Status,type(jsonp)]),
   write(Cb), write('('),
   json_write_dict(current_output, Dict),
   write(');').


error_result(dml_error(Code,Descriptor),_{ code: Code, desc:Desc }) :- !,
   format(string(Desc),'ERROR: ~w',[Descriptor]).

error_result(Ex, _{ code: 500, desc: Msg }) :-
   message_to_string(Ex,Msg).

% ------------------------------------------------------------------------------------
% Implementation of methods

:- multifile param/2.

% general
param( format,   [oneof([json,jsonp]), default(jsonp), description('Reply format')]).
param( callback, [atom,default(jsonp_cb), description('Callback for jsonp reply')]).

% define_dataset
param( library,   [oneof([beets,charm,bl,ilm]), default(bl), description('Library to search within')]).
param( dv,        [nonneg, optional(false), description('Database version ID')]).
param( genres,    [atom, default(*), description('Semicolon separated list of genre names, or "*"')]).
param( years,     [atom, default(*), description('Semicolon separeted list of release years or a range (Y1-Y2) or "*"')]).
param( composers, [atom, default(*), description('Semicolon separated list of composers or "*"')]).
param( performers,[atom, default(*), description('Semicolon separated list of performers or "*"')]).

param( cid,       [atom, optional(false), description('Collection ID')]).
param( cids,      [atom, optional(false), description('Semicolon separated list of Collection IDs')]).
param( uri,       [atom, optional(false), description('Recording URI')]).
param( limit,     [integer, default(5000), description('Maximum number of things to return')]).
param( offset,    [integer, default(0), description('Offset within list')]).

method_params(listCollections, []).
method_params(listPerspectives, [method(_)]).
method_params(collection_id, [library(_),dv(_),genres(_),years(_),composers(_),performers(_)]).
method_params(Method, [ pid(_) | Params ]) :-
   perspective(Method,_,_,_,_), 
   setof(P, perspective_param_name(Method,P), Ps),
   maplist(param_name_term,Ps,Params).

param_name_term(Name,Term) :- functor(Term,Name,1).
perspective_param_name(Method,Name) :-
   perspective(Method,_,_,Specs,_),
   member(S,Specs),
   optspec_name(S,Name).

   
:- multifile perspective/5.

method_result(listCollections, _, _{ collections:List }, unstable) :-
   findall( _{ cid:Id, query:QA, dv:DV, size:SZ },
            (  browse(dataset:dataset(dmlvis:Q, DV, Id, SZ, _)),
               term_to_atom(Q,QA)
            ),
            List).
method_result(Method,Opts,Result,stable) :- 
   method_result(Method,Opts,Result).
            


method_result(listPerspectives, Opts, _{ perspectives:List }) :-
   option(method(Method), Opts),
   findall( P, perspective(Method,P,_,_,_), List).

method_result(collection_id, Opts, _{ cid:Id, size:Size }) :-
   option(dv(DBV),Opts),
   option(library(Coll),Opts),
   collection_query(Coll, Opts, Query),
   dataset_query_id( Query, DBV, Id),
   dataset_size(Id, Size).

options_optspec(_,Opts,\O) :- option(O,Opts).
options_optspec(_,Opts,O-Def) :- option(O,Opts,Def).
options_optspec(M,Opts,O>Goal) :- options_optspec(M,Opts,O), call(M:Goal).

optspec_name(\O,Name) :- functor(O,Name,1).
optspec_name(O-_,Name) :- functor(O,Name,1).
optspec_name(O>_,Name) :- optspec_name(O,Name).

perspective(getRecordingPerspective,        properties, dmlvis, [\uri(URI)], recording_info(URI)).
perspective(getCollectionPerspective,       summary, dmlvis, [\cid(C)], collection_summary(C)).
perspective(getCollectionPerspective,       list,    dmlvis, [\cid(C),limit(Lim)-5000,offset(Off)-0], collection_list(C,Lim,Off)).
% perspective(getCollectionPairPerspective,   summary, dmlvis, [\cids(A)>parse_atom(cids([C1,C2]),A)], binary(summary,C1,C2)).
% perspective(getMultiCollectionPerspective, summary, dmlvis, [\cids(A)>parse_atom(cids(Cs),A)], multi(summary,Cs)).

collection_summary(Id,Result) :-
   insist(browse(dataset:dataset(Goal,DV,Id,Size,_)), unknown_collection(Id)),
   term_to_atom(Goal,GoalA),
   Result = _{cid:Id, size:Size, goal:GoalA, dv:DV }.

collection_list(Id, Lim, Offset, _{cid:Id, size:Size, items:Items}) :-
   dataset_size(Id,Size),
   findall(Item,limit(Lim,offset(Offset,dataset_item(Id,Item))),Items).

% --------------- recording_properties -----------------------------

recording_info(URI, Result) :-
   (  a(mo:'AudioFile',URI) -> G=audiofile_info(URI)
   ;  a(mo:'Track',URI)     -> G=track_info(URI)
   ;  a(mo:'Signal',URI)    -> G=signal_info(URI)
   ;  rdf(URI,charm:file_name,_) -> G=charm_info(URI)
   ;  throw(not_a_recording(URI))
   ),
   insist(call(G,Result),failed(G)).

audiofile_info(URI,Result) :-
   rdf_text(URI,beets:title,Title),
   rdf_text(URI,beets:album,AlbumName),
   rdf_text(URI,beets:artist,ArtistName),
   rdf_number(URI,beets:length,Duration),
   Result = _{ type:audiofile, title:Title, artist:ArtistName, album:AlbumName, duration:Duration }.

track_info(Track, Result) :-
   rdf_number(Track,mo:duration,DurationMs), Duration is DurationMs/1000.0,
   rdf_text(Track,dc:title,Title),
   rdf(Record,mo:track,Track),
   rdf(Release,mo:record,Record),
   rdf_text(Release,dc:title,AlbumName),
   rdf(Artist,foaf:made,Track),
   rdf_text(Artist,foaf:name,ArtistName),
   Result = _{ type:track, title:Title, artist:ArtistName, album:AlbumName, duration:Duration }.

signal_info(Signal, _{type:signal, tracks:Infos}) :-
   setof(T,rdf(T,mo:publication_of,Signal),Tracks),
   maplist(track_info,Tracks,Infos).

charm_info(URI, PropDict) :-
   setof(Pred-Vals,setof(Val1,Val^(rdf(URI,Pred,literal(Val)),atomise_literal(Val,Val1)),Vals),Info),
   dict_pairs(PropDict,_,Info).

atomise_literal(type(_,Val),Val) :- !.
atomise_literal(lang(_,Val),Val) :- !.
atomise_literal(Val,Val).

% -------------------- defining a dataset ------------------------------

qc(beets,Opts,X) :- maplist(filter(beets,X),Opts), a(mo:'AudioFile',X).
qc(charm,Opts,X) :- maplist(filter(charm,X),Opts), rdf(X,charm:file_name,_).
qc(bl,Opts,X)    :- maplist(filter(bl,X),Opts), rdf(X,rdf:type,mo:'Signal',bl_p2r).

filter(_,_,genres(*)) :- true.
filter(beets,X,genres(any(Gs))) :- member(G,Gs), rdf_has(X,beets:genre,literal(substring(G),_)).

filter(_,_,years(*)) :- true.
filter(D,X,years(any(Ys))) :- member(Y,Ys), filter(D,X,years(Y-Y)).
filter(D,X,years(L-U)) :- succ(U,U1), atom_number(LA,L), atom_number(U1A,U1), filter(D,X,years(LA,U1A)).
filter(beets,X,years(L,U)) :- rdf(X, beets:original_year, literal(between(L,U),_)).
filter(charm,X,years(L,U)) :- rdf(X, charm:recording_date, literal(between(L,U),_)).
filter(bl,X,years(L,U))    :- rdf(X, dcterms:created, literal(between(L,U),_)).

filter(_,_,composers(*)) :- true.
filter(D,X,composers(any(List))) :- member(C,List), filter(D,X,composer(C)).
filter(charm,X,composer(C)) :- rdf(X, charm:composer, literal(prefix(C),_)).
filter(bl,X,composer(C)) :- rdf(X, marcrel:cmp, literal(prefix(C),_)).
filter(_,_,performers(*)) :- true.
filter(D,X,performers(any(List))) :- member(C,List), filter(D,X,performer(C)).
filter(charm,X,performer(C)) :- rdf(X, charm:performer, literal(prefix(C),_)).
filter(bl,X,performer(C)) :- rdf(X, marcrel:prf, literal(prefix(C),_)).
filter(beets,X,performer(C)) :- rdf(X, beets:artist, literal(prefix(C),_)).
filter(charm,X,title(C)) :- rdf(X, charm:title, literal(substring(C),_)).
filter(bl,X,title(C)) :- rdf(X, dc:title, literal(substring(C),_)).
filter(beets,X,title(C)) :- rdf(X, beets:title, literal(like(C),_)).


collection_query(Coll, Opts, qc(Coll,Filters)) :-
   seqmap(process_qopt(Opts),
      [  qo( genres(GA),     genres(GS),     genres(*),     parse_atom(atoms(GS), GA))
      ,  qo( composers(CA),  composers(CS),  composers(*),  parse_atom(atoms(CS), CA))
      ,  qo( performers(PA), performers(PS), performers(*), parse_atom(atoms(PS), PA))
      ,  qo( years(YA),      years(YS),      years(*),      parse_atom(years(YS), YA))
      ,  qo( title(T),       title(T),       title(*),      true)
      ], 
      Filters, []).

process_qopt(Opts,qo(Opt,Filter,NullFilter,Goal)) -->
   {option(Opt,Opts,'*'), call(Goal)},
   ({Filter=NullFilter} -> []; [Filter]).
            

% --------- parsers -----------

% cids(Ids) --> seqmap_with_sep(",",alphanum,Ids).
cids(Ids) --> semicolon_sep(atom_codes,Ids).

atoms('*') --> "*", !.
atoms(any(AS)) --> semicolon_sep(atom_codes,AS).

years('*') --> "*", !.
years(L-U) --> integer(L), "-", integer(U). 
years(any(Ys)) --> semicolon_sep(number_codes,Ys).



% alphanum(X) --> string_without(",",S), {atom_string(X,S)}.

item(Conv,Item) --> string_without(";",Codes), {call(Conv,Item,Codes)}.
semicolon_sep(Conv,Items) -->
   seqmap_with_sep(";",item(Conv),Items).


parse_atom(Phrase,Atom) :- 
   atom_codes(Atom,Codes), 
   debug(vis,'Attempting to parse ~q with ~q...',[Atom,Phrase]),
   insist( phrase(Phrase,Codes), parse_failure(Phrase)),
   debug(vis,'...got ~q',[Phrase]).