Daniel@0: /* Part of DML (Digital Music Laboratory) Daniel@0: Copyright 2014-2015 Samer Abdallah, University of London Daniel@0: Daniel@0: This program is free software; you can redistribute it and/or Daniel@0: modify it under the terms of the GNU General Public License Daniel@0: as published by the Free Software Foundation; either version 2 Daniel@0: of the License, or (at your option) any later version. Daniel@0: Daniel@0: This program is distributed in the hope that it will be useful, Daniel@0: but WITHOUT ANY WARRANTY; without even the implied warranty of Daniel@0: MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the Daniel@0: GNU General Public License for more details. Daniel@0: Daniel@0: You should have received a copy of the GNU General Public Daniel@0: License along with this library; if not, write to the Free Software Daniel@0: Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301 USA Daniel@0: */ Daniel@0: Daniel@0: :- module(vamp, []). Daniel@0: Daniel@0: :- use_module(library(semweb/rdf_db)). Daniel@0: :- use_module(library(semweb/rdf_label)). Daniel@0: :- use_module(library(archive)). Daniel@0: :- use_module(library(settings)). Daniel@0: :- use_module(library(fileutils), except([file_under/4])). Daniel@0: :- use_module(library(termutils)). Daniel@0: :- use_module(library(rdfutils)). Daniel@0: :- use_module(library(xmlarchive)). Daniel@0: :- use_module(library(dcg_core)). Daniel@0: :- use_module(library(dcg_pair)). Daniel@0: :- use_module(library(dcg/basics)). Daniel@0: :- use_module(library(insist)). Daniel@0: :- use_module(library(lambda)). Daniel@0: :- use_module(entailment(p2r)). Daniel@0: :- use_module(api(archive)). Daniel@0: :- use_module(cliopatria(hooks)). Daniel@0: Daniel@0: :- set_prolog_flag(double_quotes,string). Daniel@0: :- rdf_register_prefix(vamp,'http://purl.org/ontology/vamp/'). Daniel@0: :- rdf_register_prefix(vamp_plugins,'http://vamp-plugins.org/rdf/plugins/'). Daniel@0: Daniel@0: Daniel@0: % -------------- LABEL HOOKS FOR COMPUTATIONS AND TRANSFORMS ---------------- Daniel@0: Daniel@0: rdf_label:display_label_hook(R,_,Label) :- Daniel@0: rdf(R,rdf:type,dml:'Computation'), !, Daniel@0: rdf(R,dml:'comp/function',Fn), rdf_display_label(Fn,FnLabel), Daniel@0: rdf(R,dml:'comp/input',Input), Daniel@0: ( Input=literal(InputLabel) -> true Daniel@0: ; rdf_display_label(Input,InputLabel) Daniel@0: ), Daniel@0: format(string(Label),'~s \u25B8 ~s',[InputLabel,FnLabel]). Daniel@0: Daniel@0: rdf_label:display_label_hook(R,_,Label) :- rdf(_,vamp:parameter,R), !, label(parameter,R,Label). Daniel@0: % rdf_label:display_label_hook(R,_,Label) :- rdf(R,rdf:type,vamp:'Transform'), !, label(transform,R,Label). Daniel@0: rdf_label:display_label_hook(R,_,Label) :- rdf(_,vamp:parameter_binding,R), !, label(binding,R,Label). Daniel@0: Daniel@0: label(binding,URI,Label) :- Daniel@0: rdf(URI,vamp:parameter,Param), label(parameter,Param,ParamLabel), Daniel@0: rdf(URI,vamp:value,Value), rdf_literal_value(Value,Val), Daniel@0: format(string(Label),'~s=~w',[ParamLabel,Val]). Daniel@0: Daniel@0: Daniel@0: label(parameter,URI,Label) :- Daniel@0: rdf(URI,vamp:identifier,ID), literal_text(ID,IDText), Daniel@0: ( rdf(URI,vamp:unit,Unit), Daniel@0: literal_text(Unit,UnitText), Daniel@0: UnitText\='' Daniel@0: -> literal_text(Unit,UnitText), Daniel@0: format(string(Label),'~s (~s)',[IDText,UnitText]) Daniel@0: ; format(string(Label),'~s',[IDText]) Daniel@0: ). Daniel@0: Daniel@0: label(transform,URI,Label) :- Daniel@0: rdf(URI,vamp:plugin,Plugin), rdf_display_label(Plugin,PluginName), Daniel@0: rdf(URI,vamp:output,Output), rdf_display_label(Output,OutputLabel), Daniel@0: ( setof(B,rdf(URI,vamp:parameter_binding,B),Bindings) Daniel@0: -> maplist(label(binding),Bindings,BindingLabels), Daniel@0: atomics_to_string(BindingLabels,', ',BindingsText), Daniel@0: format(string(Label),'~s (~s) | ~s',[PluginName,BindingsText,OutputLabel]) Daniel@0: ; format(string(Label),'~s | ~s',[PluginName,OutputLabel]) Daniel@0: %cdot is \u22C5 Daniel@0: ). Daniel@0: Daniel@0: % ---------------------- HIGH LEVEL OPS --------------------------- Daniel@0: Daniel@0: % :- rdf_meta make_triple(r,r,o,-). Daniel@0: % make_triple(S,P,O,rdf(S,P,O)). Daniel@0: Daniel@0: :- public import/0. Daniel@0: import :- Daniel@0: installed_plugins(Plugins), Daniel@0: load_plugins(Plugins), Daniel@0: assert_all_to( vamp, plugins_triple(Plugins)), Daniel@0: assert_all_to( vamp, vamp_triple(transforms)), Daniel@0: assert_all_to( vamp, vamp_triple('_Audio_Analysis')), Daniel@0: assert_all_to( vamp, vamp_triple('_ILM_Analysis')). Daniel@0: Daniel@0: import_directory_graph(Dir,Graph) :- Daniel@0: must_be(ground,Graph), Daniel@0: must_be(atom,Dir), Daniel@0: retractall(failed(_,_)), Daniel@0: rdf_retractall(_,_,_,Graph), Daniel@0: with_status_line(assert_all_to(Graph, vamp_triple(Dir))). Daniel@0: Daniel@0: vamp_triple(Pattern,Triple) :- Daniel@0: absolute_file_name(archive(vamp),VampRoot), Daniel@0: atomic_list_concat([VampRoot,'/',Pattern],AbsPattern), Daniel@0: absolute_file_name(AbsPattern,AbsDir,[expand(true),file_type(directory)]), Daniel@0: atom_concat(VampRoot,RelDir,AbsDir), Daniel@0: atomic_list_concat([_|RelParts],'/',RelDir), Daniel@0: RelParts=[Top|_], Daniel@0: directory_triple(Top,[vamp|RelParts],AbsDir,Triple). Daniel@0: Daniel@0: Daniel@0: installed_plugins(Plugins) :- Daniel@0: absolute_file_name(path('sonic-annotator'),_,[access(execute)]), Daniel@0: with_input_from_file(pipe('sonic-annotator -l'), read_lines_to_strings(current_input,Lines)), Daniel@0: setof(Library:Name, Daniel@0: O^ID^(member(ID,Lines),atomic_list_concat([vamp,Library,Name,O],':',ID)), Daniel@0: Plugins). Daniel@0: Daniel@0: load_plugins(Plugins) :- Daniel@0: setof(Library, Name^member(Library:Name, Plugins), Libraries), Daniel@0: maplist(\Lib^URL^rdf_global_id(vamp_plugins:Lib,URL), Libraries, URLs), Daniel@0: rdf_load(URLs,[]). Daniel@0: Daniel@0: :- rdf_meta plugins_triple(+,t). Daniel@0: plugins_triple(Plugins,rdf(URI,rdf:type,dml:'Installed')) :- Daniel@0: rdf_current_prefix(vamp_plugins,PluginURLBase), Daniel@0: member(Library:Name,Plugins), Daniel@0: format(atom(URI),'~w~w#~w',[PluginURLBase,Library,Name]). Daniel@0: Daniel@0: Daniel@0: directory_triple(transforms,DirParts,AbsDir,Triple) :- !, Daniel@0: append(DirParts,Parts,LocParts), Daniel@0: file_under(AbsDir,AbsPath,Parts), Daniel@0: file_name_extension(_, n3, AbsPath), Daniel@0: locator_uri( file(LocParts), URI), Daniel@0: dcg_triple( transform_triples(URI, with_file(AbsPath)), Triple). Daniel@0: Daniel@0: directory_triple('_ILM_Analysis',DirParts,AbsDir,Triple) :- !, Daniel@0: append(DirParts,Parts,LocParts), Daniel@0: file_under(AbsDir,_,Parts), Daniel@0: append(_,[FileName],Parts), Daniel@0: file_name_extension(BaseName,csv,FileName), Daniel@0: Locator=file(LocParts), Daniel@0: status("Importing: ~w",[Locator]), Daniel@0: string_codes(BaseName, BaseNameCodes), Daniel@0: ( phrase(ilm_filename(AlbumId,TrackNo,PluginAndOutput), BaseNameCodes) Daniel@0: -> true Daniel@0: ; print_message(warning,failed_to_parse_ilm_file(LocParts)), fail Daniel@0: ), Daniel@0: insist(tmap(PluginAndOutput,TName)), Daniel@0: locator_uri(file([vamp,transforms,TName]),TransformGraph), Daniel@0: atom_concat(TransformGraph,'#transform',Transform), Daniel@0: locator_uri(Locator,FileURI), Daniel@0: pattern_uri(ilm:track/num(AlbumId)/num(TrackNo), AudioObject), Daniel@0: dcg_triple(computation_triples(_,AudioObject,Transform,FileURI), Triple). Daniel@0: Daniel@0: directory_triple(_,DirParts,AbsDir,Triple) :- Daniel@0: append(DirParts,Parts,LocParts), Daniel@0: file_under(AbsDir,AbsPath,Parts), Daniel@0: file_name_extension(_,Ext,AbsPath), Daniel@0: append([_,_|PathParts],[FileName],LocParts), Daniel@0: ( archive_ext(Ext) Daniel@0: -> fail % DISABLED Daniel@0: %append(PathParts,Tail,CompositeParts), Daniel@0: %atomics_to_string(LocParts,'/',RelPath), Daniel@0: %with_archive_file(AbsPath, Name, Daniel@0: % archive_entry_triple(CompositeParts-Tail,RelPath,Name,Triple)) Daniel@0: ; file_name_extension(BaseName,Ext,FileName), Daniel@0: dcg_triple( file_triples(Ext, BaseName, PathParts, file(LocParts), Daniel@0: with_file(AbsPath)), Daniel@0: Triple) Daniel@0: ). Daniel@0: Daniel@0: Daniel@0: Daniel@0: read_lines_to_strings(Stream,Lines) :- Daniel@0: read_line_to_string(Stream,String), Daniel@0: ( String=end_of_file Daniel@0: -> Lines=[] Daniel@0: ; Lines=[String|Rest], Daniel@0: read_lines_to_strings(Stream,Rest) Daniel@0: ). Daniel@0: Daniel@0: ilm_filename(AlbumId,TrackNo,PluginAndOutput) --> Daniel@0: integer(AlbumId), "-", Daniel@0: integer(TrackNo), ".", Daniel@0: integer(_), "_vamp_", Daniel@0: string_without([],Codes), Daniel@0: {atom_codes(PluginAndOutput,Codes)}. Daniel@0: Daniel@0: tmap('beatroot-vamp_beatroot_beats', 'beatroot_standard.n3'). Daniel@0: tmap('qm-vamp-plugins_qm-chromagram_chromagram', 'qm-chromagram_standard.n3'). Daniel@0: tmap('qm-vamp-plugins_qm-mfcc_coefficients', 'qm-mfcc-standard.n3'). Daniel@0: tmap('qm-vamp-plugins_qm-keydetector_key', 'qm_vamp_key_standard.n3'). Daniel@0: tmap('qm-vamp-plugins_qm-keydetector_tonic', 'qm_vamp_key_standard_tonic.n3'). Daniel@0: tmap('qm-vamp-plugins_qm-segmenter_segmentation', 'qm-segmentation_standard.n3'). Daniel@0: tmap('qm-vamp-plugins_qm-tempotracker_beats', 'tempotracker_beats_standard.n3'). Daniel@0: tmap('qm-vamp-plugins_qm-tempotracker_tempo', 'tempotracker_tempo_standard.n3'). Daniel@0: Daniel@0: Daniel@0: with_file(File,Stream,Goal) :- Daniel@0: with_stream(Stream,open(File,read,Stream),Goal). Daniel@0: Daniel@0: %% archive_entry(+Prefix:diff_list(string), +ArchivePath:string,+Name:atom,-Triple:triple,+Archive:archive) is nondet. Daniel@0: % Daniel@0: % Produces all the triples associated with the current archive entry. ArchivePath is The relative Daniel@0: % path to the archive from data root directory (in the setting vamp:data_directory). Daniel@0: % Prefix is a difference list containing the path components to be prefixed to the inter-archive Daniel@0: % path to generate the full path associated with the entry. Daniel@0: archive_entry_triple(Parts-Tail,ArchivePath,Name,Triple,Archive) :- Daniel@0: split_string(Name,"/","",InArchiveParts), Daniel@0: append(Tail,[FileName],InArchiveParts), Daniel@0: % Parts is now full composite path excluding file name Daniel@0: file_name_extension(BaseName,Ext,FileName), Daniel@0: dcg_triple( Daniel@0: file_triples(Ext, BaseName, Parts, archive_entry(ArchivePath,Name), Daniel@0: with_current_entry_stream(Archive)), Daniel@0: Triple). Daniel@0: Daniel@0: archive_ext('7z'). Daniel@0: archive_ext(gz). Daniel@0: archive_ext(bz2). Daniel@0: archive_ext(zip). Daniel@0: Daniel@0: recompute_labels :- Daniel@0: forall( rdf(T,rdf:type,vamp:'Transform'), Daniel@0: ( label(transform,T,LabelS), Daniel@0: atom_string(Label,LabelS), Daniel@0: ( rdf(T,rdfs:label,Old) Daniel@0: -> rdf_update(T,rdfs:label,Old,object(literal(Label))) Daniel@0: ; rdf_assert(T,rdfs:label,literal(Label),vamp) Daniel@0: ) Daniel@0: ) Daniel@0: ). Daniel@0: Daniel@0: Daniel@0: % ------------------- FILE IMPORTER, GENERAL PART --------------------- Daniel@0: % Daniel@0: Daniel@0: % :- rdf_meta rdf(r,r,o,?,?). Daniel@0: rdf(S,P,O) --> Daniel@0: { expand_resource(S,SS), Daniel@0: expand_resource(P,PP), Daniel@0: expand_resource(O,OO) Daniel@0: }, Daniel@0: [rdf(SS,PP,OO)]. Daniel@0: Daniel@0: expand_resource(X,X) :- var(X), !, rdf_bnode(X). Daniel@0: expand_resource(literal(X),O) :- !, rdf_global_object(literal(X),O). Daniel@0: expand_resource(X,Y) :- pattern_uri(X,Y). Daniel@0: Daniel@0: computation_triples(Computation,Input,Function,Output) --> Daniel@0: ( {rdf(_,dml:'comp/output', Output,vamp)} -> [] % Already loaded Daniel@0: ; rdf(Computation, rdf:type, dml:'Computation'), Daniel@0: rdf(Computation, dml:'comp/input', Input), Daniel@0: rdf(Computation, dml:'comp/function', Function), Daniel@0: rdf(Computation, dml:'comp/output', Output) Daniel@0: ). Daniel@0: Daniel@0: Daniel@0: parse_dirname(Dirname,Hash) :- Daniel@0: sub_string(Dirname,_,_,After,".n3_"), Daniel@0: sub_string(Dirname,_,After,0,HashString), Daniel@0: atom_string(Hash,HashString). Daniel@0: Daniel@0: :- dynamic failed/2. Daniel@0: :- meta_predicate file_triples(+,+,+,+,2,?,?). Daniel@0: Daniel@0: file_triples(n3,BaseName,_,_,Reader) --> !, Daniel@0: { (sub_atom(BaseName,B,_,_,'_vamp_') -> B=<2; true), % to allow for qm_vampXXXXX.n3 Daniel@0: sub_atom(BaseName,_,5,0,Hash), Daniel@0: status("Importing transform: ~w.n3",[BaseName]), Daniel@0: pattern_uri(dml:transform/Hash,Graph) Daniel@0: }, Daniel@0: transform_triples(Graph,Reader). Daniel@0: Daniel@0: file_triples(csv,BaseName,PathParts,Locator,_) --> !, Daniel@0: { status("Importing: ~w",[Locator]), Daniel@0: append(PathPrefix,[DirName],PathParts), Daniel@0: parse_dirname(DirName,Hash), Daniel@0: atomic_list_concat([transform,'/',Hash,'#',transform], Transform) , Daniel@0: once(sub_string(BaseName,Bef,_,_,"_vamp")), Daniel@0: sub_string(BaseName,0,Bef,_,IDString), Daniel@0: atom_string(ID,IDString), Daniel@0: locator_uri(Locator,FileURI) Daniel@0: }, Daniel@0: { id_to_audio_uri(PathPrefix,ID,AudioObject) -> true Daniel@0: ; % print_message(warning,failed(id_to_audio_uri(PathParts,PathPrefix,DirName,ID,AudioObject))), Daniel@0: PathParts=[Collection|_], Daniel@0: atomic_list_concat([Collection,ID],'/',AudioLocator), Daniel@0: humdrum_p2r:id_assert(vamp:failed(id_to_audio_uri(PathPrefix,ID,AudioObject),AudioLocator)), Daniel@0: AudioObject=literal(AudioLocator) Daniel@0: }, Daniel@0: computation_triples(_, AudioObject, dml:Transform, FileURI). Daniel@0: Daniel@0: Daniel@0: transform_triples(Graph,Reader) --> Daniel@0: { rdf_graph(Graph) -> true % already loaded Daniel@0: ; call(Reader,S,rdf_load(S,[format(turtle),silent(true),base_uri(Graph),graph(Graph)])) Daniel@0: }, Daniel@0: { rdf(Transform,rdf:type,vamp:'Transform',Graph) }, Daniel@0: ( { rdf(Transform,rdfs:label,_) } -> [] Daniel@0: ; { once(label(transform,Transform,LabelS)) }, % precompute label Daniel@0: { atom_string(Label,LabelS) }, Daniel@0: rdf(Transform,rdfs:label,literal(Label)) Daniel@0: ). Daniel@0: Daniel@0: :- use_module(library(memo)). Daniel@0: :- volatile_memo bare_id_to_audio_uri(+atom,-maybe(atom)). Daniel@0: bare_id_to_audio_uri(ID,just(URI)) :- Daniel@0: rdf(DigSig,bldata:path,literal(substring(ID),_)), Daniel@0: ( rdf(DigSig,mo:sampled_version_of,URI) -> true Daniel@0: ; rdf(DigSig,rdf:type,mo:'Signal'), URI=DigSig Daniel@0: ). Daniel@0: bare_id_to_audio_uri(_,nothing). Daniel@0: Daniel@0: %% id_to_audio_uri(+PathParts:list(atom), +ID:atom -URI:uri) is semidet. Daniel@0: % Daniel@0: % This predicate has to work out wich recording is being referred to Daniel@0: % by the name of this output file. It is a not terribly reliable. Daniel@0: id_to_audio_uri(PathParts,ID,URI) :- Daniel@0: ( PathParts = ['CHARM-Collection'|_] Daniel@0: -> rdf(URI,charm:file_name,literal(ID)) Daniel@0: ; PathParts = ['mazurka-dataset'|_] Daniel@0: -> atom_concat(pid,PID,ID), Daniel@0: rdf(URI,mazurka:pid,literal(PID)) Daniel@0: ; PathParts = ['_Non-music'|_] Daniel@0: -> bare_id_to_audio_uri(ID,URI) Daniel@0: ; atomics_to_string(PathParts,"/",Dir), Daniel@0: atomic_list_concat([Dir,'/',ID,'.'],Prefix), Daniel@0: rdf(DigSig,bldata:path,literal(prefix(Prefix),_)), Daniel@0: ( rdf(DigSig,mo:sampled_version_of,URI) -> true Daniel@0: ; rdf(DigSig,rdf:type,mo:'Signal'), URI=DigSig Daniel@0: ) Daniel@0: ). Daniel@0: Daniel@0: Daniel@0: %% missing_audio(-Path:atom,-Matches:list(uri)) is nondet. Daniel@0: % Daniel@0: % This predicate help to find which recordings referred to by imported Daniel@0: % computations could not be found. Daniel@0: missing_audio(Path,Matches) :- Daniel@0: setof(Path,SS^rdf(SS,dml:'comp/input',literal(Path)),Paths), Daniel@0: member(Path,Paths), Daniel@0: atomic_list_concat([_,Filename],'/',Path), Daniel@0: sub_atom(Filename,0,_,2,II), Daniel@0: ( setof(S-Lit,rdf(S,mo:available_as,literal(prefix(II),Lit)),M) Daniel@0: -> Matches=M Daniel@0: ; Matches=[] Daniel@0: ). Daniel@0: Daniel@0: % show_counts(Name) --> Daniel@0: % \< get(D-F), Daniel@0: % { status('directories: ~|~` t~d~3+, files: ~|~` t~d~5+, ~s',[D,F,Name]) }. Daniel@0: Daniel@0: Daniel@0: assert_all_to(Graph,Pred) :- forall(call(Pred,rdf(S,P,O)), rdf_assert(S,P,O,Graph)). Daniel@0: Daniel@0: dcg_triple(Phrase,rdf(S,P,O)) :- Daniel@0: call_dcg(Phrase,Triples,[]), Daniel@0: member(rdf(S,P,O),Triples). Daniel@0: Daniel@0: pattern_uri(Pattern,URI) :- uripattern:pattern_uri(Pattern,URI), !. Daniel@0: Daniel@0: %% file_under(+Dir:path,-AbsPath:path,-Parts:list(string)) is nondet. Daniel@0: % Finds files under directory Dir, succeeding multiple times with AbsPath Daniel@0: % bound to the absolute path (as an atom), and Parts bound to a list Daniel@0: % of directory components ending with the file name. Daniel@0: file_under(Spec,AbsPath,Parts) :- Daniel@0: absolute_file_name(Spec,Dir), Daniel@0: file_under(Dir,AbsPath,Parts,[]). Daniel@0: Daniel@0: %% file_under(+Root:path(dir), -File:path(file)) is nondet. Daniel@0: file_under(Root,File) --> Daniel@0: { atom_concat(Root,'/*',Pattern), Daniel@0: status("Expanding: ~w",[Pattern]), Daniel@0: expand_pattern(Pattern,Item) Daniel@0: }, Daniel@0: ( {exists_file(Item)} Daniel@0: -> {file_base_name(Item,Name), File=Item}, [Name] Daniel@0: ; {exists_directory(Item)} Daniel@0: -> {file_base_name(Item,DirName)}, [DirName], Daniel@0: file_under(Item,File) Daniel@0: ). Daniel@0: Daniel@0: graph_triples(G,Triples) :- findall(rdf(S,P,O),rdf(S,P,O,G),Triples).