annotate cpack/dml/lib/humdrum_p2r.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(humdrum_p2r, [ humdrum_import/1, hum_uri_path/2 ]).
Daniel@0 20
Daniel@0 21 /** <module> Manages a database of Humdrum files and mappings to RDF.
Daniel@0 22 */
Daniel@0 23
Daniel@0 24 :- use_module(library(memo)).
Daniel@0 25 :- use_module(library(humdrum)).
Daniel@0 26 :- use_module(library(humdrum/humdrum_world), [with_kern_module/4]).
Daniel@0 27 :- use_module(library(fileutils)).
Daniel@0 28 :- use_module(library(termutils)).
Daniel@0 29 :- use_module(library(typedef)).
Daniel@0 30 :- use_module(library(dcg_core)).
Daniel@0 31 :- use_module(library(musiclab)).
Daniel@0 32 :- use_module(library(settings)).
Daniel@0 33 :- use_module(entailment(p2r)).
Daniel@0 34
Daniel@0 35 :- set_prolog_flag(double_quotes,string).
Daniel@0 36
Daniel@0 37 :- rdf_register_prefix(humdb,'http://dml.org/humdrum/data/').
Daniel@0 38 :- rdf_register_prefix(hum,'http://dml.org/humdrum/schema/').
Daniel@0 39 :- rdf_register_prefix(kern,'kern:').
Daniel@0 40
Daniel@0 41 :- setting(kern_root,string,"~/lib/kern","Root of kern lib tree").
Daniel@0 42 :- setting(kern_subdirs,list(atom),[classical,lorraine,jrp,ragtime,ireland,pentatonic,idyom],"Kern library directories to import").
Daniel@0 43
Daniel@0 44 uripattern:def( work(Opus), humdb:work/enc(Opus)).
Daniel@0 45 uripattern:def( trefcode(C), hum:refcode/trans/enc(C)).
Daniel@0 46 uripattern:def( refcode(C), hum:refcode/enc(C)).
Daniel@0 47 uripattern:def( kernfile(F), kern:tail(F)).
Daniel@0 48
Daniel@0 49 % Humdrum schema
Daniel@0 50 rdf(hum:refcode('OTL'), rdfs:subPropertyOf, dc:title),
Daniel@0 51 rdf(hum:composer, rdfs:subPropertyOf, foaf:maker),
Daniel@0 52 rdf(hum:opus, rdfs:subPropertyOf, mo:opus),
Daniel@0 53 rdf(hum:'Work', rdfs:subClassOf, mo:'MusicalWork'),
Daniel@0 54 rdf(hum:'File', rdfs:subClassOf, mo:'Score'),
Daniel@0 55 rdf(hum:encodedBy, rdfs:type, rdf:'ObjectProperty'),
Daniel@0 56 % rdf(hum:encodedBy, owl:inverseOf, hum:encodes) <== true.
Daniel@0 57
Daniel@0 58 rdf(\refcode(C), rdfs:subPropertyOf, \trefcode(C)) <==
Daniel@0 59 setof(C, translated_refcode(C), Codes),
Daniel@0 60 member(C, Codes).
Daniel@0 61
Daniel@0 62 rdf(\trefcode(C), rdf:comment, Desc1) <==
Daniel@0 63 setof(C, translated_refcode(C), Codes),
Daniel@0 64 member(C, Codes),
Daniel@0 65 hum_prop_desc(C,Desc),
Daniel@0 66 atom_concat(Desc,' (translated)',Desc1).
Daniel@0 67
Daniel@0 68 translated_refcode(Code) :-
Daniel@0 69 browse(file_props(_,Props)),
Daniel@0 70 member(Code-((sec-_)-_),Props).
Daniel@0 71
Daniel@0 72 hum_prop_desc(C,_) ==>
Daniel@0 73 rdf(\refcode(C), rdf:type, rdf:'ObjectProperty'),
Daniel@0 74 rdf(\refcode(C), rdf:domain, hum:'File').
Daniel@0 75
Daniel@0 76 hum_prop_desc(C,Desc) ==>
Daniel@0 77 rdf(\refcode(C), rdf:comment, literal(Desc)).
Daniel@0 78
Daniel@0 79 % -- mappings that use file_opus/2 ---------------
Daniel@0 80
Daniel@0 81 %% file(-File) is nondet.
Daniel@0 82 % True when File is a Humdrum file that has been imported into
Daniel@0 83 % the current database.
Daniel@0 84 :- dynamic file/1.
Daniel@0 85
Daniel@0 86 %% file_opus(-File,-Opus) is nondet.
Daniel@0 87 % True when Humdrum file File contains an SCT refcode
Daniel@0 88 % (scholarly catalog number) Opus.
Daniel@0 89 file_opus(F,O) :- file(F), file_prop(F,'SCT',_,O).
Daniel@0 90
Daniel@0 91 rdf(\kernfile(F), \trefcode(C), literal(Value)) <==
Daniel@0 92 call_with_mode(browse,file_prop(F,C,sec,Value)).
Daniel@0 93
Daniel@0 94 rdf(\kernfile(F), \refcode(C), literal(Value)) <==
Daniel@0 95 call_with_mode(browse,file_prop(F,C,pri,Value)).
Daniel@0 96
Daniel@0 97 rdf(\kernfile(F), hum:directory, literal(Dir1)) <==
Daniel@0 98 file(F),
Daniel@0 99 file_directory_name(F,Dir),
Daniel@0 100 atom_concat('/',Dir1,Dir).
Daniel@0 101
Daniel@0 102 file(F) ==>
Daniel@0 103 % rdf(\kernfile(F), hum:language, hum:language/humdrum),
Daniel@0 104 rdf(\kernfile(F), rdf:type, hum:'File').
Daniel@0 105
Daniel@0 106 file_opus(_,O) ==>
Daniel@0 107 rdf(\work(O), rdf:type, hum:'Work'),
Daniel@0 108 rdf(\work(O), hum:opus, literal(O)).
Daniel@0 109
Daniel@0 110 % file_opus(F,O) ==>
Daniel@0 111 % rdf(\kernfile(F), hum:encodes, \work(O)).
Daniel@0 112
Daniel@0 113
Daniel@0 114 % rdf(\work(O), dc:title, literal(Title)) <==
Daniel@0 115 % file_opus(F,O),
Daniel@0 116 % (file_has(F,'OTL',Title); file_has(F,'OTP',Title)).
Daniel@0 117
Daniel@0 118 % rdf(\work(O), dc:title, literal(lang(Lang,Title))) <==
Daniel@0 119 % file_opus(F,O),
Daniel@0 120 % file_has(F,'OTL',Title),
Daniel@0 121 % file_has(F,'TXO',Lang).
Daniel@0 122
Daniel@0 123 % rdf(\work(O), hum:partOf, humdb:parent_work/enc(P)) <==
Daniel@0 124 % file_opus(F,O),
Daniel@0 125 % (file_has(F,'OPT',P); file_has(F,'OPR',P)).
Daniel@0 126
Daniel@0 127 % rdf(\work(O), hum:composer, humdb:agent/enc(C)) <==
Daniel@0 128 % file_opus(F,O), file_has(F,'COM',C).
Daniel@0 129
Daniel@0 130 % rdf(\work(O), hum:number, literal(Num)) <==
Daniel@0 131 % file_opus(F,O), file_has(F,'ONM',Num).
Daniel@0 132
Daniel@0 133 % ----- mappings using composers/1 --------
Daniel@0 134
Daniel@0 135 % rdf(humdb:agent/enc(C), foaf:name, literal(C)),
Daniel@0 136 % rdf(humdb:agent/enc(C), rdf:type, mo:'MusicArtist') <==
Daniel@0 137 % composers(Composers),
Daniel@0 138 % member(C,Composers).
Daniel@0 139
Daniel@0 140 % ----- mappings using parent_works/1 --------
Daniel@0 141
Daniel@0 142 % rdf(humdb:parent_work/enc(P), rdf:type, hum:'Work'),
Daniel@0 143 % rdf(humdb:parent_work/enc(P), dc:title, literal(P)) <==
Daniel@0 144 % parent_works(Works),
Daniel@0 145 % member(P,Works).
Daniel@0 146
Daniel@0 147
Daniel@0 148 has_stripped(Recs,Prop,Status,Literal) :-
Daniel@0 149 member(ref(Prop,Lang,RawValue),Recs),
Daniel@0 150 split_string(RawValue,""," ",[String]),
Daniel@0 151 String\="", atom_string(Value,String),
Daniel@0 152 refcode_literal(Lang,Value,Status,Literal).
Daniel@0 153
Daniel@0 154 refcode_literal(def, Val, pri, Val).
Daniel@0 155 refcode_literal(P-Lang, Val, P, lang(L,Val)) :- lang(Lang,L).
Daniel@0 156
Daniel@0 157 :- type prop ---> prop(atom,atom,ground).
Daniel@0 158 :- volatile_memo file_props(+file:atomic,-props:list(prop)).
Daniel@0 159
Daniel@0 160 file_props(File,Props) :-
Daniel@0 161 setting(kern_root,Root0),
Daniel@0 162 expand_file_name(Root0,[Root]),
Daniel@0 163 string_concat(Root,File,Abs),
Daniel@0 164 % !!! FIXME: will barf if Root contains funny characters
Daniel@0 165 format(string(Cmd),"grep '^!!!' \"~w\"",[Abs]),
Daniel@0 166 hum_read(pipe(Cmd),utf8,Recs),
Daniel@0 167 setof(prop(Prop,Status,Lit),has_stripped(Recs,Prop,Status,Lit),Props).
Daniel@0 168
Daniel@0 169
Daniel@0 170 :- volatile_memo parent_works(-works:list(ground)).
Daniel@0 171 parent_works(Works) :-
Daniel@0 172 writeln('% Compiling list of parent works...'),
Daniel@0 173 setof(P, F^O^(file_opus(F,O),file_prop(F,'OPR',_,P)), Works).
Daniel@0 174
Daniel@0 175 :- volatile_memo composers(-composers:list(atom)).
Daniel@0 176
Daniel@0 177 %% composers(-Composers:list(atom)) is det.
Daniel@0 178 % Compiles a list of composer names referenced in the current
Daniel@0 179 % Humdrum file property database file_props/2.
Daniel@0 180 composers(Composers) :-
Daniel@0 181 writeln('% Compiling list of composers...'),
Daniel@0 182 findall(C, call_with_mode(browse,file_prop(_,'COM',_,C)), CList),
Daniel@0 183 sort(CList,Composers).
Daniel@0 184
Daniel@0 185 % rdf(URI,rdf:type,mo:'MusicArtist') <==
Daniel@0 186 % composers(Comps),
Daniel@0 187 % member(C,Comps),
Daniel@0 188 % agent_uri(composer,C,URI).
Daniel@0 189
Daniel@0 190 % rdf(URI,hum:name,literal(Name)) <==
Daniel@0 191 % agent_uri(composer,Name,URI).
Daniel@0 192
Daniel@0 193 % rdf(\kernfile(F), hum:composer, literal(Name)) <==
Daniel@0 194 % call_with_mode(browse,file_prop(F,'COM',pri,Name)),
Daniel@0 195 % agent_uri(composer,Name,URI).
Daniel@0 196
Daniel@0 197
Daniel@0 198 file_work_terms(File) -->
Daniel@0 199 if(file_prop(File,'OTL',_,Title), [Title]),
Daniel@0 200 if(file_prop(File,'OPR',_,Parent), [Parent]),
Daniel@0 201 if(file_prop(File,'OPN',_,Opus), [Opus]),
Daniel@0 202 if(file_prop(File,'SCT',_,Cat), [Cat]).
Daniel@0 203
Daniel@0 204
Daniel@0 205 file_prop(File,Prop,Status,Lit) :-
Daniel@0 206 file_props(File,Props),
Daniel@0 207 member(prop(Prop,Status,Lit),Props).
Daniel@0 208
Daniel@0 209
Daniel@0 210 hum_uri_path(URI,Path) :-
Daniel@0 211 atom_concat('kern:',Rel,URI),
Daniel@0 212 setting(kern_root,Root),
Daniel@0 213 expand_file_name(Root,[Root1]),
Daniel@0 214 string_concat(Root1,Rel,Path).
Daniel@0 215
Daniel@0 216
Daniel@0 217 %% humdrum_import(+Path:atom) is det.
Daniel@0 218 %
Daniel@0 219 % Searches for files in the directory tree beneath
Daniel@0 220 % =|<kern_root>/Path|=, where =|<kern_root"|= is the current
Daniel@0 221 % value of the setting =|humdrum_p2r:kern_root|=. Path can
Daniel@0 222 % be any relative path. Files are added to memoised property
Daniel@0 223 % database predicate file_props/2.
Daniel@0 224 humdrum_import(Path) :-
Daniel@0 225 setting(kern_root,Root0),
Daniel@0 226 expand_file_name(Root0,[Root]),
Daniel@0 227 with_status_line(
Daniel@0 228 forall( ( kern_file(under(Root/Path),File),
Daniel@0 229 atom_concat(Root,Rel,File),
Daniel@0 230 memo(file_props(Rel,_),_-ok)),
Daniel@0 231 ( status(" Imported ~s",[Rel]),
Daniel@0 232 id_assert(file(Rel))) )).
Daniel@0 233
Daniel@0 234 :- volatile_memo scan_library_dir(+ground,-float).
Daniel@0 235 scan_library_dir(Dir,T):- humdrum_import(Dir), get_time(T).
Daniel@0 236
Daniel@0 237
Daniel@0 238 :- public import/0, import/1.
Daniel@0 239 import :-
Daniel@0 240 setting(kern_subdirs,Dirs),
Daniel@0 241 import(Dirs).
Daniel@0 242 import(Dirs) :-
Daniel@0 243 maplist(scan_library_dir,Dirs,_),
Daniel@0 244 assert_all(humdrum_p2r).
Daniel@0 245
Daniel@0 246 :- volatile_memo humfile_status(+string,-ground).
Daniel@0 247 humfile_status(Path,Status) :-
Daniel@0 248 status(Path,[]),
Daniel@0 249 catch( ( with_kern_module(Path,utf8,_,true) -> Status=ok
Daniel@0 250 ; Status=fail),
Daniel@0 251 Ex, Status=ex(Ex)).
Daniel@0 252
Daniel@0 253
Daniel@0 254 humdrum_check :-
Daniel@0 255 with_status_line(
Daniel@0 256 forall( (rdf_db:rdf(X,rdf:type,hum:'File'), hum_uri_path(X,Path)),
Daniel@0 257 ( humfile_status(Path,Status),
Daniel@0 258 ( Status=ok -> true
Daniel@0 259 ; Status=fail -> format('\nFailed on: ~w\n',[Path])
Daniel@0 260 ; Status=ex(Ex) -> format('\nException on: ~w\n',[Path]),
Daniel@0 261 print_message(error,Ex)
Daniel@0 262 )
Daniel@0 263 ))).
Daniel@0 264
Daniel@0 265 kern_file(Findspec,File) :-
Daniel@0 266 find_files(Findspec,File),
Daniel@0 267 extension_in(File,[krn,kern,'KRN','KERN']).
Daniel@0 268
Daniel@0 269 id_assert(Fact) :- call(Fact) -> true; assert(Fact).
Daniel@0 270
Daniel@0 271 lang('ENG',en).
Daniel@0 272 lang('EN',en).
Daniel@0 273 lang('FRA',fr).
Daniel@0 274 lang('FRE',fr).
Daniel@0 275 lang('FR',fr).
Daniel@0 276 lang('DE',de).
Daniel@0 277 lang('DEU',de).
Daniel@0 278 lang('GER',de).
Daniel@0 279 lang('ITA',it).
Daniel@0 280 lang('IT',it).
Daniel@0 281 lang('NO',no).
Daniel@0 282 lang('NOR',no).
Daniel@0 283 lang('LAT',la).
Daniel@0 284 lang('LA',la).
Daniel@0 285 lang('RU',ru).
Daniel@0 286 lang('RUS',ru).