annotate cpack/dml/lib/timeline.pl @ 0:718306e29690 tip

commiting public release
author Daniel Wolff
date Tue, 09 Feb 2016 21:05:06 +0100
parents
children
rev   line source
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(mo, [
Daniel@0 20 load_chord_symbols/0
Daniel@0 21 , load_chord_symbols_on/1
Daniel@0 22 , has_title/2
Daniel@0 23 , timeline/1
Daniel@0 24 , interval_on/2
Daniel@0 25 , event_on/2
Daniel@0 26 , event_time/2
Daniel@0 27 , event_chord/2
Daniel@0 28 , sorted_events_on/2
Daniel@0 29 , sorted_timed_events/2
Daniel@0 30 , timeline_event_terms/2
Daniel@0 31 , timed_event_term/2
Daniel@0 32 , interval_term/2
Daniel@0 33 , chord_term/2
Daniel@0 34 , note_term/2
Daniel@0 35 ]).
Daniel@0 36
Daniel@0 37 :- use_module(library(semweb/rdf_db)).
Daniel@0 38 :- use_module(library(semweb/rdf_http_plugin)).
Daniel@0 39 :- use_module(library(apply_macros)).
Daniel@0 40
Daniel@0 41 load_chord_symbols :-
Daniel@0 42 setof(C,A^rdf(A,chord:chord,C),Chords),
Daniel@0 43 rdf_load(Chords).
Daniel@0 44
Daniel@0 45 load_chord_symbols_on(TL) :-
Daniel@0 46 setof(C,E^I^(interval_on(I,TL),event_time(E,I),event_chord(E,C)),Chords),
Daniel@0 47 rdf_load(Chords).
Daniel@0 48
Daniel@0 49 has_title(TL,Tit) :- rdf(TL,dc:title,Tit).
Daniel@0 50
Daniel@0 51 timeline(TL) :- rdf(TL,rdf:type,tl:'TimeLine').
Daniel@0 52 interval_on(I,TL) :- rdf(I,tl:onTimeLine, TL).
Daniel@0 53 event_time(E,T) :- rdf(E,event:time,T).
Daniel@0 54 event_on(E,TL) :- interval_on(I,TL), event_time(E,I).
Daniel@0 55
Daniel@0 56 interval_ends(I,T1) :-
Daniel@0 57 rdf(I,tl:endsAtDuration,literal(AT1)),
Daniel@0 58 decode_duration(AT1,T1).
Daniel@0 59
Daniel@0 60 interval_starts(I,T1) :-
Daniel@0 61 rdf(I,tl:beginsAtDuration,literal(AT1)),
Daniel@0 62 decode_duration(AT1,T1).
Daniel@0 63
Daniel@0 64 decode_duration(A,T) :- sub_atom(A,1,_,1,B), atom_number(B,T).
Daniel@0 65
Daniel@0 66 sorted_events_on(TL,Events) :-
Daniel@0 67 sorted_timed_events(TL,STE),
Daniel@0 68 maplist(strip_key,STE,Events).
Daniel@0 69
Daniel@0 70 sorted_timed_events(TL,Events) :-
Daniel@0 71 findall(interval(T1,T2)-E, (
Daniel@0 72 interval_on(I,TL),
Daniel@0 73 interval_starts(I,T1),
Daniel@0 74 interval_ends(I,T2),
Daniel@0 75 event_time(E,I)
Daniel@0 76 ),TE),
Daniel@0 77 keysort(TE,Events).
Daniel@0 78
Daniel@0 79 strip_key(_-E,E).
Daniel@0 80 event_chord(E,C) :- rdf(E,chord:chord,C).
Daniel@0 81
Daniel@0 82 timed_event_term(interval(T1,T2)-Event, event(T1,Dur,ChordTerm)) :-
Daniel@0 83 Dur is T2-T1,
Daniel@0 84 event_chord(Event,Chord),
Daniel@0 85 chord_term(Chord,ChordTerm).
Daniel@0 86
Daniel@0 87
Daniel@0 88 user:term_expansion(note_mapping(A,B),note_mapping(AA,B)) :- rdf_global_id(A,AA).
Daniel@0 89 user:term_expansion(modified(A,B,C),modified(AA,B,C)) :- rdf_global_id(A,AA).
Daniel@0 90
Daniel@0 91 :- rdf_meta note_term(r,?).
Daniel@0 92 :- rdf_meta chord_term(r,?).
Daniel@0 93 :- rdf_meta modified(r,?,?).
Daniel@0 94
Daniel@0 95
Daniel@0 96 % represent a chord algebraically as a Prolog term
Daniel@0 97 chord_term(Chord,Term) :- chord_term_semidet(Chord,T) -> Term=T; Term=no_chord.
Daniel@0 98
Daniel@0 99 chord_term_semidet(Chord,chord(Root,Bass,Intervals)) :-
Daniel@0 100 rdf(Chord,chord:root,R),
Daniel@0 101 note_term(R,Root),
Daniel@0 102 (rdf(Chord,chord:bass,B)->interval_term(B,Bass);Bass=1),
Daniel@0 103 setof(I,rdf(Chord,chord:interval,I),IX),
Daniel@0 104 maplist(interval_term,IX,Intervals).
Daniel@0 105
Daniel@0 106 note_term(Note,N) :- note_mapping(Note,N).
Daniel@0 107 note_term(Note,MN) :-
Daniel@0 108 rdf(Note,chord:natural, Nat), note_term(Nat,N),
Daniel@0 109 rdf(Note,chord:modifier, Mod), modified(Mod,N,MN).
Daniel@0 110
Daniel@0 111 modified(chord:flat, N, flat(N)).
Daniel@0 112 modified(chord:doubleflat, N, flat(flat(N))).
Daniel@0 113 modified(chord:sharp, N, sharp(N)).
Daniel@0 114 modified(chord:doublesharp, N, sharp(sharp(N))).
Daniel@0 115
Daniel@0 116 note_mapping(chord:'note/A',a).
Daniel@0 117 note_mapping(chord:'note/B',b).
Daniel@0 118 note_mapping(chord:'note/C',c).
Daniel@0 119 note_mapping(chord:'note/D',d).
Daniel@0 120 note_mapping(chord:'note/E',e).
Daniel@0 121 note_mapping(chord:'note/F',f).
Daniel@0 122 note_mapping(chord:'note/G',g).
Daniel@0 123
Daniel@0 124 interval_term(Interval,Term) :-
Daniel@0 125 rdf(Interval,chord:degree,D), D=literal(type(_,DA)), atom_number(DA,Deg),
Daniel@0 126 ( rdf(Interval,chord:modifier,Mod)
Daniel@0 127 -> modified(Mod,Deg,Term)
Daniel@0 128 ; Term=Deg
Daniel@0 129 ).
Daniel@0 130
Daniel@0 131 timeline_event_terms(TL,Terms) :-
Daniel@0 132 sorted_timed_events(TL,Events),
Daniel@0 133 maplist(timed_event_term,Events,Terms).
Daniel@0 134