1/* Part of plumdrum
    2	Copyright 2012-2015 Samer Abdallah (Queen Mary University of London; UCL)
    3	 
    4	This program is free software; you can redistribute it and/or
    5	modify it under the terms of the GNU Lesser 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 Lesser General Public License for more details.
   13
   14	You should have received a copy of the GNU Lesser 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(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)).
 kern_get_events(+EventPred:pred(time,A), -Events:list(A)) is det
% Collect timed events and return as a temporally sorted list.
   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).
 kern_get_notes(+Mod:module, +Decoder:kern_event_decoder(A), -Events:list(A)) is det
Collect all notes in a kern file module and return as a list whose element type is determined by Decoder.
   45kern_get_notes(Mod,Decoder,XXX) :-
   46   kern_get_events(note_event(Mod,Decoder),XXX).
 kern_get_spine_notes(+Mod:module, +Decoder:kern_event_decoder(A), +Spine:spine, -Events:list(A)) is det
Collect all notes one a given spine in a kern file module and return as a list whose element type is determined by Decoder.
   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).
 compare_time_key(+R:relation, +X:pair(time,A), +Y:pair(time,B)) is semidet
compare_time_key( -R:relation, +X:time, +Y:time) is det.
   77compare_time_key(R,X-A,Y-B) :- (X<Y -> R=(<); X>Y -> R=(>); compare(R,A,B)).
 pitch_notenum(+P:pitch, -NN:between(0,127)) is det
Compute MIDI note number (0--127) for a given Kern pitch
   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).
 pitch_class(+P:pitch, -PC:pitch_class) is det
Get pitch class from pitch by stripping octave modifiers.
  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)