Mercurial > hg > dml-open-cliopatria
comparison cpack/dml/lib/vamp.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(vamp, []). | |
20 | |
21 :- use_module(library(semweb/rdf_db)). | |
22 :- use_module(library(semweb/rdf_label)). | |
23 :- use_module(library(archive)). | |
24 :- use_module(library(settings)). | |
25 :- use_module(library(fileutils), except([file_under/4])). | |
26 :- use_module(library(termutils)). | |
27 :- use_module(library(rdfutils)). | |
28 :- use_module(library(xmlarchive)). | |
29 :- use_module(library(dcg_core)). | |
30 :- use_module(library(dcg_pair)). | |
31 :- use_module(library(dcg/basics)). | |
32 :- use_module(library(insist)). | |
33 :- use_module(library(lambda)). | |
34 :- use_module(entailment(p2r)). | |
35 :- use_module(api(archive)). | |
36 :- use_module(cliopatria(hooks)). | |
37 | |
38 :- set_prolog_flag(double_quotes,string). | |
39 :- rdf_register_prefix(vamp,'http://purl.org/ontology/vamp/'). | |
40 :- rdf_register_prefix(vamp_plugins,'http://vamp-plugins.org/rdf/plugins/'). | |
41 | |
42 | |
43 % -------------- LABEL HOOKS FOR COMPUTATIONS AND TRANSFORMS ---------------- | |
44 | |
45 rdf_label:display_label_hook(R,_,Label) :- | |
46 rdf(R,rdf:type,dml:'Computation'), !, | |
47 rdf(R,dml:'comp/function',Fn), rdf_display_label(Fn,FnLabel), | |
48 rdf(R,dml:'comp/input',Input), | |
49 ( Input=literal(InputLabel) -> true | |
50 ; rdf_display_label(Input,InputLabel) | |
51 ), | |
52 format(string(Label),'~s \u25B8 ~s',[InputLabel,FnLabel]). | |
53 | |
54 rdf_label:display_label_hook(R,_,Label) :- rdf(_,vamp:parameter,R), !, label(parameter,R,Label). | |
55 % rdf_label:display_label_hook(R,_,Label) :- rdf(R,rdf:type,vamp:'Transform'), !, label(transform,R,Label). | |
56 rdf_label:display_label_hook(R,_,Label) :- rdf(_,vamp:parameter_binding,R), !, label(binding,R,Label). | |
57 | |
58 label(binding,URI,Label) :- | |
59 rdf(URI,vamp:parameter,Param), label(parameter,Param,ParamLabel), | |
60 rdf(URI,vamp:value,Value), rdf_literal_value(Value,Val), | |
61 format(string(Label),'~s=~w',[ParamLabel,Val]). | |
62 | |
63 | |
64 label(parameter,URI,Label) :- | |
65 rdf(URI,vamp:identifier,ID), literal_text(ID,IDText), | |
66 ( rdf(URI,vamp:unit,Unit), | |
67 literal_text(Unit,UnitText), | |
68 UnitText\='' | |
69 -> literal_text(Unit,UnitText), | |
70 format(string(Label),'~s (~s)',[IDText,UnitText]) | |
71 ; format(string(Label),'~s',[IDText]) | |
72 ). | |
73 | |
74 label(transform,URI,Label) :- | |
75 rdf(URI,vamp:plugin,Plugin), rdf_display_label(Plugin,PluginName), | |
76 rdf(URI,vamp:output,Output), rdf_display_label(Output,OutputLabel), | |
77 ( setof(B,rdf(URI,vamp:parameter_binding,B),Bindings) | |
78 -> maplist(label(binding),Bindings,BindingLabels), | |
79 atomics_to_string(BindingLabels,', ',BindingsText), | |
80 format(string(Label),'~s (~s) | ~s',[PluginName,BindingsText,OutputLabel]) | |
81 ; format(string(Label),'~s | ~s',[PluginName,OutputLabel]) | |
82 %cdot is \u22C5 | |
83 ). | |
84 | |
85 % ---------------------- HIGH LEVEL OPS --------------------------- | |
86 | |
87 % :- rdf_meta make_triple(r,r,o,-). | |
88 % make_triple(S,P,O,rdf(S,P,O)). | |
89 | |
90 :- public import/0. | |
91 import :- | |
92 installed_plugins(Plugins), | |
93 load_plugins(Plugins), | |
94 assert_all_to( vamp, plugins_triple(Plugins)), | |
95 assert_all_to( vamp, vamp_triple(transforms)), | |
96 assert_all_to( vamp, vamp_triple('_Audio_Analysis')), | |
97 assert_all_to( vamp, vamp_triple('_ILM_Analysis')). | |
98 | |
99 import_directory_graph(Dir,Graph) :- | |
100 must_be(ground,Graph), | |
101 must_be(atom,Dir), | |
102 retractall(failed(_,_)), | |
103 rdf_retractall(_,_,_,Graph), | |
104 with_status_line(assert_all_to(Graph, vamp_triple(Dir))). | |
105 | |
106 vamp_triple(Pattern,Triple) :- | |
107 absolute_file_name(archive(vamp),VampRoot), | |
108 atomic_list_concat([VampRoot,'/',Pattern],AbsPattern), | |
109 absolute_file_name(AbsPattern,AbsDir,[expand(true),file_type(directory)]), | |
110 atom_concat(VampRoot,RelDir,AbsDir), | |
111 atomic_list_concat([_|RelParts],'/',RelDir), | |
112 RelParts=[Top|_], | |
113 directory_triple(Top,[vamp|RelParts],AbsDir,Triple). | |
114 | |
115 | |
116 installed_plugins(Plugins) :- | |
117 absolute_file_name(path('sonic-annotator'),_,[access(execute)]), | |
118 with_input_from_file(pipe('sonic-annotator -l'), read_lines_to_strings(current_input,Lines)), | |
119 setof(Library:Name, | |
120 O^ID^(member(ID,Lines),atomic_list_concat([vamp,Library,Name,O],':',ID)), | |
121 Plugins). | |
122 | |
123 load_plugins(Plugins) :- | |
124 setof(Library, Name^member(Library:Name, Plugins), Libraries), | |
125 maplist(\Lib^URL^rdf_global_id(vamp_plugins:Lib,URL), Libraries, URLs), | |
126 rdf_load(URLs,[]). | |
127 | |
128 :- rdf_meta plugins_triple(+,t). | |
129 plugins_triple(Plugins,rdf(URI,rdf:type,dml:'Installed')) :- | |
130 rdf_current_prefix(vamp_plugins,PluginURLBase), | |
131 member(Library:Name,Plugins), | |
132 format(atom(URI),'~w~w#~w',[PluginURLBase,Library,Name]). | |
133 | |
134 | |
135 directory_triple(transforms,DirParts,AbsDir,Triple) :- !, | |
136 append(DirParts,Parts,LocParts), | |
137 file_under(AbsDir,AbsPath,Parts), | |
138 file_name_extension(_, n3, AbsPath), | |
139 locator_uri( file(LocParts), URI), | |
140 dcg_triple( transform_triples(URI, with_file(AbsPath)), Triple). | |
141 | |
142 directory_triple('_ILM_Analysis',DirParts,AbsDir,Triple) :- !, | |
143 append(DirParts,Parts,LocParts), | |
144 file_under(AbsDir,_,Parts), | |
145 append(_,[FileName],Parts), | |
146 file_name_extension(BaseName,csv,FileName), | |
147 Locator=file(LocParts), | |
148 status("Importing: ~w",[Locator]), | |
149 string_codes(BaseName, BaseNameCodes), | |
150 ( phrase(ilm_filename(AlbumId,TrackNo,PluginAndOutput), BaseNameCodes) | |
151 -> true | |
152 ; print_message(warning,failed_to_parse_ilm_file(LocParts)), fail | |
153 ), | |
154 insist(tmap(PluginAndOutput,TName)), | |
155 locator_uri(file([vamp,transforms,TName]),TransformGraph), | |
156 atom_concat(TransformGraph,'#transform',Transform), | |
157 locator_uri(Locator,FileURI), | |
158 pattern_uri(ilm:track/num(AlbumId)/num(TrackNo), AudioObject), | |
159 dcg_triple(computation_triples(_,AudioObject,Transform,FileURI), Triple). | |
160 | |
161 directory_triple(_,DirParts,AbsDir,Triple) :- | |
162 append(DirParts,Parts,LocParts), | |
163 file_under(AbsDir,AbsPath,Parts), | |
164 file_name_extension(_,Ext,AbsPath), | |
165 append([_,_|PathParts],[FileName],LocParts), | |
166 ( archive_ext(Ext) | |
167 -> fail % DISABLED | |
168 %append(PathParts,Tail,CompositeParts), | |
169 %atomics_to_string(LocParts,'/',RelPath), | |
170 %with_archive_file(AbsPath, Name, | |
171 % archive_entry_triple(CompositeParts-Tail,RelPath,Name,Triple)) | |
172 ; file_name_extension(BaseName,Ext,FileName), | |
173 dcg_triple( file_triples(Ext, BaseName, PathParts, file(LocParts), | |
174 with_file(AbsPath)), | |
175 Triple) | |
176 ). | |
177 | |
178 | |
179 | |
180 read_lines_to_strings(Stream,Lines) :- | |
181 read_line_to_string(Stream,String), | |
182 ( String=end_of_file | |
183 -> Lines=[] | |
184 ; Lines=[String|Rest], | |
185 read_lines_to_strings(Stream,Rest) | |
186 ). | |
187 | |
188 ilm_filename(AlbumId,TrackNo,PluginAndOutput) --> | |
189 integer(AlbumId), "-", | |
190 integer(TrackNo), ".", | |
191 integer(_), "_vamp_", | |
192 string_without([],Codes), | |
193 {atom_codes(PluginAndOutput,Codes)}. | |
194 | |
195 tmap('beatroot-vamp_beatroot_beats', 'beatroot_standard.n3'). | |
196 tmap('qm-vamp-plugins_qm-chromagram_chromagram', 'qm-chromagram_standard.n3'). | |
197 tmap('qm-vamp-plugins_qm-mfcc_coefficients', 'qm-mfcc-standard.n3'). | |
198 tmap('qm-vamp-plugins_qm-keydetector_key', 'qm_vamp_key_standard.n3'). | |
199 tmap('qm-vamp-plugins_qm-keydetector_tonic', 'qm_vamp_key_standard_tonic.n3'). | |
200 tmap('qm-vamp-plugins_qm-segmenter_segmentation', 'qm-segmentation_standard.n3'). | |
201 tmap('qm-vamp-plugins_qm-tempotracker_beats', 'tempotracker_beats_standard.n3'). | |
202 tmap('qm-vamp-plugins_qm-tempotracker_tempo', 'tempotracker_tempo_standard.n3'). | |
203 | |
204 | |
205 with_file(File,Stream,Goal) :- | |
206 with_stream(Stream,open(File,read,Stream),Goal). | |
207 | |
208 %% archive_entry(+Prefix:diff_list(string), +ArchivePath:string,+Name:atom,-Triple:triple,+Archive:archive) is nondet. | |
209 % | |
210 % Produces all the triples associated with the current archive entry. ArchivePath is The relative | |
211 % path to the archive from data root directory (in the setting vamp:data_directory). | |
212 % Prefix is a difference list containing the path components to be prefixed to the inter-archive | |
213 % path to generate the full path associated with the entry. | |
214 archive_entry_triple(Parts-Tail,ArchivePath,Name,Triple,Archive) :- | |
215 split_string(Name,"/","",InArchiveParts), | |
216 append(Tail,[FileName],InArchiveParts), | |
217 % Parts is now full composite path excluding file name | |
218 file_name_extension(BaseName,Ext,FileName), | |
219 dcg_triple( | |
220 file_triples(Ext, BaseName, Parts, archive_entry(ArchivePath,Name), | |
221 with_current_entry_stream(Archive)), | |
222 Triple). | |
223 | |
224 archive_ext('7z'). | |
225 archive_ext(gz). | |
226 archive_ext(bz2). | |
227 archive_ext(zip). | |
228 | |
229 recompute_labels :- | |
230 forall( rdf(T,rdf:type,vamp:'Transform'), | |
231 ( label(transform,T,LabelS), | |
232 atom_string(Label,LabelS), | |
233 ( rdf(T,rdfs:label,Old) | |
234 -> rdf_update(T,rdfs:label,Old,object(literal(Label))) | |
235 ; rdf_assert(T,rdfs:label,literal(Label),vamp) | |
236 ) | |
237 ) | |
238 ). | |
239 | |
240 | |
241 % ------------------- FILE IMPORTER, GENERAL PART --------------------- | |
242 % | |
243 | |
244 % :- rdf_meta rdf(r,r,o,?,?). | |
245 rdf(S,P,O) --> | |
246 { expand_resource(S,SS), | |
247 expand_resource(P,PP), | |
248 expand_resource(O,OO) | |
249 }, | |
250 [rdf(SS,PP,OO)]. | |
251 | |
252 expand_resource(X,X) :- var(X), !, rdf_bnode(X). | |
253 expand_resource(literal(X),O) :- !, rdf_global_object(literal(X),O). | |
254 expand_resource(X,Y) :- pattern_uri(X,Y). | |
255 | |
256 computation_triples(Computation,Input,Function,Output) --> | |
257 ( {rdf(_,dml:'comp/output', Output,vamp)} -> [] % Already loaded | |
258 ; rdf(Computation, rdf:type, dml:'Computation'), | |
259 rdf(Computation, dml:'comp/input', Input), | |
260 rdf(Computation, dml:'comp/function', Function), | |
261 rdf(Computation, dml:'comp/output', Output) | |
262 ). | |
263 | |
264 | |
265 parse_dirname(Dirname,Hash) :- | |
266 sub_string(Dirname,_,_,After,".n3_"), | |
267 sub_string(Dirname,_,After,0,HashString), | |
268 atom_string(Hash,HashString). | |
269 | |
270 :- dynamic failed/2. | |
271 :- meta_predicate file_triples(+,+,+,+,2,?,?). | |
272 | |
273 file_triples(n3,BaseName,_,_,Reader) --> !, | |
274 { (sub_atom(BaseName,B,_,_,'_vamp_') -> B=<2; true), % to allow for qm_vampXXXXX.n3 | |
275 sub_atom(BaseName,_,5,0,Hash), | |
276 status("Importing transform: ~w.n3",[BaseName]), | |
277 pattern_uri(dml:transform/Hash,Graph) | |
278 }, | |
279 transform_triples(Graph,Reader). | |
280 | |
281 file_triples(csv,BaseName,PathParts,Locator,_) --> !, | |
282 { status("Importing: ~w",[Locator]), | |
283 append(PathPrefix,[DirName],PathParts), | |
284 parse_dirname(DirName,Hash), | |
285 atomic_list_concat([transform,'/',Hash,'#',transform], Transform) , | |
286 once(sub_string(BaseName,Bef,_,_,"_vamp")), | |
287 sub_string(BaseName,0,Bef,_,IDString), | |
288 atom_string(ID,IDString), | |
289 locator_uri(Locator,FileURI) | |
290 }, | |
291 { id_to_audio_uri(PathPrefix,ID,AudioObject) -> true | |
292 ; % print_message(warning,failed(id_to_audio_uri(PathParts,PathPrefix,DirName,ID,AudioObject))), | |
293 PathParts=[Collection|_], | |
294 atomic_list_concat([Collection,ID],'/',AudioLocator), | |
295 humdrum_p2r:id_assert(vamp:failed(id_to_audio_uri(PathPrefix,ID,AudioObject),AudioLocator)), | |
296 AudioObject=literal(AudioLocator) | |
297 }, | |
298 computation_triples(_, AudioObject, dml:Transform, FileURI). | |
299 | |
300 | |
301 transform_triples(Graph,Reader) --> | |
302 { rdf_graph(Graph) -> true % already loaded | |
303 ; call(Reader,S,rdf_load(S,[format(turtle),silent(true),base_uri(Graph),graph(Graph)])) | |
304 }, | |
305 { rdf(Transform,rdf:type,vamp:'Transform',Graph) }, | |
306 ( { rdf(Transform,rdfs:label,_) } -> [] | |
307 ; { once(label(transform,Transform,LabelS)) }, % precompute label | |
308 { atom_string(Label,LabelS) }, | |
309 rdf(Transform,rdfs:label,literal(Label)) | |
310 ). | |
311 | |
312 :- use_module(library(memo)). | |
313 :- volatile_memo bare_id_to_audio_uri(+atom,-maybe(atom)). | |
314 bare_id_to_audio_uri(ID,just(URI)) :- | |
315 rdf(DigSig,bldata:path,literal(substring(ID),_)), | |
316 ( rdf(DigSig,mo:sampled_version_of,URI) -> true | |
317 ; rdf(DigSig,rdf:type,mo:'Signal'), URI=DigSig | |
318 ). | |
319 bare_id_to_audio_uri(_,nothing). | |
320 | |
321 %% id_to_audio_uri(+PathParts:list(atom), +ID:atom -URI:uri) is semidet. | |
322 % | |
323 % This predicate has to work out wich recording is being referred to | |
324 % by the name of this output file. It is a not terribly reliable. | |
325 id_to_audio_uri(PathParts,ID,URI) :- | |
326 ( PathParts = ['CHARM-Collection'|_] | |
327 -> rdf(URI,charm:file_name,literal(ID)) | |
328 ; PathParts = ['mazurka-dataset'|_] | |
329 -> atom_concat(pid,PID,ID), | |
330 rdf(URI,mazurka:pid,literal(PID)) | |
331 ; PathParts = ['_Non-music'|_] | |
332 -> bare_id_to_audio_uri(ID,URI) | |
333 ; atomics_to_string(PathParts,"/",Dir), | |
334 atomic_list_concat([Dir,'/',ID,'.'],Prefix), | |
335 rdf(DigSig,bldata:path,literal(prefix(Prefix),_)), | |
336 ( rdf(DigSig,mo:sampled_version_of,URI) -> true | |
337 ; rdf(DigSig,rdf:type,mo:'Signal'), URI=DigSig | |
338 ) | |
339 ). | |
340 | |
341 | |
342 %% missing_audio(-Path:atom,-Matches:list(uri)) is nondet. | |
343 % | |
344 % This predicate help to find which recordings referred to by imported | |
345 % computations could not be found. | |
346 missing_audio(Path,Matches) :- | |
347 setof(Path,SS^rdf(SS,dml:'comp/input',literal(Path)),Paths), | |
348 member(Path,Paths), | |
349 atomic_list_concat([_,Filename],'/',Path), | |
350 sub_atom(Filename,0,_,2,II), | |
351 ( setof(S-Lit,rdf(S,mo:available_as,literal(prefix(II),Lit)),M) | |
352 -> Matches=M | |
353 ; Matches=[] | |
354 ). | |
355 | |
356 % show_counts(Name) --> | |
357 % \< get(D-F), | |
358 % { status('directories: ~|~` t~d~3+, files: ~|~` t~d~5+, ~s',[D,F,Name]) }. | |
359 | |
360 | |
361 assert_all_to(Graph,Pred) :- forall(call(Pred,rdf(S,P,O)), rdf_assert(S,P,O,Graph)). | |
362 | |
363 dcg_triple(Phrase,rdf(S,P,O)) :- | |
364 call_dcg(Phrase,Triples,[]), | |
365 member(rdf(S,P,O),Triples). | |
366 | |
367 pattern_uri(Pattern,URI) :- uripattern:pattern_uri(Pattern,URI), !. | |
368 | |
369 %% file_under(+Dir:path,-AbsPath:path,-Parts:list(string)) is nondet. | |
370 % Finds files under directory Dir, succeeding multiple times with AbsPath | |
371 % bound to the absolute path (as an atom), and Parts bound to a list | |
372 % of directory components ending with the file name. | |
373 file_under(Spec,AbsPath,Parts) :- | |
374 absolute_file_name(Spec,Dir), | |
375 file_under(Dir,AbsPath,Parts,[]). | |
376 | |
377 %% file_under(+Root:path(dir), -File:path(file)) is nondet. | |
378 file_under(Root,File) --> | |
379 { atom_concat(Root,'/*',Pattern), | |
380 status("Expanding: ~w",[Pattern]), | |
381 expand_pattern(Pattern,Item) | |
382 }, | |
383 ( {exists_file(Item)} | |
384 -> {file_base_name(Item,Name), File=Item}, [Name] | |
385 ; {exists_directory(Item)} | |
386 -> {file_base_name(Item,DirName)}, [DirName], | |
387 file_under(Item,File) | |
388 ). | |
389 | |
390 graph_triples(G,Triples) :- findall(rdf(S,P,O),rdf(S,P,O,G),Triples). |