Mercurial > hg > dml-open-cliopatria
comparison cpack/dml/api/dmlvis.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(dmlvis, | |
20 [ cc/3 | |
21 , recording_property/3 | |
22 ]). | |
23 | |
24 /** <module> DML Visualisation web service | |
25 */ | |
26 | |
27 | |
28 :- use_module(library(http/html_write)). | |
29 :- use_module(library(http/html_head)). | |
30 :- use_module(library(http/thread_httpd)). | |
31 :- use_module(library(http/http_dispatch)). | |
32 :- use_module(library(http/http_parameters)). | |
33 :- use_module(library(http/http_json)). | |
34 :- use_module(library(http/json)). | |
35 :- use_module(library(thread_pool)). | |
36 :- use_module(library(semweb/rdf_label)). | |
37 :- use_module(library(sandbox)). | |
38 :- use_module(library(dcg_core)). | |
39 :- use_module(library(dcg_pair)). | |
40 :- use_module(library(dcg_codes)). | |
41 :- use_module(library(dcg_macros)). | |
42 :- use_module(library(fileutils)). | |
43 :- use_module(library(listutils)). | |
44 :- use_module(library(optutils)). | |
45 :- use_module(library(swipe)). | |
46 :- use_module(library(memo)). | |
47 :- use_module(library(rdfutils)). | |
48 :- use_module(library(httpfiles)). | |
49 :- use_module(library(dataset)). | |
50 :- use_module(library(computations), [rows_cols/3]). | |
51 :- use_module(library(csvutils), [uri_to_csv/2]). | |
52 :- use_module(library(insist)). | |
53 :- use_module(library(lambda)). | |
54 :- use_module(library(dcg/basics), [string_without//2, integer//1]). | |
55 :- use_module(library(solution_sequences)). | |
56 | |
57 :- use_module(components(audio)). | |
58 | |
59 :- meta_predicate cc(2,2,1). | |
60 :- meta_predicate method_result_cc(+,+,2,1). | |
61 | |
62 :- set_prolog_flag(double_quotes,codes). | |
63 :- set_prolog_flag(back_quotes,string). | |
64 | |
65 http:location(v1,root(api/v4),[]). | |
66 | |
67 :- http_handler(v1(getCollectionId), getCollectionId, []). | |
68 :- http_handler(v1(getCollectionPerspective), getCollectionPerspective, []). | |
69 :- http_handler(v1(getRecordingPerspective), getRecordingPerspective, [spawn(vis_recording)]). | |
70 :- http_handler(v1(listCollections), listCollections, []). | |
71 :- http_handler(v1(listPlaces), listPlaces, []). | |
72 :- http_handler(v1(listPerspectives), listPerspectives, []). | |
73 :- http_handler(v1(csv_time_window), csv_time_window, []). | |
74 | |
75 % ------------------------------------------------------------------------------------ | |
76 | |
77 %% vis(+Method,+Request) is det. | |
78 % | |
79 % General VIS API HTTP handler. Returns either JSON or JSONP depending on the | |
80 % format parameter. If JSONP is selected (the default), the callback parameter | |
81 % determines the Javascript callback function. The JSON result structure is of | |
82 % type | |
83 % == | |
84 % { | |
85 % query: string ~'The original query, excluding protocol and host', | |
86 % result: (error_struct|A) ~'Result structure A or error information' | |
87 % } | |
88 % == | |
89 % where | |
90 % == | |
91 % error_struct == { code: integer, decs:string } | |
92 % == | |
93 % See individual methods for more information about their return types. | |
94 vis(Method,Request) :- | |
95 get_time(T0), | |
96 method_params(Method,Params), | |
97 member(request_uri(Query),Request), | |
98 vis_parameters(Request, [format(Format), callback(Callback) | Params],ROpts), | |
99 (Format=jsonp -> Fmt=jsonp(Callback,ROpts); Fmt=json(ROpts)), | |
100 Responder=send_response(Fmt,Query,T0), | |
101 debug(dmlvis(method),'~q',[method_result_cc(Method,Params,Responder,writeln)]), | |
102 method_result_cc(Method,Params,dmlvis:Responder,error_cont(Query,Responder)). | |
103 | |
104 send_response(Fmt,Query,T0,Result,Status) :- | |
105 get_time(T1), DT=T1-T0, | |
106 debug(dmlvis(response),'Sending response after ~3f s to ~q',[DT,Query]), | |
107 once(reply_as(Fmt,Status,_{ query:Query, result: Result})). | |
108 | |
109 error_cont(Q,Cont,Ex) :- | |
110 debug(dmlvis(error),'Sending error ~W in response to ~q',[Ex,[quoted(true),max_depth(8)],Q]), | |
111 error_result(Ex,Result), | |
112 call(Cont,Result,error). | |
113 | |
114 vis_parameters(Request,Params,ReplyOpts) :- | |
115 Params1=[random(_, [optional(true)]) | Params], | |
116 http_parameters(Request, Params1, [attribute_declarations(param), form_data(AllParams)]), | |
117 findall(N, (member(N=_,AllParams), \+used_param(N,Params1)), Unused), | |
118 (select(indent,Unused,Unused1) -> ReplyOpts=[]; ReplyOpts=[width(0)], Unused1=Unused), | |
119 (select(dv,Unused1,Unused2) -> true; Unused2=Unused1), | |
120 insist(Unused2=[], unrecognised_parameters(Unused2)). | |
121 | |
122 used_param(N,ValidParams) :- | |
123 member(Q,ValidParams), | |
124 functor(Q,N,_). | |
125 | |
126 % result_response(Fmt,Q,Result,Status,Response) :- | |
127 % with_output_to(string(Response), | |
128 % reply_as(Fmt,Status,_{ query:Q, result: Result})). | |
129 | |
130 reply_as(json(Opts),Status,Dict) :- !, | |
131 write_headers([Status,type(json)]), | |
132 json_write_dict(current_output, Dict, Opts). | |
133 reply_as(jsonp(Cb,Opts),Status,Dict) :- !, | |
134 write_headers([Status,type(jsonp)]), | |
135 write(Cb), write('('), | |
136 json_write_dict(current_output, Dict, Opts), | |
137 write(');'). | |
138 | |
139 | |
140 error_result(Ex, _{ errors:[Err] }) :- error_result1(Ex,Err). | |
141 | |
142 error_result1(dml_error(Code,Descriptor),_{ code: Code, desc:Descriptor }) :- !. | |
143 | |
144 error_result1(Ex, _{ code: 500, desc: Msg }) :- | |
145 message_to_string(Ex,Msg). | |
146 | |
147 % ------------------------------------------------------------------------------------ | |
148 % Handlers with documentation | |
149 | |
150 %% getCollectionId(+Request) is det. | |
151 % | |
152 % Define a collection satisfying given search terms. Result is a collection | |
153 % ID, which may be the same as a previously defined collection if it consists | |
154 % of the same items. | |
155 % | |
156 % Parameters are as follows. In all cases, =|sclist(Type)|= denotes a semicolon | |
157 % separated list of values of given type OR the string '*', which is the default. | |
158 % The value '*' means that no filtering is done on the releveant property. The | |
159 % list is interpreted as an AND-list or an OR-list depending on which property | |
160 % is being tested. String matching is case insensitive. | |
161 % The only required parameter is =|dv|=. | |
162 % == | |
163 % dv : integer ~ database version | |
164 % library : sclist(lib_name) ~ OR-list of libraries to search | |
165 % collection : sclist(pattern) ~ OR-list of BL collection name patterns | |
166 % composer : sclist(string) ~ OR-list of composer prefixes | |
167 % performer : sclist(string) ~ OR-list of performer prefixes | |
168 % title : sclist(string) ~ AND-list of title substrings | |
169 % genre : sclist(string) ~ OR-list of genre substrings | |
170 % place : sclist(string) ~ OR-list of place substrings | |
171 % language : sclist(string) ~ OR-list of langauage name prefixes | |
172 % year : sclist(year) | range ~ OR-list of genre substrings | |
173 % sample : nonneg | 'all' ~ sample a random subset of this size | |
174 % sv : integer ~ sample version for sample | |
175 % | |
176 % lib_name --> 'bl' | 'charm' | 'ilm' | 'mazurka' | 'beets'. | |
177 % range --> year, '-', year. | |
178 % == | |
179 % NB. A =|pattern|= is a string which may contain '*' to match any sequence of | |
180 % characters. The pattern must match the WHOLE value being tested, eg to search | |
181 % for the substring 'Botswana', you must include '*' at both ends of the pattern, | |
182 % eg =|'*botswana*'|=. | |
183 % | |
184 % A successful result is of type | |
185 % == | |
186 % result(getCollectionId) == { | |
187 % cid: string ~'collection id', | |
188 % size: natural ~'number of items in collection' | |
189 % }. | |
190 % == | |
191 getCollectionId(R) :- vis(getCollectionId,R). | |
192 | |
193 %% getCollectionPerspective(+Request) is det. | |
194 % | |
195 % Get a given perspective on a previously defined collection. | |
196 % Result will depend on the particular perspective chosen. | |
197 % All perspectives require the parameter =|cid(string)|=. Most | |
198 % perspectives accept the parameters =|recompute(oneof([none,failed,force]))|= | |
199 % and =|vamp_on_demand(boolean)|=. | |
200 % Defined perspectives are | |
201 % | |
202 % == | |
203 % summary : [] -> { cid:string, size: natural, goal: string }. | |
204 % | |
205 % list : | |
206 % [ limit(natural)/5000, offset(natural)/0, sort_by(oneof([label, date]))/label ] | |
207 % -> { cid:string, items: list( {uri:uri, label:string, audio:list(link(audio)), date:string }) }. | |
208 % | |
209 % midi_pitch_histogram : | |
210 % [ weighting(oneof([none,dur,vel]))/none ] | |
211 % -> { values:list(integer), counts:list(natural) }. | |
212 % | |
213 % pitch_histogram : | |
214 % [ weighting(oneof([none,dur,vel]))/none, quant(natural)/5, min(integer)/20, max(integer)/100, lang(oneof([ml,r]))/ml ] | |
215 % -> { edges:list(nonneg), counts:list(natural) }. | |
216 % | |
217 % tempo_histogram : | |
218 % [ period(nonneg)/1, min(integer)/20, max(integer)/100, num_bins(natural)/50, lang(oneof([ml,r]))/ml ] | |
219 % -> { edges:list(nonneg), counts:list(natural) }. | |
220 % | |
221 % mean_tempo_curve : | |
222 % [ num_samples(natural)/20, lang(oneof([ml,r]))/ml ] | |
223 % -> { means:list(nonneg), std_devs:list(nonneg) }. | |
224 % | |
225 % tonic_relative_pitch_class_histogram : [] | |
226 % -> { values:list(string), counts:list(nonneg), ok_count:natural, failed:{prolog:list, python:list}}. | |
227 % | |
228 % pitch_lookup : | |
229 % [ midi_pitch(between(0,127)), weighting(oneof([none,dur,vel]))/none, | |
230 % limit(natural)/5000, offset(natural)/0 ] | |
231 % -> { }. | |
232 % | |
233 % tonic_histogram : [] -> { }. | |
234 % | |
235 % pitch_class_histogram : [] -> { }. | |
236 % | |
237 % tuning_stats : [] -> { }. | |
238 % | |
239 % tuning_stats_by_year : [] -> { }. | |
240 % | |
241 % places_hist : [] -> { }. | |
242 % | |
243 % key_relative_chord_seq : | |
244 % [ spm_minlen(natural)/2, spm_maxseqs(natural)/500, spm_algorithm(Alg)/'CM-SPADE', | |
245 % spm_ignore_n(natural)/1, spm_maxtime(number)/60, spm_minsupport(number)/50 ] | |
246 % -> { }. | |
247 % | |
248 % similarity : | |
249 % [ sim_downsample(number)/1,sim_clusters(number)/40,sim_reclimit(number)/2000, | |
250 % sim_type(string)/'euclidean',sim_features(string)/'chromagram', | |
251 % sim_compressor(string)/'zlib'] | |
252 % -> { }. | |
253 % == | |
254 getCollectionPerspective(R) :- vis(getCollectionPerspective,R). | |
255 | |
256 %% getCollectionPairPerspective(+Request) is det. | |
257 % | |
258 % Get a given comparative perspective on a pair of previously defined collections. | |
259 % Result will depend on the particular perspective chosen. Defined perspectives are: | |
260 getCollectionPairPerspective(R) :- vis(getCollectionPairPerspective,R). | |
261 | |
262 %% getMultiCollectionPerspective(+Request) is det. | |
263 % Get a given comparative perspective on a set of previously defined collections. | |
264 getMultiCollectionPerspective(R) :- vis(getMultiCollectionPerspective,R). | |
265 | |
266 %% getRecordingPerspective(+Request) is det. | |
267 % Get a given perspective for a given recording URI. Perspectives, their parameters and | |
268 % their output types are as follows (all perspectives require a uri parameter) | |
269 % == | |
270 % properties : [] -> { | |
271 % library:string, | |
272 % title:string, | |
273 % composer:list(string), | |
274 % performer:list(string), | |
275 % genre:list(string), | |
276 % place:string, | |
277 % language:string, | |
278 % recording_date:string | |
279 % }. | |
280 % | |
281 % transcription : [] -> { csv: uri(csv([time,dur,freq,vel,pitch_name])) }. | |
282 % transcription_fine : [] -> { csv: uri(csv([time,dur,freq,vel,pitch_name)) }. | |
283 % chords : [] -> { csv: uri(csv([time,chord_name])) }. | |
284 % chords_notes : [] -> { csv: uri(csv([time,dur,integer)) }. | |
285 % key : [] -> { csv: uri(csv([time,integer,string])) }. | |
286 % key_tonic : [] -> { csv: uri(csv) }. | |
287 % tempo : [] -> { csv: uri(csv([time,nonneg,tempo_string])). | |
288 % beats : [] -> { csv: uri(csv([time,tempo_string])) }. | |
289 % beatroot : [] -> { csv: uri(csv([time])) }. | |
290 % | |
291 % tempo_nonuniform : [] -> { times:list(float), values:list(float) }. | |
292 % tempo_uniform : [ lang(oneof([ml,r]))/ml ] -> { times:list(float), values:list(float) }. | |
293 % tempo_normalised : [ lang(oneof([ml,r]))/ml ] -> { times:list(float), values:list(float) }. | |
294 % tempo_histogram : | |
295 % [ period(nonneg)/1, num_bins(natural)/50, min(nonneg)/20, max(nonneg)/100, lang(oneof([ml,r]))/ml ] | |
296 % -> { edges: list(float), counts: list(natural) }. | |
297 % | |
298 % midi_pitch_histogram : | |
299 % [ weighting(note_weight)/none ] | |
300 % -> { values: list(integer), counts: list(natural) }. | |
301 % | |
302 % pitch_histogram : | |
303 % [weighting(note_weight)/none, quant(natural)/5, min(integer)/20, max(integer)/100, lang(oneof([ml,r]))/ml ] | |
304 % -> { edges: list(float), counts: list(natural) }. | |
305 % | |
306 % chord_histogram : [] -> { values:list(string), counts:list(natural) }. | |
307 % | |
308 % spectrogram : [offset(nonneg)/0, length(nonneg)/60 ] -> { csv: uri }. | |
309 % == | |
310 % | |
311 % Supplementary types: | |
312 % == | |
313 % note_weight --> 'none'; 'dur'; 'vel'; 'dur*vel'. | |
314 % | |
315 % time == float. | |
316 % dur == nonneg. | |
317 % freq == nonneg. | |
318 % vel == nonneg. | |
319 % == | |
320 getRecordingPerspective(R) :- vis(getRecordingPerspective,R). | |
321 | |
322 %% listCollections(+Request) is det. | |
323 % Lists previously defined collections and the Prolog queries that define them. | |
324 % == | |
325 % listCollections : [] -> { | |
326 % collections: list({ cid : string, | |
327 % query : string, | |
328 % dv : integer, | |
329 % size : natural, | |
330 % timestamp : string | |
331 % }) | |
332 % }. | |
333 listCollections(R) :- vis(listCollections,R). | |
334 | |
335 %% listPlaces(+Request) is det. | |
336 % Lists known place names, currently the distinct values of the dcterms:spatial predicate. | |
337 % == | |
338 % listPlaces : [] -> { | |
339 % places: list({ name : string | |
340 % }) | |
341 % }. | |
342 listPlaces(R) :- vis(listPlaces,R). | |
343 | |
344 %% listPerspectives(+Request) is det. | |
345 % Lists available perspective for a given method. | |
346 listPerspectives(R) :- vis(listPerspectives,R). | |
347 | |
348 %% csv_time_window(+Request) is det. | |
349 % | |
350 % Returns the contents of a CSV file between between given time limits, | |
351 % assuming the the first column is a time value. | |
352 % Also returns the time of the last row. Parameters and return structure are | |
353 % == | |
354 % csv_time_window : | |
355 % [uri(uri(csv)), start(float), end(float) ] | |
356 % -> { duration:float, columns: list(list) }. | |
357 % == | |
358 % URI parameter must be the URI of a CSV file. | |
359 % Data is returned a list of lists, where each inner list is one column | |
360 % of the CSV. | |
361 csv_time_window(R) :- vis(csv_time_window,R). | |
362 | |
363 | |
364 % ------------------------------------------------------------------------------------ | |
365 % Implementation of methods | |
366 | |
367 :- multifile param/2. | |
368 | |
369 param( format, [oneof([json,jsonp]), default(jsonp), description('Reply format')]). | |
370 param( callback, [atom,default(jsonp_cb), description('Callback for jsonp reply')]). | |
371 param( dv, [nonneg, optional(false), description('Database version ID')]). | |
372 | |
373 param( cid, [atom, optional(false), description('Collection ID')]). | |
374 param( pid, [atom, optional(false), description('Perspective ID')]). | |
375 param( cids, [atom, optional(false), description('Semicolon separated list of Collection IDs')]). | |
376 param( uri, [atom, optional(false), description('Item URI')]). | |
377 param( library, [atom, default(*), description('Semicolon separated list of libraries to search')]). | |
378 param( genre, [atom, default(*), description('Semicolon separated list of genre names, or "*"')]). | |
379 param( year, [atom, default(*), description('Semicolon separeted list of release years or a range (Y1-Y2) or "*"')]). | |
380 param( composer, [atom, default(*), description('Semicolon separated list of composers or "*"')]). | |
381 param( performer, [atom, default(*), description('Semicolon separated list of performers or "*"')]). | |
382 param( place, [atom, default(*), description('Semicolon separated list of place names or "*"')]). | |
383 param( language, [atom, default(*), description('Semicolon separated list of language name prefixes or "*"')]). | |
384 param( collection,[atom, default(*), description('Semicolon separated list of BL collection names or "*"')]). | |
385 param( title, [atom, default(*), description('Semicolon separated AND-list of title substrings or "*"')]). | |
386 param( method, [atom, optional(false), description('API method name')]). | |
387 param( limit, [integer, default(5000), description('Maximum number of things to return')]). | |
388 param( offset, [integer, default(0), description('Offset within list')]). | |
389 param( sort_by, [oneof([label,date]), default(label), description('Sort recordings list by this property')]). | |
390 param( start, [number, optional(false), description('Start of window in seconds')]). | |
391 param( end, [number, optional(false), description('End of window in seconds')]). | |
392 param( sample, [number, default(all), description('Sample a random subset of this size')]). | |
393 param( sv, [number, default(1), description('Version of random subset')]). | |
394 param( midi_pitch,[nonneg, default(60), description('MIDI note number 0..127')]). | |
395 | |
396 method_params(listCollections, []). | |
397 method_params(listPlaces, []). | |
398 method_params(listPerspectives, [ method(_) ]). | |
399 method_params(getCollectionId, [ dv(_), library(_), genre(_), place(_), language(_), year(_), composer(_), | |
400 performer(_), collection(_), title(_), sample(_), sv(_) ]). | |
401 method_params(csv_time_window, [ uri(_), start(_), end(_) ]). | |
402 method_params(Method, [ pid(_) | Params ]) :- | |
403 once(perspective(Method,_)), | |
404 setof(P, perspective_param_name(Method,P), Ps), | |
405 maplist(param_name_term,Ps,Params). | |
406 | |
407 param_name_term(Name,Term) :- functor(Term,Name,1). | |
408 perspective_param_name(Method,Name) :- | |
409 perspective(Method,_,Specs,_), | |
410 member(S,Specs), | |
411 optspec_name(S,Name). | |
412 | |
413 | |
414 :- multifile perspective/4. | |
415 | |
416 %% cc(+Pred:pred(-A,-cc_status), +Cont:pred(+A,+cc_status), +ErrorCont:pred(+exception)) is det. | |
417 % Call a predicate with success and error continuations. | |
418 % Pred roduces a result of type A and a status. If it succeeds, the result and status are passed | |
419 % to the continuation Cont. Otherwise, an exception is passed to ErrorCont. | |
420 cc(Goal,Cont,ErrorCont) :- catch(cc_wrapper(Goal,Cont), Ex, call(ErrorCont,Ex)). | |
421 cc_wrapper(Goal,Cont) :- insist(call(Goal,Result,Status)), call(Cont,Result,Status). | |
422 | |
423 place_name(P) :- rdf(_,dcterms:spatial,literal(P)). | |
424 | |
425 %% method_result_cc(+Method,+Params:options,+C:success_cont,+E:error_cont) is det. | |
426 % | |
427 % Perspectives are handle using continuations to allow spawning | |
428 % == | |
429 % success_cont == pred(+dict,+vis_status). | |
430 % error_cont == pred(+exception). | |
431 % vis_status ---> stable; unstable. | |
432 % == | |
433 % Method must be a method id registered in perspective/2 or handled my method_resut/4. | |
434 method_result_cc(Method,Params,Cont,ErrorCont) :- | |
435 perspective(Method,_), !, | |
436 option(pid(PId),Params), | |
437 catch(( insist( perspective(Method,PId,Specs,Pred), unknown_perspective(PId)), | |
438 insist( maplist(options_optspec(Params),Specs)), | |
439 call(Pred,Cont,ErrorCont) | |
440 ), Ex, call(ErrorCont,Ex)). | |
441 | |
442 % all non-perspective methods are handled in this thread | |
443 method_result_cc(Method,Params,Cont,ErrorCont) :- | |
444 cc( method_result(Method,Params), Cont, ErrorCont). | |
445 | |
446 %% method_result(+Method, +Opts, -Result, -Status:vis_status) is det. | |
447 % | |
448 % Handles methods =|listCollections, listPerspectives, getCollectionId, csv_time_window|=. | |
449 method_result(listCollections, _, _{ collections:List }, unstable) :- | |
450 findall( _{ cid:Id, query:QA, dv:DV, size:SZ, timestamp:TS }, | |
451 ( browse(dataset:dataset(dmlvis:Q, DV, Id, SZ, _),comp(_,Timestamp,_)-ok), | |
452 format_time(string(TS),'%FT%T%:z',Timestamp), | |
453 term_to_atom(Q,QA) | |
454 ), | |
455 List). | |
456 | |
457 method_result(listPlaces, _, _{ places:List }, unstable) :- | |
458 findall( _{ name:Name, count:N }, aggregate(count,place_name(Name),N), List). | |
459 | |
460 | |
461 method_result(listPerspectives, Opts, _{ perspectives:List }, stable) :- | |
462 option(method(Method), Opts), | |
463 findall( P, perspective(Method,P), List). | |
464 | |
465 method_result(getCollectionId, Opts, _{ cid:Id, size:Size, full_size:FullSize }, stable) :- | |
466 build_dataset_query(Query,DBV,Size-FullSize,Opts,Remaining), | |
467 insist(Remaining=[], unrecognised_search_criteria(Remaining)), | |
468 insist(dataset_query_id( Query, DBV, Id),empty_dataset(Query)), | |
469 dataset_size(Id, Size). | |
470 | |
471 method_result(csv_time_window, Opts, _{ duration:Dur, columns:Columns }, stable) :- | |
472 maplist(options_optspec(Opts), [ \uri(URI), \start(Start), \end(End) ]), | |
473 uri_to_csv(URI,Rows), | |
474 insist(Rows\=[], empty_csv(URI)), | |
475 | |
476 append(_,[EndRow],Rows), | |
477 functor(EndRow,_,NumCols), | |
478 arg(1,EndRow,Dur), | |
479 | |
480 numlist(1,NumCols,Is), | |
481 drop_while(row_before(Start),Rows,Rows1), | |
482 take_while(row_before(End),Rows1,Rows2), | |
483 rows_cols(Is,Rows2,Columns). | |
484 | |
485 row_before(T0,Row) :- arg(1,Row,T), T<T0. | |
486 | |
487 options_optspec(Opts,+O) :- option(O,Opts). | |
488 options_optspec(Opts,O-Def) :- option(O,Opts,Def). | |
489 % options_optspec(M,Opts,O>Goal) :- options_optspec(M,Opts,O), call(M:Goal). | |
490 | |
491 optspec_name(+O,Name) :- functor(O,Name,1). | |
492 optspec_name(O-_,Name) :- functor(O,Name,1). | |
493 % optspec_name(O>_,Name) :- optspec_name(O,Name). | |
494 | |
495 perspective(Method,Perspective) :- perspective(Method,Perspective,_,_). | |
496 | |
497 perspective(getRecordingPerspective, properties, [+uri(URI)], cc(recording_info(URI))). | |
498 perspective(getCollectionPerspective, summary, [+cid(C)], cc(collection_summary(C))). | |
499 perspective(getCollectionPerspective, list, [+cid(C),limit(Lim)-5000,offset(Off)-0,sort_by(SortBy)-label], cc(collection_list(C,Lim,Off,SortBy))). | |
500 | |
501 collection_summary(Id,Result,stable) :- | |
502 insist(dataset_size(Id,Size), unknown_collection(Id)), | |
503 findall( _{goal:GoalA, dv:DV}, ( dataset_query_dv(Id,Goal,DV), | |
504 term_to_atom(Goal,GoalA) ), Queries), | |
505 Result = _{cid:Id, size:Size, queries:Queries }. | |
506 | |
507 | |
508 collection_list(Id, Lim, Offset, SortBy, _{cid:Id, size:Size, items:Items}, stable) :- | |
509 insist(dataset_size(Id,Size), unknown_collection(Id)), | |
510 findall(SortVal-Item, dataset_itemx(SortBy,Id,Item,SortVal), KeyedItems), sort(KeyedItems,Sorted), | |
511 findall(Item,limit(Lim,offset(Offset,member(_-Item,Sorted))),Items). | |
512 | |
513 dataset_itemx(SortProp, Id, Itemx, SortVal) :- | |
514 dataset_item(Id,URI), | |
515 filter(Lib,URI,in_library), | |
516 findall(Prop:Val, ( member(Prop,[label,audio,date]), | |
517 recording_property(URI,Lib,Prop,Val) ), Props), | |
518 (member(SortProp:Val,Props) -> SortVal=just(Val); SortVal=nothing), | |
519 dict_create(Itemx,_,[uri:URI | Props]). | |
520 | |
521 | |
522 recording_info(URI, Result, stable) :- | |
523 insist(filter(Lib,URI,in_library),unknown_recording(URI)), | |
524 findall(Prop:Val, recording_property(URI,Lib,Prop,Val), Props), | |
525 dict_create(Result,_,[ library:Lib | Props ]). | |
526 | |
527 recording_property(URI,Prop,Val) :- | |
528 filter(Lib,URI,in_library), | |
529 recording_property(URI,Lib,Prop,Val). | |
530 | |
531 recording_property(URI,_,label,Label) :- | |
532 rdf_display_label(URI,Label). | |
533 recording_property(URI,_,audio,Links) :- | |
534 % !!! HACK: force scraping for BL items here.. | |
535 % DISABLED - seems to upset BL server... | |
536 % (rdf(URI,dml:blpage,_) -> once(bl_p2r:scrape_audio_link(URI,_)); true), | |
537 setof(L,F^audio_link(URI,L,F),Links). | |
538 recording_property(URI,Lib,Prop,Val) :- | |
539 lib_property_read(Lib, Prop, Reader), | |
540 pred_values(URI,Lib:Prop,Reader,Val). | |
541 | |
542 | |
543 pred_values(URI,Lib:Prop,-Converter,Val) :- | |
544 lib_property(Lib,Prop,Pred), | |
545 once(rdf(URI,Pred,Obj)), | |
546 call(Converter,Obj,Val). | |
547 pred_values(URI,LibProp,+Converter,Vals) :- | |
548 findall(Val, pred_values(URI,LibProp,-Converter,Val), Vals). | |
549 | |
550 lib_property_read(_, collection, -literal_text). | |
551 lib_property_read(_, composer, +literal_text). | |
552 lib_property_read(_, performer, +literal_text). | |
553 lib_property_read(_, title, -literal_text). | |
554 lib_property_read(_, date, -literal_text). | |
555 lib_property_read(_, place, -literal_text). | |
556 lib_property_read(_, language, +literal_text). | |
557 lib_property_read(ilm, genre, +genre_label). | |
558 | |
559 genre_label(Genre,Label) :- | |
560 rdf(Genre,rdfs:label,Lit), | |
561 literal_text(Lit,Label). | |
562 | |
563 % ------------------- DEFINING NEW COLLECTIONS ----------------------- | |
564 | |
565 build_dataset_query(Query,DBV,Size-FullSize) --> | |
566 select_option(dv(DBV)), | |
567 select_option(sample(Subset)), | |
568 select_option(sv(SV)), | |
569 full_query(FQ), | |
570 { Subset=all -> Query=FQ, Size=FullSize | |
571 ; Query=sample(Subset,SV,FQ), | |
572 aggregate_all(count,call(FQ,_),FullSize) | |
573 }. | |
574 | |
575 full_query(qc(Filters)) --> | |
576 run_left(seqmap(process_qopt, | |
577 [ qo( library, atoms(LS), libraries(LS)) | |
578 , qo( collection, atoms(CC), any(collection,CC)) | |
579 , qo( title, atoms(TS), all(title,TS)) | |
580 , qo( composer, atoms(CS), any(composer,CS)) | |
581 , qo( performer, atoms(PS), any(performer,PS)) | |
582 , qo( genre, atoms(GS), any(genre,GS)) | |
583 , qo( year, years(YS), year(YS)) | |
584 , qo( place, atoms(PS), any(place,PS)) | |
585 , qo( language, atoms(LNS), any(language,LNS)) | |
586 ]), Filters, []). | |
587 | |
588 process_qopt(qo(OptName,Parser,Filter)) --> | |
589 { Opt=..[OptName,OptVal] }, | |
590 \> option_default_select(Opt,'*'), | |
591 ( {OptVal='*'} -> [] | |
592 ; {parse_atom(Parser,OptVal)}, | |
593 \< [Filter] | |
594 ). | |
595 | |
596 sample(Size,_,Query,X) :- | |
597 setof(X, call(Query,X), All), | |
598 length(All,Total), | |
599 ( Total=<Size -> Subset=All | |
600 ; randset(Size, Total, All, [], Subset) | |
601 ), | |
602 member(X,Subset). | |
603 | |
604 randset(0, _, _) --> !. | |
605 randset(K, N, [A|As]) --> | |
606 ({random(N)>=K} -> {K1=K}; {K1 is K-1}, cons(A)), | |
607 {N1 is N-1}, randset(K1,N1,As). | |
608 | |
609 | |
610 qc(Filters,X) :- maplist(filter(Lib,X),Filters), filter(Lib,X,in_library). | |
611 | |
612 %% lib_property(-Library, -Property, -Predicate) is nondet. | |
613 % | |
614 % This predicate manages the mapping from API search fields to RDF | |
615 % predicates. There are still some questions about: | |
616 % | |
617 % $ composer : marcrel cmp, arr, lyr | |
618 % $ performer : marcrel prf, sng, cnd, drt | |
619 :- rdf_meta lib_property(?,+,r). | |
620 lib_property(bl, collection, dcterms:isPartOf). | |
621 lib_property(bl, language, dcterms:language). | |
622 lib_property(bl, language, dc:language). | |
623 lib_property(bl, place, dcterms:spatial). | |
624 lib_property(ilm, genre, mo:genre). | |
625 | |
626 % lib_property(beets, date, beets:original_year). | |
627 lib_property(ilm, date, ilm:release_date). | |
628 lib_property(charm, date, charm:recording_date). | |
629 lib_property(mazurka, date, mazurka:recording_date). | |
630 lib_property(bl, date, dcterms:created). | |
631 | |
632 lib_property(charm, composer, charm:composer). | |
633 lib_property(mazurka, composer, mazurka:composer). | |
634 lib_property(bl, composer, marcrel:cmp). | |
635 lib_property(bl, composer, marcrel:arr). | |
636 lib_property(beets, composer, beets:composer). | |
637 | |
638 lib_property(charm, performer, charm:performer). | |
639 lib_property(mazurka, performer, mazurka:performer). | |
640 lib_property(bl, performer, marcrel:prf). | |
641 lib_property(bl, performer, marcrel:sng). | |
642 lib_property(beets, performer, beets:artist). | |
643 lib_property(ilm, performer, ilm:arist). | |
644 | |
645 lib_property(charm, title, charm:title). | |
646 lib_property(mazurka, title, mazurka:title). | |
647 lib_property(bl, title, dc:title). | |
648 lib_property(beets, title, beets:title). | |
649 lib_property(ilm, title, dc:title). | |
650 | |
651 lib_property_search(_,collection,X, substring(X)). | |
652 lib_property_search(_,place, X, substring(X)). | |
653 lib_property_search(_,language, X, prefix(X)). | |
654 lib_property_search(_,composer, X, prefix(X)). | |
655 lib_property_search(_,performer, X, prefix(X)). | |
656 lib_property_search(_,title, X, substring(X)). | |
657 lib_property_search(beets, date, L-U, between(L,U1)) :- succ(U,U1). | |
658 lib_property_search(_Lib, date, L-U, between(LA,U1A)) :- | |
659 % Lib\=beets, | |
660 succ(U,U1), | |
661 atom_number(LA,L), | |
662 atom_number(U1A,U1). | |
663 | |
664 %% filter(+Lib, -Resource, +SearchSpec) is nondet. | |
665 filter(Lib, _, libraries(Ls)) :- member(Lib,Ls). | |
666 filter(Lib, X, any(Prop,Vals)) :- member(Val,Vals), filter(Lib,X,Prop,Val). | |
667 filter(Lib, X, all(Prop,Vals)) :- maplist(filter(Lib,X,Prop),Vals). | |
668 filter(Lib, X, year(any(Ys))) :- member(Y,Ys), filter(Lib,X,date,Y-Y). | |
669 filter(Lib, X, year(L-U)) :- filter(Lib,X,date,L-U). | |
670 filter(Lib, X, Prop-Val) :- filter(Lib,X,Prop,Val). | |
671 | |
672 filter(charm, X, in_library) :- rdf(X,charm:file_name,_,charm_p2r). | |
673 filter(mazurka, X, in_library) :- rdf(X,mazurka:pid,_,mazurka_p2r). | |
674 filter(bl, X, in_library) :- rdf(X,rdf:type,mo:'Signal',bl_p2r). | |
675 filter(ilm, X, in_library) :- rdf(X,mo:track_number,_,ilm_p2r). | |
676 filter(beets, X, in_library) :- rdf(X,rdf:type,mo:'AudioFile',beets_p2r). | |
677 | |
678 %% filter(+Lib, -Resource, +Property, +Value) is nondet. | |
679 | |
680 % filter(beets, X,genre,G) :- rdf_has(X,beets:genre,literal(substring(G),_)). | |
681 filter(ilm, X,genre,G) :- | |
682 rdf(GR,rdfs:label,literal(substring(G),_),ilm_p2r), | |
683 rdf(GR,rdf:type,mo:'Genre',ilm_p2r), | |
684 rdf(X,mo:genre,GR). | |
685 | |
686 filter(Lib, X, Prop, Val) :- | |
687 lib_property(Lib,Prop,Pred), | |
688 lib_property_search(Lib,Prop,Val,Search), | |
689 rdf(X,Pred,literal(Search,_)). | |
690 | |
691 % --------- parsers ----------- | |
692 | |
693 % cids(Ids) --> seqmap_with_sep(",",alphanum,Ids). | |
694 cids(Ids) --> semicolon_sep(atom_codes,Ids). | |
695 | |
696 % atoms('*') --> "*", !. | |
697 atoms(AS) --> semicolon_sep(atom_codes,AS1), {maplist(downcase_atom,AS1,AS2),sort(AS2,AS)}. | |
698 whole(A) --> string_without("",Codes), {atom_codes(A1,Codes), downcase_atom(A1,A)}. | |
699 | |
700 % years('*') --> "*", !. | |
701 years(L-U) --> integer(L), "-", integer(U). | |
702 years(any(Ys)) --> semicolon_sep(number_codes,Ys1), {sort(Ys1,Ys)}. | |
703 | |
704 % alphanum(X) --> string_without(",",S), {atom_string(X,S)}. | |
705 | |
706 item(Conv,Item) --> string_without(";",Codes), {call(Conv,Item,Codes)}. | |
707 semicolon_sep(Conv,Items) --> | |
708 seqmap_with_sep(";",item(Conv),Items). | |
709 | |
710 | |
711 parse_atom(Phrase,Atom) :- | |
712 atom_codes(Atom,Codes), | |
713 insist( phrase(Phrase,Codes), parse_failure(Phrase)). | |
714 | |
715 thread_pool:create_pool(vis_recording) :- | |
716 current_prolog_flag(cpu_count,N), | |
717 thread_pool_create(vis_recording, N, [backlog(50)]). |