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