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