Mercurial > hg > dml-open-cliopatria
comparison 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 |
comparison
equal
deleted
inserted
replaced
-1:000000000000 | 0:718306e29690 |
---|---|
1 /* Part of DML (Digital Music Laboratory) | |
2 Copyright 2014-2015 Samer Abdallah, University of London | |
3 | |
4 This program is free software; you can redistribute it and/or | |
5 modify it under the terms of the GNU 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 General Public License for more details. | |
13 | |
14 You should have received a copy of the GNU 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(mo, [ | |
20 load_chord_symbols/0 | |
21 , load_chord_symbols_on/1 | |
22 , has_title/2 | |
23 , timeline/1 | |
24 , interval_on/2 | |
25 , event_on/2 | |
26 , event_time/2 | |
27 , event_chord/2 | |
28 , sorted_events_on/2 | |
29 , sorted_timed_events/2 | |
30 , timeline_event_terms/2 | |
31 , timed_event_term/2 | |
32 , interval_term/2 | |
33 , chord_term/2 | |
34 , note_term/2 | |
35 ]). | |
36 | |
37 :- use_module(library(semweb/rdf_db)). | |
38 :- use_module(library(semweb/rdf_http_plugin)). | |
39 :- use_module(library(apply_macros)). | |
40 | |
41 load_chord_symbols :- | |
42 setof(C,A^rdf(A,chord:chord,C),Chords), | |
43 rdf_load(Chords). | |
44 | |
45 load_chord_symbols_on(TL) :- | |
46 setof(C,E^I^(interval_on(I,TL),event_time(E,I),event_chord(E,C)),Chords), | |
47 rdf_load(Chords). | |
48 | |
49 has_title(TL,Tit) :- rdf(TL,dc:title,Tit). | |
50 | |
51 timeline(TL) :- rdf(TL,rdf:type,tl:'TimeLine'). | |
52 interval_on(I,TL) :- rdf(I,tl:onTimeLine, TL). | |
53 event_time(E,T) :- rdf(E,event:time,T). | |
54 event_on(E,TL) :- interval_on(I,TL), event_time(E,I). | |
55 | |
56 interval_ends(I,T1) :- | |
57 rdf(I,tl:endsAtDuration,literal(AT1)), | |
58 decode_duration(AT1,T1). | |
59 | |
60 interval_starts(I,T1) :- | |
61 rdf(I,tl:beginsAtDuration,literal(AT1)), | |
62 decode_duration(AT1,T1). | |
63 | |
64 decode_duration(A,T) :- sub_atom(A,1,_,1,B), atom_number(B,T). | |
65 | |
66 sorted_events_on(TL,Events) :- | |
67 sorted_timed_events(TL,STE), | |
68 maplist(strip_key,STE,Events). | |
69 | |
70 sorted_timed_events(TL,Events) :- | |
71 findall(interval(T1,T2)-E, ( | |
72 interval_on(I,TL), | |
73 interval_starts(I,T1), | |
74 interval_ends(I,T2), | |
75 event_time(E,I) | |
76 ),TE), | |
77 keysort(TE,Events). | |
78 | |
79 strip_key(_-E,E). | |
80 event_chord(E,C) :- rdf(E,chord:chord,C). | |
81 | |
82 timed_event_term(interval(T1,T2)-Event, event(T1,Dur,ChordTerm)) :- | |
83 Dur is T2-T1, | |
84 event_chord(Event,Chord), | |
85 chord_term(Chord,ChordTerm). | |
86 | |
87 | |
88 user:term_expansion(note_mapping(A,B),note_mapping(AA,B)) :- rdf_global_id(A,AA). | |
89 user:term_expansion(modified(A,B,C),modified(AA,B,C)) :- rdf_global_id(A,AA). | |
90 | |
91 :- rdf_meta note_term(r,?). | |
92 :- rdf_meta chord_term(r,?). | |
93 :- rdf_meta modified(r,?,?). | |
94 | |
95 | |
96 % represent a chord algebraically as a Prolog term | |
97 chord_term(Chord,Term) :- chord_term_semidet(Chord,T) -> Term=T; Term=no_chord. | |
98 | |
99 chord_term_semidet(Chord,chord(Root,Bass,Intervals)) :- | |
100 rdf(Chord,chord:root,R), | |
101 note_term(R,Root), | |
102 (rdf(Chord,chord:bass,B)->interval_term(B,Bass);Bass=1), | |
103 setof(I,rdf(Chord,chord:interval,I),IX), | |
104 maplist(interval_term,IX,Intervals). | |
105 | |
106 note_term(Note,N) :- note_mapping(Note,N). | |
107 note_term(Note,MN) :- | |
108 rdf(Note,chord:natural, Nat), note_term(Nat,N), | |
109 rdf(Note,chord:modifier, Mod), modified(Mod,N,MN). | |
110 | |
111 modified(chord:flat, N, flat(N)). | |
112 modified(chord:doubleflat, N, flat(flat(N))). | |
113 modified(chord:sharp, N, sharp(N)). | |
114 modified(chord:doublesharp, N, sharp(sharp(N))). | |
115 | |
116 note_mapping(chord:'note/A',a). | |
117 note_mapping(chord:'note/B',b). | |
118 note_mapping(chord:'note/C',c). | |
119 note_mapping(chord:'note/D',d). | |
120 note_mapping(chord:'note/E',e). | |
121 note_mapping(chord:'note/F',f). | |
122 note_mapping(chord:'note/G',g). | |
123 | |
124 interval_term(Interval,Term) :- | |
125 rdf(Interval,chord:degree,D), D=literal(type(_,DA)), atom_number(DA,Deg), | |
126 ( rdf(Interval,chord:modifier,Mod) | |
127 -> modified(Mod,Deg,Term) | |
128 ; Term=Deg | |
129 ). | |
130 | |
131 timeline_event_terms(TL,Terms) :- | |
132 sorted_timed_events(TL,Events), | |
133 maplist(timed_event_term,Events,Terms). | |
134 |