18
19:- module(kern_rules,
20 [ spine/1 21 , spine/2 22 , next_spine/2 23 , colinear/2 24 , fwd/2 25
26 , all_spines/2 27 , xinterp/3 28 , interp/2 29 , tempo/2 30 , barlines/2 31 , barline/3 32 , barline/2 33 , articulation/3 34 , data/2 35 , note/4 36 , kern_note/5 37
38 39 , data_token/2
40 , metre_to_bar_duration/2
41
42 , time//1 43 , token//1 44 ]).
152:- module_transparent
153 spine/1
154 , spine/2
155 , next_spine/2
156 , tempo/2
157 , colinear/2
158 , fwd/2
159 , interp/2
160 , xinterp/3
161 , barlines/2
162 , barline/3
163 , barline/2
164 , articulation/3
165 , data/2
166 , all_spines/2
167 , note/4
168 , kern_note/5
169 , tied_note//5
170 , next_tied_note/7
171
172 , time//1
173 , token//1
. 175
176:- use_module(library(humdrum/kern)).
183spine(S,R) :- xinterp(_,S,R).
190spine(S) :- context_module(M), M:spine(_,S,_,_).
197all_spines(P,R) :-
198 setof(S,call(P,S,R),SX), 199 setof(S,spine(S,R),SX).
210colinear(S,S) :- spine(S).
211
212colinear(S1,S2) :-
213 spine(S1),
214 context_module(M),
215 colinear1(M,[S1],S2).
216
217colinear1(M,SX1,S2) :-
218 next_spine_set(M,SX1,SX2),
219 ( member(S2,SX2)
220 ; ( var(S2) -> SX3=SX2
221 ; include(after(M,S2),SX2,SX3)
222 ),
223 colinear1(M,SX3,S2)
224 ).
225
226after(M,S1,S2) :-
227 M:spine(_,S1,S1_starts,_),
228 M:spine(_,S2,_,S2_ends),
229 S1_starts > S2_ends.
236next_spine(S1,S2) :- context_module(M), next_spine(M,S1,S2).
237
238next_spine(M,S1,S2) :- M:change_spine(_,_,S1,S2,_).
239next_spine(M,S1,S2) :- M:split_spines(S1,S1a,S1b,_), (S2=S1a;S2=S1b).
240next_spine(M,S1,S2) :- M:join_spines(S1,_,S2,_); M:join_spines(_,S1,S2,_).
241
242next_spine_set(M,SX1,SX2) :-
243 setof(SS, S1^(member(S1,SX1), next_spine(M,S1,SS)), SX2).
252fwd((S1,R1),(S2,R2)) :-
253 succ(R1,R2),
254 spine(S2,R2),
255 colinear(S1,S2).
264xinterp(X,S,R) :- context_module(M), M:spine(X,S,I,J), between(I,J,R).
271interp(S,R) :- context_module(M), M:interp(_,S,R).
278barline(B,S,R) :- context_module(M), M:data(tok(bar(B)),S,R).
285barlines(B,R) :- all_spines(data(tok(bar(B))),R).
292articulation(A,S,R) :-
293 context_module(M),
294 M:data(tok(Toks),S,R),
295 member(articulation(A), Toks).
303tempo(Tempo,R) :- all_spines(interp(metro(Tempo)),R).
310barline(S,R) :- barline(_,S,R).
317data(S,R) :- context_module(M), M:data(_,S,R).
330note(Note,Total_Dur,Time,S) :-
331 context_module(M),
332 kern_note(Note,Dur,Tie,S,R),
333 M:time(Time,R),
334 ( Tie=not_tied -> Total_Dur=Dur
335 ; Tie=open
336 -> ( tied_note(cont, Note, Time, Dur, S, 0, Total_Dur) -> true
337 ; format('* ERROR: tied note (~w) at ~w NOT FOUND.\n',[Note,(S/R)]),
338 Total_Dur=Dur
339 )
340 ).
341
342
343tied_note( close, _, _, Dur, _) --> !, add(Dur).
344tied_note( cont, Note, Time, Dur, S) -->
345 346 347 add(Dur),
348 { 349 add(Dur,Time,Time1),
350 ( next_tied_note(colinear, Note, Time1, S, S1, Dur1, Tie)
351 ; next_tied_note(kern_rules:true, Note, Time1, S, S1, Dur1, Tie)
352 ), !
353 },
354 tied_note(Tie,Note,Time1,Dur1,S1).
355
356add(X,Y,Z) :- Z is X+Y.
357
358next_tied_note(Constraint, Note, Time1, S,S1, Dur1, Tie) :-
359 context_module(M),
360 M:time(Time1,R1),
361 M:data(Data,S1,R1), Data\=tok(bar(_)),
362 call(Constraint,S,S1),
363 kern_note(Note,Dur1,Tie,S1,R1),
364 (Tie=cont;Tie=close).
365
366true(_,_).
384kern_note(Event,Dur,Tie,S,R) :-
385 context_module(M),
386 M:data(Data,S,R),
387 xinterp(kern,S,R),
388 data_token(Data,Tok),
389 ( kern_pitch(Tok,Pitch) -> Event=pitch(Pitch)
390 ; kern_rest(Tok) -> Event=rest
391 ),
392 kern_duration(Tok,Dur),
393 kern_tie(Tok,Tie).
394
395
396kern_tie(Sigs,Tie) :- (member(par(Tie,tie),Sigs) -> true; Tie=not_tied).
401data_token(tok(T),T) :- !, T\=bar(_).
402data_token(sub(TX),T) :- member(T,TX).
407metre_to_bar_duration(metre(N,D),BD) :- BD is N rdiv D.
408
409
413time(T,(S,R),(S,R)) :- context_module(M), M:time(T,R).
416token(T,(S,R),(S,R)) :- context_module(M), M:data(X,S,R), data_token(X,T)
Kern inference rules
Usage
This module is designed to be called from a module containing a database describing a humdrum object, which may be created from a Humdrum file by using assert_humdrum/3 in
humdrum_world.pl
The following predicates must be defined in the calling module.
Performance interpretation
dynamics
ornament(_)
trill(whole)
trill(semi)
mordent(whole)
/\___mordent(semi)
/\___inv_mordent(whole)
\/---inv_mordent(semi)
\/--- Speed?grace(_)
TODO
(these are from the kern player - what are they doing here?)*/