18
19:- module(kernutils,
20 [ kern_get_notes/3
21 , kern_get_spine_notes/4
22 , kern_get_events/2
23 , compare_time_key/3
24 , pitch_notenum/2
25 , pitch_class/2
26 ]). 27
28:- meta_predicate kern_get_events(2,-). 29
30:- use_module(library(pairs)).
35kern_get_events(EventPred,XXX) :-
36 setof( T-Event, call(EventPred,T,Event), Events),
37 predsort(compare_time_key,Events,Sorted),
38 pairs_values(Sorted,XXX).
45kern_get_notes(Mod,Decoder,XXX) :-
46 kern_get_events(note_event(Mod,Decoder),XXX).
52kern_get_spine_notes(Mod,Decoder,Spine,XXX) :-
53 kern_get_events(note_event(Mod,Decoder,Spine),XXX).
54
55note_event(Module,Decoder,Time,Info) :- note_event(Module,Decoder,_,Time,Info).
56note_event(Module,Decoder,Spine,Time,Info) :-
57 Module:note(KernEv,Dur,Time,Spine),
58 call(Decoder,KernEv,Time,Dur,Info).
59
60decode_note_pitch_dur(Event,T,Dur,(Note,Dur)) :- decode_note_pitch(Event,T,Dur,Note).
61decode_note_nnum_dur(Event,T,Dur,(Note,Dur)) :- decode_note_nnum(Event,T,Dur,Note).
62decode_time_dur_pitch(pitch(P),T,Dur,note(T,Dur,P)).
63decode_time_dur_nn(pitch(P),T,Dur,note(T,Dur,NN)) :- pitch_notenum(P,NN).
64decode_full(Event,T,Dur,note(T,Dur,Event)).
65
66decode_note_pitch( pitch(P),_,_,pitch(P)).
67decode_note_pitch( rest, _,_,rest).
68
69decode_note_nnum( pitch(P),_,_,nn(NN)) :- pitch_notenum(P,NN).
70decode_note_nnum( rest, _,_,rest).
71
72decode_pitch( pitch(P),_,_,P).
73decode_nnum( pitch(P),_,_,NN) :- pitch_notenum(P,NN).
77compare_time_key(R,X-A,Y-B) :- (X<Y -> R=(<); X>Y -> R=(>); compare(R,A,B)).
82pitch_notenum(PC/Oct,NN) :- !, pc_nn(PC,NN1), oct_semis(Oct,O), NN is NN1 - O.
83pitch_notenum(PC*Oct,NN) :- !, pc_nn(PC,NN1), oct_semis(Oct,O), NN is NN1 + O.
84pitch_notenum(PC,NN) :- pc_nn(PC,NN).
85
86oct_semis(oct^N,M) :- !, M is 12*N.
87oct_semis(oct,12).
88
89pc_nn(sharp(PC),N) :- !, pc_nn(PC,M), succ(M,N).
90pc_nn(flat(PC),N) :- !, pc_nn(PC,M), succ(N,M).
91pc_nn(c,60).
92pc_nn(d,62).
93pc_nn(e,64).
94pc_nn(f,65).
95pc_nn(g,67).
96pc_nn(a,69).
97pc_nn(b,71).
102pitch_class(P,_) :- must_be(nonvar,P), fail.
103pitch_class(P/oct,PC) :- !, pitch_class(P,PC).
104pitch_class(P*oct,PC) :- !, pitch_class(P,PC).
105pitch_class(P,P)