Mercurial > hg > dml-open-cliopatria
comparison 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 |
comparison
equal
deleted
inserted
replaced
-1:000000000000 | 0:718306e29690 |
---|---|
1 /* Part of DML (Digital Music Laboratory) | |
2 Copyright 2014-2015 Samer Abdallah, University of London | |
3 | |
4 This program is free software; you can redistribute it and/or | |
5 modify it under the terms of the GNU General Public License | |
6 as published by the Free Software Foundation; either version 2 | |
7 of the License, or (at your option) any later version. | |
8 | |
9 This program is distributed in the hope that it will be useful, | |
10 but WITHOUT ANY WARRANTY; without even the implied warranty of | |
11 MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the | |
12 GNU General Public License for more details. | |
13 | |
14 You should have received a copy of the GNU General Public | |
15 License along with this library; if not, write to the Free Software | |
16 Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301 USA | |
17 */ | |
18 | |
19 :- module(vis2, []). | |
20 | |
21 /** <module> DML Visualisation web service | |
22 */ | |
23 | |
24 | |
25 :- use_module(library(http/html_write)). | |
26 :- use_module(library(http/html_head)). | |
27 :- use_module(library(http/http_dispatch)). | |
28 :- use_module(library(http/http_parameters)). | |
29 :- use_module(library(http/http_json)). | |
30 :- use_module(library(http/json)). | |
31 :- use_module(library(thread_pool)). | |
32 :- use_module(library(sandbox)). | |
33 :- use_module(library(dcg_core)). | |
34 :- use_module(library(dcg_codes)). | |
35 :- use_module(library(dcg_macros)). | |
36 :- use_module(library(fileutils)). | |
37 :- use_module(library(swipe)). | |
38 :- use_module(library(memo)). | |
39 :- use_module(library(rdfutils)). | |
40 :- use_module(library(httpfiles)). | |
41 :- use_module(library(dataset)). | |
42 :- use_module(library(insist)). | |
43 :- use_module(library(lambda)). | |
44 :- use_module(library(dcg/basics), [string_without//2, integer//1]). | |
45 :- use_module(library(solution_sequences)). | |
46 | |
47 :- set_prolog_flag(double_quotes,codes). | |
48 :- set_prolog_flag(back_quotes,string). | |
49 | |
50 http:location(v2,api(v2),[]). | |
51 | |
52 :- http_handler(v2(dataset), list_datasets, []). | |
53 :- http_handler(v2(dataset/define), define_dataset, []). | |
54 :- http_handler(v2(view/dataset/index), dataset_views, []). | |
55 :- http_handler(v2(view/dataset/items), dataset_items, []). | |
56 :- http_handler(v2(view/dataset/summary), dataset_summary, []). | |
57 :- http_handler(v2(view/recording/index), recording_views, []). | |
58 :- http_handler(v2(view/recording/properties), recording_properties, []). | |
59 | |
60 :- initialization | |
61 current_thread_pool(dmlvis), !; | |
62 thread_pool_create(vis, 8, [backlog(100)]). | |
63 | |
64 % ------------------------------------------------------------------------------------ | |
65 % Handlers with documentation | |
66 | |
67 %% list_datasets(+Request) is det. | |
68 % Lists previously defined datsets and the Prolog queries that define them. | |
69 list_datasets(R) :- vis(list_datasets,R). | |
70 | |
71 %% define_dataset(+Request) is det. | |
72 % Define a dataset satisfying given search terms. Result is a dataset | |
73 % ID, which may be the same as a previously defined dataset if it consists | |
74 % of the same items. | |
75 define_dataset(R) :- vis(define_dataset,R). | |
76 | |
77 %% dataset_views(+Request) is det. | |
78 % Lists available views for datasets. | |
79 dataset_views(R) :- vis(list_views(dataset),R). | |
80 | |
81 %% dataset_items(+Request) is det. | |
82 % Lists items in a given dataset specified by its ID.. | |
83 dataset_items(R) :- vis(dataset_items,R). | |
84 | |
85 %% dataset_summary(+Request) is det. | |
86 % Returns some summary information about a dataset. | |
87 dataset_summary(R) :- vis(dataset_summary,R). | |
88 | |
89 %% recording_views(+Request) is det. | |
90 % Lists available views for recordings. | |
91 recording_views(R) :- vis(list_views(recording),R). | |
92 | |
93 %% recording_properties(+Request) is det. | |
94 % Returns all the properties currently held in the RDF graph about a given recording. | |
95 recording_properties(R) :- vis(recording_properties,R). | |
96 | |
97 | |
98 % ------------------------------------------------------------------------------------ | |
99 | |
100 %% vis(+Method,+Request) is det. | |
101 % | |
102 % Top level predicate for implementing VIS API. Handles common tasks | |
103 % like determining the reply format, handling errors, and formatting the reply. | |
104 vis(Method,Request) :- | |
105 method_params_goal(Method,Params,Goal), | |
106 vis(Params,Goal,Request). | |
107 | |
108 vis(Params,Goal,Request) :- | |
109 http_parameters(Request, [format(Format), callback(Callback) | Params], | |
110 [attribute_declarations(param)]), | |
111 (Format=jsonp -> Fmt=jsonp(Callback); Fmt=json), | |
112 member(request_uri(Query),Request), | |
113 catch( insist(call(Goal,Result,Status)), | |
114 Ex, (error_result(Ex,Result), Status=error)), | |
115 result_response(Fmt,Query,Result,Status,Response), | |
116 write(Response). | |
117 | |
118 result_response(Fmt,Q,Result,Status,Response) :- | |
119 with_output_to(string(Response), | |
120 reply_as(Fmt,Status,_{ query:Q, result: Result})). | |
121 | |
122 reply_as(json,Status,Dict) :- | |
123 write_headers([Status,type(json)]), | |
124 json_write_dict(current_output, Dict). | |
125 reply_as(jsonp(Cb),Status,Dict) :- | |
126 write_headers([Status,type(jsonp)]), | |
127 write(Cb), write('('), | |
128 json_write_dict(current_output, Dict), | |
129 write(');'). | |
130 | |
131 | |
132 error_result(dml_error(Code,Descriptor),_{ code: Code, desc:Desc }) :- !, | |
133 format(string(Desc),'ERROR: ~w',[Descriptor]). | |
134 | |
135 error_result(Ex, _{ code: 500, desc: Msg }) :- | |
136 message_to_string(Ex,Msg). | |
137 | |
138 % ------------------------------------------------------------------------------------ | |
139 % Implementation of methods | |
140 | |
141 :- multifile param/2. | |
142 | |
143 % general | |
144 param( format, [oneof([json,jsonp]), default(jsonp), description('Reply format')]). | |
145 param( callback, [atom,default(jsonp_cb), description('Callback for jsonp reply')]). | |
146 | |
147 % define_dataset | |
148 param( library, [oneof([beets,charm,bl,ilm]), default(bl), description('Library to search within')]). | |
149 param( dv, [nonneg, optional(false), description('Database version ID')]). | |
150 param( genres, [atom, default(*), description('Semicolon separated list of genre names, or "*"')]). | |
151 param( years, [atom, default(*), description('Semicolon separeted list of release years or a range (Y1-Y2) or "*"')]). | |
152 param( composers, [atom, default(*), description('Semicolon separated list of composers or "*"')]). | |
153 param( performers,[atom, default(*), description('Semicolon separated list of performers or "*"')]). | |
154 | |
155 param( cid, [atom, optional(false), description('Collection ID')]). | |
156 param( cids, [atom, optional(false), description('Semicolon separated list of Collection IDs')]). | |
157 param( uri, [atom, optional(false), description('Recording URI')]). | |
158 param( limit, [integer, default(5000), description('Maximum number of things to return')]). | |
159 param( offset, [integer, default(0), description('Offset within list')]). | |
160 | |
161 method_params(listCollections, []). | |
162 method_params(listPerspectives, [method(_)]). | |
163 method_params(collection_id, [library(_),dv(_),genres(_),years(_),composers(_),performers(_)]). | |
164 method_params(Method, [ pid(_) | Params ]) :- | |
165 perspective(Method,_,_,_,_), | |
166 setof(P, perspective_param_name(Method,P), Ps), | |
167 maplist(param_name_term,Ps,Params). | |
168 | |
169 param_name_term(Name,Term) :- functor(Term,Name,1). | |
170 perspective_param_name(Method,Name) :- | |
171 perspective(Method,_,_,Specs,_), | |
172 member(S,Specs), | |
173 optspec_name(S,Name). | |
174 | |
175 | |
176 :- multifile perspective/5. | |
177 | |
178 method_result(listCollections, _, _{ collections:List }, unstable) :- | |
179 findall( _{ cid:Id, query:QA, dv:DV, size:SZ }, | |
180 ( browse(dataset:dataset(dmlvis:Q, DV, Id, SZ, _)), | |
181 term_to_atom(Q,QA) | |
182 ), | |
183 List). | |
184 method_result(Method,Opts,Result,stable) :- | |
185 method_result(Method,Opts,Result). | |
186 | |
187 | |
188 | |
189 method_result(listPerspectives, Opts, _{ perspectives:List }) :- | |
190 option(method(Method), Opts), | |
191 findall( P, perspective(Method,P,_,_,_), List). | |
192 | |
193 method_result(collection_id, Opts, _{ cid:Id, size:Size }) :- | |
194 option(dv(DBV),Opts), | |
195 option(library(Coll),Opts), | |
196 collection_query(Coll, Opts, Query), | |
197 dataset_query_id( Query, DBV, Id), | |
198 dataset_size(Id, Size). | |
199 | |
200 options_optspec(_,Opts,\O) :- option(O,Opts). | |
201 options_optspec(_,Opts,O-Def) :- option(O,Opts,Def). | |
202 options_optspec(M,Opts,O>Goal) :- options_optspec(M,Opts,O), call(M:Goal). | |
203 | |
204 optspec_name(\O,Name) :- functor(O,Name,1). | |
205 optspec_name(O-_,Name) :- functor(O,Name,1). | |
206 optspec_name(O>_,Name) :- optspec_name(O,Name). | |
207 | |
208 perspective(getRecordingPerspective, properties, dmlvis, [\uri(URI)], recording_info(URI)). | |
209 perspective(getCollectionPerspective, summary, dmlvis, [\cid(C)], collection_summary(C)). | |
210 perspective(getCollectionPerspective, list, dmlvis, [\cid(C),limit(Lim)-5000,offset(Off)-0], collection_list(C,Lim,Off)). | |
211 % perspective(getCollectionPairPerspective, summary, dmlvis, [\cids(A)>parse_atom(cids([C1,C2]),A)], binary(summary,C1,C2)). | |
212 % perspective(getMultiCollectionPerspective, summary, dmlvis, [\cids(A)>parse_atom(cids(Cs),A)], multi(summary,Cs)). | |
213 | |
214 collection_summary(Id,Result) :- | |
215 insist(browse(dataset:dataset(Goal,DV,Id,Size,_)), unknown_collection(Id)), | |
216 term_to_atom(Goal,GoalA), | |
217 Result = _{cid:Id, size:Size, goal:GoalA, dv:DV }. | |
218 | |
219 collection_list(Id, Lim, Offset, _{cid:Id, size:Size, items:Items}) :- | |
220 dataset_size(Id,Size), | |
221 findall(Item,limit(Lim,offset(Offset,dataset_item(Id,Item))),Items). | |
222 | |
223 % --------------- recording_properties ----------------------------- | |
224 | |
225 recording_info(URI, Result) :- | |
226 ( a(mo:'AudioFile',URI) -> G=audiofile_info(URI) | |
227 ; a(mo:'Track',URI) -> G=track_info(URI) | |
228 ; a(mo:'Signal',URI) -> G=signal_info(URI) | |
229 ; rdf(URI,charm:file_name,_) -> G=charm_info(URI) | |
230 ; throw(not_a_recording(URI)) | |
231 ), | |
232 insist(call(G,Result),failed(G)). | |
233 | |
234 audiofile_info(URI,Result) :- | |
235 rdf_text(URI,beets:title,Title), | |
236 rdf_text(URI,beets:album,AlbumName), | |
237 rdf_text(URI,beets:artist,ArtistName), | |
238 rdf_number(URI,beets:length,Duration), | |
239 Result = _{ type:audiofile, title:Title, artist:ArtistName, album:AlbumName, duration:Duration }. | |
240 | |
241 track_info(Track, Result) :- | |
242 rdf_number(Track,mo:duration,DurationMs), Duration is DurationMs/1000.0, | |
243 rdf_text(Track,dc:title,Title), | |
244 rdf(Record,mo:track,Track), | |
245 rdf(Release,mo:record,Record), | |
246 rdf_text(Release,dc:title,AlbumName), | |
247 rdf(Artist,foaf:made,Track), | |
248 rdf_text(Artist,foaf:name,ArtistName), | |
249 Result = _{ type:track, title:Title, artist:ArtistName, album:AlbumName, duration:Duration }. | |
250 | |
251 signal_info(Signal, _{type:signal, tracks:Infos}) :- | |
252 setof(T,rdf(T,mo:publication_of,Signal),Tracks), | |
253 maplist(track_info,Tracks,Infos). | |
254 | |
255 charm_info(URI, PropDict) :- | |
256 setof(Pred-Vals,setof(Val1,Val^(rdf(URI,Pred,literal(Val)),atomise_literal(Val,Val1)),Vals),Info), | |
257 dict_pairs(PropDict,_,Info). | |
258 | |
259 atomise_literal(type(_,Val),Val) :- !. | |
260 atomise_literal(lang(_,Val),Val) :- !. | |
261 atomise_literal(Val,Val). | |
262 | |
263 % -------------------- defining a dataset ------------------------------ | |
264 | |
265 qc(beets,Opts,X) :- maplist(filter(beets,X),Opts), a(mo:'AudioFile',X). | |
266 qc(charm,Opts,X) :- maplist(filter(charm,X),Opts), rdf(X,charm:file_name,_). | |
267 qc(bl,Opts,X) :- maplist(filter(bl,X),Opts), rdf(X,rdf:type,mo:'Signal',bl_p2r). | |
268 | |
269 filter(_,_,genres(*)) :- true. | |
270 filter(beets,X,genres(any(Gs))) :- member(G,Gs), rdf_has(X,beets:genre,literal(substring(G),_)). | |
271 | |
272 filter(_,_,years(*)) :- true. | |
273 filter(D,X,years(any(Ys))) :- member(Y,Ys), filter(D,X,years(Y-Y)). | |
274 filter(D,X,years(L-U)) :- succ(U,U1), atom_number(LA,L), atom_number(U1A,U1), filter(D,X,years(LA,U1A)). | |
275 filter(beets,X,years(L,U)) :- rdf(X, beets:original_year, literal(between(L,U),_)). | |
276 filter(charm,X,years(L,U)) :- rdf(X, charm:recording_date, literal(between(L,U),_)). | |
277 filter(bl,X,years(L,U)) :- rdf(X, dcterms:created, literal(between(L,U),_)). | |
278 | |
279 filter(_,_,composers(*)) :- true. | |
280 filter(D,X,composers(any(List))) :- member(C,List), filter(D,X,composer(C)). | |
281 filter(charm,X,composer(C)) :- rdf(X, charm:composer, literal(prefix(C),_)). | |
282 filter(bl,X,composer(C)) :- rdf(X, marcrel:cmp, literal(prefix(C),_)). | |
283 filter(_,_,performers(*)) :- true. | |
284 filter(D,X,performers(any(List))) :- member(C,List), filter(D,X,performer(C)). | |
285 filter(charm,X,performer(C)) :- rdf(X, charm:performer, literal(prefix(C),_)). | |
286 filter(bl,X,performer(C)) :- rdf(X, marcrel:prf, literal(prefix(C),_)). | |
287 filter(beets,X,performer(C)) :- rdf(X, beets:artist, literal(prefix(C),_)). | |
288 filter(charm,X,title(C)) :- rdf(X, charm:title, literal(substring(C),_)). | |
289 filter(bl,X,title(C)) :- rdf(X, dc:title, literal(substring(C),_)). | |
290 filter(beets,X,title(C)) :- rdf(X, beets:title, literal(like(C),_)). | |
291 | |
292 | |
293 collection_query(Coll, Opts, qc(Coll,Filters)) :- | |
294 seqmap(process_qopt(Opts), | |
295 [ qo( genres(GA), genres(GS), genres(*), parse_atom(atoms(GS), GA)) | |
296 , qo( composers(CA), composers(CS), composers(*), parse_atom(atoms(CS), CA)) | |
297 , qo( performers(PA), performers(PS), performers(*), parse_atom(atoms(PS), PA)) | |
298 , qo( years(YA), years(YS), years(*), parse_atom(years(YS), YA)) | |
299 , qo( title(T), title(T), title(*), true) | |
300 ], | |
301 Filters, []). | |
302 | |
303 process_qopt(Opts,qo(Opt,Filter,NullFilter,Goal)) --> | |
304 {option(Opt,Opts,'*'), call(Goal)}, | |
305 ({Filter=NullFilter} -> []; [Filter]). | |
306 | |
307 | |
308 % --------- parsers ----------- | |
309 | |
310 % cids(Ids) --> seqmap_with_sep(",",alphanum,Ids). | |
311 cids(Ids) --> semicolon_sep(atom_codes,Ids). | |
312 | |
313 atoms('*') --> "*", !. | |
314 atoms(any(AS)) --> semicolon_sep(atom_codes,AS). | |
315 | |
316 years('*') --> "*", !. | |
317 years(L-U) --> integer(L), "-", integer(U). | |
318 years(any(Ys)) --> semicolon_sep(number_codes,Ys). | |
319 | |
320 | |
321 | |
322 % alphanum(X) --> string_without(",",S), {atom_string(X,S)}. | |
323 | |
324 item(Conv,Item) --> string_without(";",Codes), {call(Conv,Item,Codes)}. | |
325 semicolon_sep(Conv,Items) --> | |
326 seqmap_with_sep(";",item(Conv),Items). | |
327 | |
328 | |
329 parse_atom(Phrase,Atom) :- | |
330 atom_codes(Atom,Codes), | |
331 debug(vis,'Attempting to parse ~q with ~q...',[Atom,Phrase]), | |
332 insist( phrase(Phrase,Codes), parse_failure(Phrase)), | |
333 debug(vis,'...got ~q',[Phrase]). | |
334 |