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