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