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