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(kerndata,
|
Daniel@0
|
20 [ uri_spine_pitches/3
|
Daniel@0
|
21 , uri_spine_events/4
|
Daniel@0
|
22 , uri_opus/2
|
Daniel@0
|
23 , events_nth_phrase/3
|
Daniel@0
|
24 , dataset_size/2
|
Daniel@0
|
25 , dataset_items/2
|
Daniel@0
|
26 , dataset_sequences/2
|
Daniel@0
|
27 , dataset_random_subsets/4
|
Daniel@0
|
28 , item_sequence/2
|
Daniel@0
|
29 , item_opus/2
|
Daniel@0
|
30 , item_uri/2
|
Daniel@0
|
31 , metpos/4
|
Daniel@0
|
32 , with_kern_module/3
|
Daniel@0
|
33 , fileset/1
|
Daniel@0
|
34 ]).
|
Daniel@0
|
35
|
Daniel@0
|
36 /** <module> Managings sets of Kern scores
|
Daniel@0
|
37
|
Daniel@0
|
38 This module provides tools for defining and working with sets of musical
|
Daniel@0
|
39 fragments extracted from Humdrum/Kern scores. Sets of files are defined by
|
Daniel@0
|
40 searches in the RDF database. Then, a small language of operations can be
|
Daniel@0
|
41 used to extract given spines and/or break melodic sequences into phrases.
|
Daniel@0
|
42
|
Daniel@0
|
43 A named fileset is a term (the name) associated with a file set specification.
|
Daniel@0
|
44 A fileset specification is a nondeterministic binary predicate which yields
|
Daniel@0
|
45 both a Humdrum file URI and a spine number. An alternative way to refer to a
|
Daniel@0
|
46 file set is anonymously, as a term \Spec. A fileset, then is either a named
|
Daniel@0
|
47 fileset or an anonymous fileset:
|
Daniel@0
|
48 ==
|
Daniel@0
|
49 anonymous_filset ---> \fileset_spec.
|
Daniel@0
|
50 fileset_spec == pred(-uri, -spine_spec).
|
Daniel@0
|
51 named_fileset == term.
|
Daniel@0
|
52 fileset == named_fileset | anonymous_fileset.
|
Daniel@0
|
53 spine == natural. % {1,2,...}
|
Daniel@0
|
54
|
Daniel@0
|
55 spine_spec ---> extract(spine)
|
Daniel@0
|
56 ; trace(spine)
|
Daniel@0
|
57 ; merge
|
Daniel@0
|
58 ; all.
|
Daniel@0
|
59 ==
|
Daniel@0
|
60 Named filesets are defined using the multifile predicate fileset/2.
|
Daniel@0
|
61
|
Daniel@0
|
62 Some predicates are available for convenient construction of fileset_specs:
|
Daniel@0
|
63 ==
|
Daniel@0
|
64 with_spine( +S:spine, +Finder:pred(-uri), -URI:uri, -S:spine_spec) is nondet.
|
Daniel@0
|
65 trace_spine( +S:spine, +Finder:pred(-uri), -URI:uri, -S:spine_spec) is nondet.
|
Daniel@0
|
66 merge_spines( +Finder:pred(-uri), -URI:uri, -S:spine_spec) is nondet.
|
Daniel@0
|
67 all_spines( +Finder:pred(-uri), -URI:uri, -S:spine_spec) is nondet.
|
Daniel@0
|
68
|
Daniel@0
|
69 kern_uri( +FS:find_spec, -URI:uri) is nondet.
|
Daniel@0
|
70
|
Daniel@0
|
71 find_spec ---> (find_spec ; find_spec) % set union
|
Daniel@0
|
72 ; (find_spec , find_spec) % set intersection
|
Daniel@0
|
73 ; under(path) % recursive directory search
|
Daniel@0
|
74 ; in(path) % single directory search
|
Daniel@0
|
75 ; uri=object. % match on RDF property
|
Daniel@0
|
76
|
Daniel@0
|
77 path == atom. % a path relative to root of Humdrum file library.
|
Daniel@0
|
78 object == uri | literal | literal_search_spec.
|
Daniel@0
|
79
|
Daniel@0
|
80 literal == { lang(atom,atom), type(uri,atom) } | atom.
|
Daniel@0
|
81 literal_search_spec ---> literal(literal_query,atom).
|
Daniel@0
|
82 literal_query ---> plain(atom)
|
Daniel@0
|
83 ; exact(atom)
|
Daniel@0
|
84 ; substring(atom)
|
Daniel@0
|
85 ; word(atom)
|
Daniel@0
|
86 ; prefix(atom)
|
Daniel@0
|
87 ; ge(atom)
|
Daniel@0
|
88 ; le(atom)
|
Daniel@0
|
89 ; between(atom,atom)
|
Daniel@0
|
90 ; like(atom).
|
Daniel@0
|
91 ==
|
Daniel@0
|
92 Thus, as a fileset_spec, the term =|with_spine(S,Finder)|= yields the Sth spine
|
Daniel@0
|
93 of each URI produced by Finder. =|all_spines(Finder)|= yields all spines of each file
|
Daniel@0
|
94 produced by Finder. See rdf/3 for more information about literal query terms.
|
Daniel@0
|
95
|
Daniel@0
|
96 Datasets are defined in terms of filesets:
|
Daniel@0
|
97 ==
|
Daniel@0
|
98 fileset :< dataset. % any fileset is also a dataset: each member yields one sequence
|
Daniel@0
|
99 phrases(fileset) :< dataset. % denotes the set of phrases segmented from fileset.
|
Daniel@0
|
100 extract(DS:dataset, Size:nonneg, Offset:nonneg) :: dataset.
|
Daniel@0
|
101 subset(DS:dataset, Size:nonneg, Indices:list(nonneg)) :: dataset.
|
Daniel@0
|
102 subset_ref(DS:dataset, Size:nonneg, SubsetRef:atom) :: dataset.
|
Daniel@0
|
103 null :: dataset.
|
Daniel@0
|
104 ==
|
Daniel@0
|
105
|
Daniel@0
|
106 Each item in a dataset is represented by a term of the following type:
|
Daniel@0
|
107 ==
|
Daniel@0
|
108 dataset_item ---> whole(uri,spine) % Humdrum URI and spine number
|
Daniel@0
|
109 ; phrase(uri,spine,natural). % URI, spine and phrase number
|
Daniel@0
|
110 ; merged(uri). % all spines, highest note of chords
|
Daniel@0
|
111 ==
|
Daniel@0
|
112 Items can be obtained using dataset_items/2.
|
Daniel@0
|
113 Each item corresponds to a list of note numbers, which can be obtained using
|
Daniel@0
|
114 item_sequence/2, or dataset_sequences/2.
|
Daniel@0
|
115
|
Daniel@0
|
116 */
|
Daniel@0
|
117
|
Daniel@0
|
118 :- meta_predicate with_kern_module(+,-,0).
|
Daniel@0
|
119
|
Daniel@0
|
120 :- use_module(library(memo)).
|
Daniel@0
|
121 :- use_module(library(dcg_core)).
|
Daniel@0
|
122 :- use_module(library(snobol)).
|
Daniel@0
|
123 :- use_module(library(listutils)).
|
Daniel@0
|
124 :- use_module(library(fileutils)).
|
Daniel@0
|
125 :- use_module(library(termutils)).
|
Daniel@0
|
126 :- use_module(library(insist)).
|
Daniel@0
|
127 :- use_module(library(humdrum)).
|
Daniel@0
|
128 :- use_module(library(humdrum/kern)).
|
Daniel@0
|
129 :- use_module(library(humdrum/dynam)).
|
Daniel@0
|
130 :- use_module(library(humdrum/humdrum_world)).
|
Daniel@0
|
131 :- use_module(library(humdrum/kernutils)).
|
Daniel@0
|
132 :- use_module(library(lambda)).
|
Daniel@0
|
133 :- use_module(library(semweb/rdf_db)).
|
Daniel@0
|
134 :- use_module(library(humdrum_p2r), [hum_uri_path/2]).
|
Daniel@0
|
135 :- use_module(library(dataset), [random_subset/4]).
|
Daniel@0
|
136
|
Daniel@0
|
137 :- set_prolog_flag(double_quotes, codes).
|
Daniel@0
|
138 :- initialization memo_attach(memo(kerndata),[]).
|
Daniel@0
|
139
|
Daniel@0
|
140 :- dynamic item_sequence/2.
|
Daniel@0
|
141 :- multifile fileset/2.
|
Daniel@0
|
142
|
Daniel@0
|
143 %% fileset(-FS:named_fileset) is nondet.
|
Daniel@0
|
144 % True when FS identifies an explicitly declared Kern file-set.
|
Daniel@0
|
145 fileset(FS) :- fileset(FS,Spec), FS \= \Spec.
|
Daniel@0
|
146
|
Daniel@0
|
147 %% fileset(+FS:named_fileset, -Spec:fileset_spec) is semidet.
|
Daniel@0
|
148 %% fileset(-FS:named_fileset, -Spec:fileset_spec) is nondet.
|
Daniel@0
|
149 %
|
Daniel@0
|
150 % Database of named filesets and their fileset specifiers.
|
Daniel@0
|
151 fileset(lorraine, with_spine(1,kern_uri(in('lorraine')))).
|
Daniel@0
|
152 fileset(nova_scotia, with_spine(1,kern_uri(in('classical/songs/unaccompanied/nova-scotia/kern')))).
|
Daniel@0
|
153 fileset(ireland, with_spine(1,kern_uri(in('ireland')))).
|
Daniel@0
|
154 fileset(chorales, with_spine(1,kern_uri(in('classical/bach/chorales')))).
|
Daniel@0
|
155 fileset(chorales371, with_spine(4,kern_uri(in('classical/bach/371chorales')))).
|
Daniel@0
|
156 fileset(bach_cello, with_spec(merge,kern_uri(in('classical/bach/cello')))).
|
Daniel@0
|
157 fileset(bach_violin, with_spec(merge,kern_uri(in('classical/bach/violin')))).
|
Daniel@0
|
158 fileset(beethoven_quartets, all_spines(kern_uri(in('classical/beethoven/quartet')))).
|
Daniel@0
|
159 fileset(essen, with_spine(1,kern_uri(under('essen/europe')))).
|
Daniel@0
|
160 fileset(essen(china),with_spine(1,kern_uri(under('essen/china')))).
|
Daniel@0
|
161 fileset(essen(Rgn), with_spine(1,kern_uri(under(Dir)))) :-
|
Daniel@0
|
162 member(Rgn,[germany,rossiya,magyar,elsass,lothring,nederlan,schweiz,oesterrh,jugoslav]),
|
Daniel@0
|
163 atom_concat('essen/europe/',Rgn,Dir).
|
Daniel@0
|
164 fileset(essen(germany,Sub), with_spine(1,kern_uri(under(Dir)))) :-
|
Daniel@0
|
165 member(Sub,[dva,allerkbd,kinder,altdeu1,altdeu2,fink,zuccal,ballad,boehme,erk]),
|
Daniel@0
|
166 atom_concat('essen/europe/germany/',Sub,Dir).
|
Daniel@0
|
167
|
Daniel@0
|
168
|
Daniel@0
|
169 %% uri_opus(+URI:uri,-Opus:atom) is semidet.
|
Daniel@0
|
170 %% uri_opus(-URI:uri,-Opus:atom) is nondet.
|
Daniel@0
|
171 % Relation between Humdrum file URIs and their Humdrum SCT property.
|
Daniel@0
|
172 uri_opus(URI,Opus) :- rdf(URI,hum:'refcode/SCT',literal(Opus)).
|
Daniel@0
|
173
|
Daniel@0
|
174 % :- volatile_memo file_opus( +file:atom, -opus:atom).
|
Daniel@0
|
175 % file_opus(File,Opus) :-
|
Daniel@0
|
176 % with_kern_module(File, utf8, Mod, (Mod:ref('SCT',_,Opus) -> true; Opus=unknown(_))).
|
Daniel@0
|
177
|
Daniel@0
|
178 %% item_opus(+Item:dataset_item, -Opus:atom) is semidet.
|
Daniel@0
|
179 % Relation between a dataset item and the opus of its associated Humdrum file.
|
Daniel@0
|
180 item_opus(Item,Opus) :- item_uri(Item,URI), uri_opus(URI,Opus).
|
Daniel@0
|
181
|
Daniel@0
|
182 %% item_uri(+Item:dataset_item, -URI:uri) is semidet.
|
Daniel@0
|
183 % Relation between a dataset item and the URI of its associated Humdrum file.
|
Daniel@0
|
184 item_uri(phrase(URI,_,_),URI).
|
Daniel@0
|
185 item_uri(whole(URI,_),URI).
|
Daniel@0
|
186 item_uri(merged(URI),URI).
|
Daniel@0
|
187
|
Daniel@0
|
188
|
Daniel@0
|
189 %% dataset_size(+DS:dataset, -N:nonneg) is det.
|
Daniel@0
|
190 % Get the size of a given dataset. This predicate is persistently memoised,
|
Daniel@0
|
191 % since computing the size of a large dataset may involve reading many Humdrum
|
Daniel@0
|
192 % files.
|
Daniel@0
|
193
|
Daniel@0
|
194 :- persistent_memo dataset_size( +ground, -nonneg).
|
Daniel@0
|
195
|
Daniel@0
|
196 dataset_size(Dataset,NumItems) :-
|
Daniel@0
|
197 eval_dataset(Dataset,Items),
|
Daniel@0
|
198 length(Items,NumItems).
|
Daniel@0
|
199
|
Daniel@0
|
200 %% dataset_items(+DS:dataset, -S:list(dataset_item)) is det.
|
Daniel@0
|
201 dataset_items(DS,Items) :- eval_dataset(DS,Items).
|
Daniel@0
|
202
|
Daniel@0
|
203 %% dataset_sequences(+DS:dataset, -S:list(list(integer))) is det.
|
Daniel@0
|
204 dataset_sequences(DS,SS) :-
|
Daniel@0
|
205 dataset_items(DS,Items),
|
Daniel@0
|
206 maplist(item_sequence,Items,SS).
|
Daniel@0
|
207
|
Daniel@0
|
208 %% eval_dataset(+DS:dataset, -Items:list(dataset_item)) is det.
|
Daniel@0
|
209 eval_dataset(DS,_) :- must_be(ground,DS), fail.
|
Daniel@0
|
210 eval_dataset(extract(DS,N,I), D2) :- !,
|
Daniel@0
|
211 eval_dataset(DS, D1),
|
Daniel@0
|
212 drop(I, D1, D3),
|
Daniel@0
|
213 take(N, D3, D2).
|
Daniel@0
|
214
|
Daniel@0
|
215 eval_dataset(subset_ref(DS,N,Ref), D2) :- !,
|
Daniel@0
|
216 dataset_size(DS,Size),
|
Daniel@0
|
217 random_subset(Size,N,Ref,IX),
|
Daniel@0
|
218 eval_dataset(subset(DS,N,IX), D2).
|
Daniel@0
|
219
|
Daniel@0
|
220 eval_dataset(subset(DS,N,IX), D2) :- !,
|
Daniel@0
|
221 eval_dataset(DS, D1),
|
Daniel@0
|
222 length(IX,N),
|
Daniel@0
|
223 maplist(\I^X^nth1(I,D1,X), IX, D2).
|
Daniel@0
|
224
|
Daniel@0
|
225 eval_dataset(null,[]).
|
Daniel@0
|
226 eval_dataset(DS,Items) :-
|
Daniel@0
|
227 fileset_items(DS,Items).
|
Daniel@0
|
228
|
Daniel@0
|
229 :- thread_local item_/1.
|
Daniel@0
|
230 :- volatile_memo fileset_items( +ds:ground, -items:list(ground)).
|
Daniel@0
|
231 %% fileset_items(+FS, -Items:list(dataset_item)) is det.
|
Daniel@0
|
232 % FS can be a fileset or a term =|phrases(Fileset)|=, denoting the set of
|
Daniel@0
|
233 % sequence resulting from segmenting each item in Fileset into phrases.
|
Daniel@0
|
234 fileset_items(DS, Items) :-
|
Daniel@0
|
235 setup_call_cleanup(
|
Daniel@0
|
236 load(DS),
|
Daniel@0
|
237 findall(Item,item_(Item),Items),
|
Daniel@0
|
238 retractall(item_(_))),
|
Daniel@0
|
239 insist(Items\=[]).
|
Daniel@0
|
240
|
Daniel@0
|
241 load(phrases(FS)) :- fileset(FS,Spec), forall_kern(Spec,assert_phrases).
|
Daniel@0
|
242 load(FS) :- fileset(FS,Spec), forall_kern(Spec,assert_whole).
|
Daniel@0
|
243
|
Daniel@0
|
244 %% item_sequence(+Item:dataset_item, -Seq:list(integer)) is det.
|
Daniel@0
|
245 % True when Seq is the list of note numbers for a given item.
|
Daniel@0
|
246
|
Daniel@0
|
247 %% spine_nth_phrase(+Mod:module,+S:spine,-N:natural,-P:list(integer)) is nondet.
|
Daniel@0
|
248 %
|
Daniel@0
|
249 % True when P is the list of note numbers in the Nth phrase on spine S in the
|
Daniel@0
|
250 % Humdrum file represented in module Mod. Phrases can be defined in two ways:
|
Daniel@0
|
251 % 1. Using explicit Kern phrase marks
|
Daniel@0
|
252 % 2. Using notes annotated with a pause mark to determine phrase endings.
|
Daniel@0
|
253 spine_nth_phrase(Mod,Spine,N,Phrase) :-
|
Daniel@0
|
254 Mod:spine(Spine),
|
Daniel@0
|
255 ( once(spine_phrase(Mod,Spine,_,_))
|
Daniel@0
|
256 -> % spine has explicit phrases markings
|
Daniel@0
|
257 kern_get_events(event_or_delim(spine_notenum,Mod,Spine), Events),
|
Daniel@0
|
258 pairs_values(Events,Events1),
|
Daniel@0
|
259 bagof(NNs, L^phrase(contains_group(L,NNs),Events1), Phrases),
|
Daniel@0
|
260 nth1(N,Phrases,Phrase)
|
Daniel@0
|
261 ; % no phrase markings - use pauses
|
Daniel@0
|
262 kern_get_events(event_or_pause(spine_notenum,Mod,Spine), Events),
|
Daniel@0
|
263 events_nth_phrase(Events, N, Phrase)
|
Daniel@0
|
264 ).
|
Daniel@0
|
265
|
Daniel@0
|
266 assert_whole(URI,Mod,Spec) :-
|
Daniel@0
|
267 (Spec=extract(Spine); Spec=all),
|
Daniel@0
|
268 forall( kern_get_events(spine_notenum(Mod,Spine), Events),
|
Daniel@0
|
269 ( assert_id(item_sequence(whole(URI,Spine), Events)),
|
Daniel@0
|
270 assert(item_(whole(URI,Spine))))).
|
Daniel@0
|
271
|
Daniel@0
|
272 assert_whole(URI,Mod,merge) :-
|
Daniel@0
|
273 forall( kern_get_events(top_notenum(Mod), Events),
|
Daniel@0
|
274 ( assert_id(item_sequence(merged(URI), Events)),
|
Daniel@0
|
275 assert(item_(merged(URI))))).
|
Daniel@0
|
276
|
Daniel@0
|
277 assert_phrases(URI,Mod,Spec) :-
|
Daniel@0
|
278 (Spec=extract(Spine); Spec=all),
|
Daniel@0
|
279 forall( spine_nth_phrase(Mod,Spine,N,Phrase),
|
Daniel@0
|
280 ( assert_id(item_sequence(phrase(URI,Spine,N), Phrase)),
|
Daniel@0
|
281 assert(item_(phrase(URI,Spine,N))))).
|
Daniel@0
|
282
|
Daniel@0
|
283 assert_id(Fact) :- call(Fact) -> true; assert(Fact).
|
Daniel@0
|
284
|
Daniel@0
|
285
|
Daniel@0
|
286 contains_group(D,XX) --> arb, group(D,XX,[]), rem.
|
Daniel@0
|
287
|
Daniel@0
|
288 group(D,X1,X2) -->
|
Daniel@0
|
289 delimiter(D,open),
|
Daniel@0
|
290 iterate(content(D),X1,X2),
|
Daniel@0
|
291 delimiter(D,close).
|
Daniel@0
|
292
|
Daniel@0
|
293 content(_,[X|XX],XX) --> [event(X)].
|
Daniel@0
|
294 content(D,XX,XX) --> {dif(D,D1)}, delimiter(D1,_).
|
Daniel@0
|
295 content(D,X1,X2) --> group(D,X1,X2).
|
Daniel@0
|
296 delimiter(D,T) --> [T/D].
|
Daniel@0
|
297
|
Daniel@0
|
298
|
Daniel@0
|
299 %% dataset_random_subsets(+DS:dataset,+K:nonneg,+L:nonneg,-DSX:list(dataset)) is det.
|
Daniel@0
|
300 %
|
Daniel@0
|
301 % Returns L random subsets of K sequences each from dataset DS.
|
Daniel@0
|
302 % K is the size of each random subset. L is the number of subsets
|
Daniel@0
|
303 % returned. Each subset is a term of the form =|subset(DS,K,Indices)|=.
|
Daniel@0
|
304 dataset_random_subsets(DS,K,L,DSX) :-
|
Daniel@0
|
305 dataset_size(DS,N),
|
Daniel@0
|
306 numlist(1,L,SubsetIndices),
|
Daniel@0
|
307 maplist(\I^subset(DS,K,S)^random_subset(N,K,I,S),SubsetIndices,DSX).
|
Daniel@0
|
308
|
Daniel@0
|
309
|
Daniel@0
|
310 %% uri_spine_pitches(+URI:uri,+S:nonneg,-P:list(pitch)) is det.
|
Daniel@0
|
311 %% uri_spine_pitches(+URI:uri,-S:nonneg,-P:list(pitch)) is nondet.
|
Daniel@0
|
312 %
|
Daniel@0
|
313 % True when Pis a list of the pitches of notes in a spine S
|
Daniel@0
|
314 % of the Humdrum file pointed to by URI.
|
Daniel@0
|
315 uri_spine_pitches(URI,Spine,Pitches) :-
|
Daniel@0
|
316 with_kern_module(URI, Mod,
|
Daniel@0
|
317 kern_get_events(spine_pitch(Mod,Spine), Pitches)).
|
Daniel@0
|
318
|
Daniel@0
|
319 %% uri_spine_events(+URI:uri,+G:getter,+S:spine,-E:list(event(A))) is det.
|
Daniel@0
|
320 %% uri_spine_events(+URI:uri,+G:getter,-S:spine,-E:list(event(A))) is nondet.
|
Daniel@0
|
321 %
|
Daniel@0
|
322 % Get list of events from a given spine in a Humdrum file. The kind of events extracted
|
Daniel@0
|
323 % depends on the getter predicate G, which must be of type:
|
Daniel@0
|
324 % ==
|
Daniel@0
|
325 % getter(A) == pred(+M:module,-S:spine,-T:time,-E:event(A)).
|
Daniel@0
|
326 % event(A) ---> event(A) ; pause.
|
Daniel@0
|
327 % ==
|
Daniel@0
|
328
|
Daniel@0
|
329 uri_spine_events(URI,Getter,Spine,Events) :-
|
Daniel@0
|
330 with_kern_module(URI, Mod,
|
Daniel@0
|
331 kern_get_events(event_or_pause(Getter,Mod,Spine), Events)).
|
Daniel@0
|
332
|
Daniel@0
|
333 :- meta_predicate forall_kern(2,3).
|
Daniel@0
|
334 forall_kern(Findspec,Pred) :-
|
Daniel@0
|
335 with_status_line(
|
Daniel@0
|
336 forall( call(Findspec,URI,SpineSpec), (
|
Daniel@0
|
337 status('Loading: ~s',[URI]),
|
Daniel@0
|
338 with_kern_module(URI, Mod, call(Pred,URI,Mod,SpineSpec))
|
Daniel@0
|
339 ))),
|
Daniel@0
|
340 format('Finished loading.\n',[]).
|
Daniel@0
|
341
|
Daniel@0
|
342 %% with_kern_module(+URI:uri, -M:module, +Goal:pred) is nondet.
|
Daniel@0
|
343 %
|
Daniel@0
|
344 % Calls Goal with M set to the name of a temporary moduling containing
|
Daniel@0
|
345 % the information in the Kern file specified by URI.
|
Daniel@0
|
346 with_kern_module(URI,Mod,Goal) :-
|
Daniel@0
|
347 hum_uri_path(URI,Path),
|
Daniel@0
|
348 with_kern_module(Path,utf8,Mod,Goal).
|
Daniel@0
|
349
|
Daniel@0
|
350 :- meta_predicate with_spine(+,1,-,-).
|
Daniel@0
|
351 with_spine(Spine,Finder,URI,extract(Spine)) :- call(Finder,URI).
|
Daniel@0
|
352
|
Daniel@0
|
353 :- meta_predicate all_spines(+,-,-).
|
Daniel@0
|
354 all_spines(Finder,URI,all) :- call(Finder,URI).
|
Daniel@0
|
355
|
Daniel@0
|
356 :- meta_predicate with_spec(+,+,-,-).
|
Daniel@0
|
357 with_spec(SpineSpec,Finder,URI,SpineSpec) :- call(Finder,URI).
|
Daniel@0
|
358
|
Daniel@0
|
359 %% kern_uri(+FS:find_spec, -URI:uri) is nondet.
|
Daniel@0
|
360 %
|
Daniel@0
|
361 % True when URI refers to a Humdrum file that satisfies the given
|
Daniel@0
|
362 % specification. The specification type =|find_spec|= is defined in the
|
Daniel@0
|
363 % module header comment.
|
Daniel@0
|
364 kern_uri(in(Dir),URI) :- rdf(URI,hum:directory,literal(Dir)).
|
Daniel@0
|
365 kern_uri(under(Dir),URI) :- rdf(URI,hum:directory,literal(prefix(Dir),_)).
|
Daniel@0
|
366 kern_uri(A;B, URI) :- kern_uri(A,URI); kern_uri(B,URI).
|
Daniel@0
|
367 kern_uri((A,B), URI) :- kern_uri(A,URI), kern_uri(B,URI).
|
Daniel@0
|
368 kern_uri(Prop=Val,URI) :- rdf(URI,Prop,Val).
|
Daniel@0
|
369
|
Daniel@0
|
370 %% spine_pitch(+Mod:module,-Spine:nonneg,-Time,-Pitch) is nondet.
|
Daniel@0
|
371 spine_pitch(Mod,Spine,Time,P) :-
|
Daniel@0
|
372 Mod:note(pitch(P),_,Time,Spine).
|
Daniel@0
|
373
|
Daniel@0
|
374 spine_pitch_dur(Mod,Spine,Time,P-D) :-
|
Daniel@0
|
375 Mod:note(pitch(P),D,Time,Spine).
|
Daniel@0
|
376
|
Daniel@0
|
377 spine_notenum(Mod,Spine,Time,NN) :-
|
Daniel@0
|
378 spine_pitch(Mod,Spine,Time,Pitch),
|
Daniel@0
|
379 pitch_notenum(Pitch,NN).
|
Daniel@0
|
380
|
Daniel@0
|
381
|
Daniel@0
|
382 %% get the highest pitch over all spines at each time slice.
|
Daniel@0
|
383 top_notenum(Mod,Time,TopNN) :-
|
Daniel@0
|
384 aggregate(max(NN),time_notenum(Mod,Time,NN),TopNN).
|
Daniel@0
|
385
|
Daniel@0
|
386 time_notenum(Mod,Time,NN) :-
|
Daniel@0
|
387 Mod:note(pitch(P),_,Time,_),
|
Daniel@0
|
388 pitch_notenum(P,NN).
|
Daniel@0
|
389
|
Daniel@0
|
390 spine_pause(Mod,Spine,Time,pause) :- spine_pause(Mod,Spine,Time).
|
Daniel@0
|
391 spine_pause(Mod,Spine,Time) :-
|
Daniel@0
|
392 Mod:articulation(pause,Spine,Rec),
|
Daniel@0
|
393 Mod:time(T,Rec),
|
Daniel@0
|
394 Mod:duration(D,Rec),
|
Daniel@0
|
395 Time is T+D.
|
Daniel@0
|
396
|
Daniel@0
|
397 spine_phrase(Mod,Spine,Time,Time-(OpenClose/Label)) :-
|
Daniel@0
|
398 Mod:data(tok(Toks),Spine,Rec),
|
Daniel@0
|
399 member(par(OpenClose,phrase-Label),Toks),
|
Daniel@0
|
400 Mod:time(T,Rec),
|
Daniel@0
|
401 ( OpenClose=open -> Time=T
|
Daniel@0
|
402 ; OpenClose=close -> Mod:duration(D,Rec), Time is T+D
|
Daniel@0
|
403 ).
|
Daniel@0
|
404
|
Daniel@0
|
405
|
Daniel@0
|
406 twos(L) :- L=[2|L].
|
Daniel@0
|
407
|
Daniel@0
|
408 metre(4/4,1:M) :- twos(M).
|
Daniel@0
|
409 metre(3/4,(3 rdiv 4):[3,2|M]) :- twos(M).
|
Daniel@0
|
410 metre(6/8,(3 rdiv 4):[2,3|M]) :- twos(M).
|
Daniel@0
|
411 metre(9/8,(9 rdiv 8):[3,3|M]) :- twos(M).
|
Daniel@0
|
412 metre(12/8,(12 rdiv 8):[2,2,3|M]) :- twos(M).
|
Daniel@0
|
413
|
Daniel@0
|
414 %% metpos( +Bar:rational, +Metre:list(nat), +T0:rational, -R:nat) is det.
|
Daniel@0
|
415 metpos(Bar,Metre,TT,R) :- metpos_(TT,[1/Bar|Metre],0,R).
|
Daniel@0
|
416
|
Daniel@0
|
417 metpos_(0,_,R,R) :- !.
|
Daniel@0
|
418 metpos_(T0,[M0|MX],R0,R) :-
|
Daniel@0
|
419 mod1(T0*M0,T1), succ(R0,R1),
|
Daniel@0
|
420 metpos_(T1,MX,R1,R).
|
Daniel@0
|
421
|
Daniel@0
|
422 mod1(X,Y) :- Z is floor(X), Y is X - Z.
|
Daniel@0
|
423
|
Daniel@0
|
424 event_or_pause(Pred,Mod,Spine,Time,event(X)) :- call(Pred,Mod,Spine,Time,X).
|
Daniel@0
|
425 event_or_pause(_,Mod,Spine,Time,pause) :- spine_pause(Mod,Spine,Time).
|
Daniel@0
|
426
|
Daniel@0
|
427 event_or_delim(Pred,Mod,Spine,Time,2-event(X)) :-
|
Daniel@0
|
428 call(Pred,Mod,Spine,Time,X).
|
Daniel@0
|
429 event_or_delim(_,Mod,Spine,Time,Prio-Delim) :-
|
Daniel@0
|
430 spine_phrase(Mod,Spine,Time,_-Delim),
|
Daniel@0
|
431 delim_prio(Delim,Prio).
|
Daniel@0
|
432
|
Daniel@0
|
433 delim_prio(open/_,1).
|
Daniel@0
|
434 delim_prio(close/_,1).
|
Daniel@0
|
435
|
Daniel@0
|
436 %% events_nth_phrase(+Events:list(event(A)), +N:natural, -P:list(A)) is det.
|
Daniel@0
|
437 % Extract Nth phrase from a list of events or pauses.
|
Daniel@0
|
438 events_nth_phrase(Events,N,Phrase) :-
|
Daniel@0
|
439 phrase((seqmap_with_sep([pause],seqmap(event),Phrases), opt([pause])),Events,[]),
|
Daniel@0
|
440 nth1(N,Phrases,Phrase).
|
Daniel@0
|
441
|
Daniel@0
|
442 event(X) --> [event(X)].
|