Mercurial > hg > dml-open-cliopatria
diff 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 |
line wrap: on
line diff
--- /dev/null Thu Jan 01 00:00:00 1970 +0000 +++ b/cpack/dml/lib/timeline.pl Tue Feb 09 21:05:06 2016 +0100 @@ -0,0 +1,134 @@ +/* Part of DML (Digital Music Laboratory) + Copyright 2014-2015 Samer Abdallah, University of London + + This program is free software; you can redistribute it and/or + modify it under the terms of the GNU General Public License + as published by the Free Software Foundation; either version 2 + of the License, or (at your option) any later version. + + This program is distributed in the hope that it will be useful, + but WITHOUT ANY WARRANTY; without even the implied warranty of + MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the + GNU General Public License for more details. + + You should have received a copy of the GNU General Public + License along with this library; if not, write to the Free Software + Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301 USA +*/ + +:- module(mo, [ + load_chord_symbols/0 + , load_chord_symbols_on/1 + , has_title/2 + , timeline/1 + , interval_on/2 + , event_on/2 + , event_time/2 + , event_chord/2 + , sorted_events_on/2 + , sorted_timed_events/2 + , timeline_event_terms/2 + , timed_event_term/2 + , interval_term/2 + , chord_term/2 + , note_term/2 + ]). + +:- use_module(library(semweb/rdf_db)). +:- use_module(library(semweb/rdf_http_plugin)). +:- use_module(library(apply_macros)). + +load_chord_symbols :- + setof(C,A^rdf(A,chord:chord,C),Chords), + rdf_load(Chords). + +load_chord_symbols_on(TL) :- + setof(C,E^I^(interval_on(I,TL),event_time(E,I),event_chord(E,C)),Chords), + rdf_load(Chords). + +has_title(TL,Tit) :- rdf(TL,dc:title,Tit). + +timeline(TL) :- rdf(TL,rdf:type,tl:'TimeLine'). +interval_on(I,TL) :- rdf(I,tl:onTimeLine, TL). +event_time(E,T) :- rdf(E,event:time,T). +event_on(E,TL) :- interval_on(I,TL), event_time(E,I). + +interval_ends(I,T1) :- + rdf(I,tl:endsAtDuration,literal(AT1)), + decode_duration(AT1,T1). + +interval_starts(I,T1) :- + rdf(I,tl:beginsAtDuration,literal(AT1)), + decode_duration(AT1,T1). + +decode_duration(A,T) :- sub_atom(A,1,_,1,B), atom_number(B,T). + +sorted_events_on(TL,Events) :- + sorted_timed_events(TL,STE), + maplist(strip_key,STE,Events). + +sorted_timed_events(TL,Events) :- + findall(interval(T1,T2)-E, ( + interval_on(I,TL), + interval_starts(I,T1), + interval_ends(I,T2), + event_time(E,I) + ),TE), + keysort(TE,Events). + +strip_key(_-E,E). +event_chord(E,C) :- rdf(E,chord:chord,C). + +timed_event_term(interval(T1,T2)-Event, event(T1,Dur,ChordTerm)) :- + Dur is T2-T1, + event_chord(Event,Chord), + chord_term(Chord,ChordTerm). + + +user:term_expansion(note_mapping(A,B),note_mapping(AA,B)) :- rdf_global_id(A,AA). +user:term_expansion(modified(A,B,C),modified(AA,B,C)) :- rdf_global_id(A,AA). + +:- rdf_meta note_term(r,?). +:- rdf_meta chord_term(r,?). +:- rdf_meta modified(r,?,?). + + +% represent a chord algebraically as a Prolog term +chord_term(Chord,Term) :- chord_term_semidet(Chord,T) -> Term=T; Term=no_chord. + +chord_term_semidet(Chord,chord(Root,Bass,Intervals)) :- + rdf(Chord,chord:root,R), + note_term(R,Root), + (rdf(Chord,chord:bass,B)->interval_term(B,Bass);Bass=1), + setof(I,rdf(Chord,chord:interval,I),IX), + maplist(interval_term,IX,Intervals). + +note_term(Note,N) :- note_mapping(Note,N). +note_term(Note,MN) :- + rdf(Note,chord:natural, Nat), note_term(Nat,N), + rdf(Note,chord:modifier, Mod), modified(Mod,N,MN). + +modified(chord:flat, N, flat(N)). +modified(chord:doubleflat, N, flat(flat(N))). +modified(chord:sharp, N, sharp(N)). +modified(chord:doublesharp, N, sharp(sharp(N))). + +note_mapping(chord:'note/A',a). +note_mapping(chord:'note/B',b). +note_mapping(chord:'note/C',c). +note_mapping(chord:'note/D',d). +note_mapping(chord:'note/E',e). +note_mapping(chord:'note/F',f). +note_mapping(chord:'note/G',g). + +interval_term(Interval,Term) :- + rdf(Interval,chord:degree,D), D=literal(type(_,DA)), atom_number(DA,Deg), + ( rdf(Interval,chord:modifier,Mod) + -> modified(Mod,Deg,Term) + ; Term=Deg + ). + +timeline_event_terms(TL,Terms) :- + sorted_timed_events(TL,Events), + maplist(timed_event_term,Events,Terms). +