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(kerndata, Daniel@0: [ uri_spine_pitches/3 Daniel@0: , uri_spine_events/4 Daniel@0: , uri_opus/2 Daniel@0: , events_nth_phrase/3 Daniel@0: , dataset_size/2 Daniel@0: , dataset_items/2 Daniel@0: , dataset_sequences/2 Daniel@0: , dataset_random_subsets/4 Daniel@0: , item_sequence/2 Daniel@0: , item_opus/2 Daniel@0: , item_uri/2 Daniel@0: , metpos/4 Daniel@0: , with_kern_module/3 Daniel@0: , fileset/1 Daniel@0: ]). Daniel@0: Daniel@0: /** Managings sets of Kern scores Daniel@0: Daniel@0: This module provides tools for defining and working with sets of musical Daniel@0: fragments extracted from Humdrum/Kern scores. Sets of files are defined by Daniel@0: searches in the RDF database. Then, a small language of operations can be Daniel@0: used to extract given spines and/or break melodic sequences into phrases. Daniel@0: Daniel@0: A named fileset is a term (the name) associated with a file set specification. Daniel@0: A fileset specification is a nondeterministic binary predicate which yields Daniel@0: both a Humdrum file URI and a spine number. An alternative way to refer to a Daniel@0: file set is anonymously, as a term \Spec. A fileset, then is either a named Daniel@0: fileset or an anonymous fileset: Daniel@0: == Daniel@0: anonymous_filset ---> \fileset_spec. Daniel@0: fileset_spec == pred(-uri, -spine_spec). Daniel@0: named_fileset == term. Daniel@0: fileset == named_fileset | anonymous_fileset. Daniel@0: spine == natural. % {1,2,...} Daniel@0: Daniel@0: spine_spec ---> extract(spine) Daniel@0: ; trace(spine) Daniel@0: ; merge Daniel@0: ; all. Daniel@0: == Daniel@0: Named filesets are defined using the multifile predicate fileset/2. Daniel@0: Daniel@0: Some predicates are available for convenient construction of fileset_specs: Daniel@0: == Daniel@0: with_spine( +S:spine, +Finder:pred(-uri), -URI:uri, -S:spine_spec) is nondet. Daniel@0: trace_spine( +S:spine, +Finder:pred(-uri), -URI:uri, -S:spine_spec) is nondet. Daniel@0: merge_spines( +Finder:pred(-uri), -URI:uri, -S:spine_spec) is nondet. Daniel@0: all_spines( +Finder:pred(-uri), -URI:uri, -S:spine_spec) is nondet. Daniel@0: Daniel@0: kern_uri( +FS:find_spec, -URI:uri) is nondet. Daniel@0: Daniel@0: find_spec ---> (find_spec ; find_spec) % set union Daniel@0: ; (find_spec , find_spec) % set intersection Daniel@0: ; under(path) % recursive directory search Daniel@0: ; in(path) % single directory search Daniel@0: ; uri=object. % match on RDF property Daniel@0: Daniel@0: path == atom. % a path relative to root of Humdrum file library. Daniel@0: object == uri | literal | literal_search_spec. Daniel@0: Daniel@0: literal == { lang(atom,atom), type(uri,atom) } | atom. Daniel@0: literal_search_spec ---> literal(literal_query,atom). Daniel@0: literal_query ---> plain(atom) Daniel@0: ; exact(atom) Daniel@0: ; substring(atom) Daniel@0: ; word(atom) Daniel@0: ; prefix(atom) Daniel@0: ; ge(atom) Daniel@0: ; le(atom) Daniel@0: ; between(atom,atom) Daniel@0: ; like(atom). Daniel@0: == Daniel@0: Thus, as a fileset_spec, the term =|with_spine(S,Finder)|= yields the Sth spine Daniel@0: of each URI produced by Finder. =|all_spines(Finder)|= yields all spines of each file Daniel@0: produced by Finder. See rdf/3 for more information about literal query terms. Daniel@0: Daniel@0: Datasets are defined in terms of filesets: Daniel@0: == Daniel@0: fileset :< dataset. % any fileset is also a dataset: each member yields one sequence Daniel@0: phrases(fileset) :< dataset. % denotes the set of phrases segmented from fileset. Daniel@0: extract(DS:dataset, Size:nonneg, Offset:nonneg) :: dataset. Daniel@0: subset(DS:dataset, Size:nonneg, Indices:list(nonneg)) :: dataset. Daniel@0: subset_ref(DS:dataset, Size:nonneg, SubsetRef:atom) :: dataset. Daniel@0: null :: dataset. Daniel@0: == Daniel@0: Daniel@0: Each item in a dataset is represented by a term of the following type: Daniel@0: == Daniel@0: dataset_item ---> whole(uri,spine) % Humdrum URI and spine number Daniel@0: ; phrase(uri,spine,natural). % URI, spine and phrase number Daniel@0: ; merged(uri). % all spines, highest note of chords Daniel@0: == Daniel@0: Items can be obtained using dataset_items/2. Daniel@0: Each item corresponds to a list of note numbers, which can be obtained using Daniel@0: item_sequence/2, or dataset_sequences/2. Daniel@0: Daniel@0: */ Daniel@0: Daniel@0: :- meta_predicate with_kern_module(+,-,0). Daniel@0: Daniel@0: :- use_module(library(memo)). Daniel@0: :- use_module(library(dcg_core)). Daniel@0: :- use_module(library(snobol)). Daniel@0: :- use_module(library(listutils)). Daniel@0: :- use_module(library(fileutils)). Daniel@0: :- use_module(library(termutils)). Daniel@0: :- use_module(library(insist)). Daniel@0: :- use_module(library(humdrum)). Daniel@0: :- use_module(library(humdrum/kern)). Daniel@0: :- use_module(library(humdrum/dynam)). Daniel@0: :- use_module(library(humdrum/humdrum_world)). Daniel@0: :- use_module(library(humdrum/kernutils)). Daniel@0: :- use_module(library(lambda)). Daniel@0: :- use_module(library(semweb/rdf_db)). Daniel@0: :- use_module(library(humdrum_p2r), [hum_uri_path/2]). Daniel@0: :- use_module(library(dataset), [random_subset/4]). Daniel@0: Daniel@0: :- set_prolog_flag(double_quotes, codes). Daniel@0: :- initialization memo_attach(memo(kerndata),[]). Daniel@0: Daniel@0: :- dynamic item_sequence/2. Daniel@0: :- multifile fileset/2. Daniel@0: Daniel@0: %% fileset(-FS:named_fileset) is nondet. Daniel@0: % True when FS identifies an explicitly declared Kern file-set. Daniel@0: fileset(FS) :- fileset(FS,Spec), FS \= \Spec. Daniel@0: Daniel@0: %% fileset(+FS:named_fileset, -Spec:fileset_spec) is semidet. Daniel@0: %% fileset(-FS:named_fileset, -Spec:fileset_spec) is nondet. Daniel@0: % Daniel@0: % Database of named filesets and their fileset specifiers. Daniel@0: fileset(lorraine, with_spine(1,kern_uri(in('lorraine')))). Daniel@0: fileset(nova_scotia, with_spine(1,kern_uri(in('classical/songs/unaccompanied/nova-scotia/kern')))). Daniel@0: fileset(ireland, with_spine(1,kern_uri(in('ireland')))). Daniel@0: fileset(chorales, with_spine(1,kern_uri(in('classical/bach/chorales')))). Daniel@0: fileset(chorales371, with_spine(4,kern_uri(in('classical/bach/371chorales')))). Daniel@0: fileset(bach_cello, with_spec(merge,kern_uri(in('classical/bach/cello')))). Daniel@0: fileset(bach_violin, with_spec(merge,kern_uri(in('classical/bach/violin')))). Daniel@0: fileset(beethoven_quartets, all_spines(kern_uri(in('classical/beethoven/quartet')))). Daniel@0: fileset(essen, with_spine(1,kern_uri(under('essen/europe')))). Daniel@0: fileset(essen(china),with_spine(1,kern_uri(under('essen/china')))). Daniel@0: fileset(essen(Rgn), with_spine(1,kern_uri(under(Dir)))) :- Daniel@0: member(Rgn,[germany,rossiya,magyar,elsass,lothring,nederlan,schweiz,oesterrh,jugoslav]), Daniel@0: atom_concat('essen/europe/',Rgn,Dir). Daniel@0: fileset(essen(germany,Sub), with_spine(1,kern_uri(under(Dir)))) :- Daniel@0: member(Sub,[dva,allerkbd,kinder,altdeu1,altdeu2,fink,zuccal,ballad,boehme,erk]), Daniel@0: atom_concat('essen/europe/germany/',Sub,Dir). Daniel@0: Daniel@0: Daniel@0: %% uri_opus(+URI:uri,-Opus:atom) is semidet. Daniel@0: %% uri_opus(-URI:uri,-Opus:atom) is nondet. Daniel@0: % Relation between Humdrum file URIs and their Humdrum SCT property. Daniel@0: uri_opus(URI,Opus) :- rdf(URI,hum:'refcode/SCT',literal(Opus)). Daniel@0: Daniel@0: % :- volatile_memo file_opus( +file:atom, -opus:atom). Daniel@0: % file_opus(File,Opus) :- Daniel@0: % with_kern_module(File, utf8, Mod, (Mod:ref('SCT',_,Opus) -> true; Opus=unknown(_))). Daniel@0: Daniel@0: %% item_opus(+Item:dataset_item, -Opus:atom) is semidet. Daniel@0: % Relation between a dataset item and the opus of its associated Humdrum file. Daniel@0: item_opus(Item,Opus) :- item_uri(Item,URI), uri_opus(URI,Opus). Daniel@0: Daniel@0: %% item_uri(+Item:dataset_item, -URI:uri) is semidet. Daniel@0: % Relation between a dataset item and the URI of its associated Humdrum file. Daniel@0: item_uri(phrase(URI,_,_),URI). Daniel@0: item_uri(whole(URI,_),URI). Daniel@0: item_uri(merged(URI),URI). Daniel@0: Daniel@0: Daniel@0: %% dataset_size(+DS:dataset, -N:nonneg) is det. Daniel@0: % Get the size of a given dataset. This predicate is persistently memoised, Daniel@0: % since computing the size of a large dataset may involve reading many Humdrum Daniel@0: % files. Daniel@0: Daniel@0: :- persistent_memo dataset_size( +ground, -nonneg). Daniel@0: Daniel@0: dataset_size(Dataset,NumItems) :- Daniel@0: eval_dataset(Dataset,Items), Daniel@0: length(Items,NumItems). Daniel@0: Daniel@0: %% dataset_items(+DS:dataset, -S:list(dataset_item)) is det. Daniel@0: dataset_items(DS,Items) :- eval_dataset(DS,Items). Daniel@0: Daniel@0: %% dataset_sequences(+DS:dataset, -S:list(list(integer))) is det. Daniel@0: dataset_sequences(DS,SS) :- Daniel@0: dataset_items(DS,Items), Daniel@0: maplist(item_sequence,Items,SS). Daniel@0: Daniel@0: %% eval_dataset(+DS:dataset, -Items:list(dataset_item)) is det. Daniel@0: eval_dataset(DS,_) :- must_be(ground,DS), fail. Daniel@0: eval_dataset(extract(DS,N,I), D2) :- !, Daniel@0: eval_dataset(DS, D1), Daniel@0: drop(I, D1, D3), Daniel@0: take(N, D3, D2). Daniel@0: Daniel@0: eval_dataset(subset_ref(DS,N,Ref), D2) :- !, Daniel@0: dataset_size(DS,Size), Daniel@0: random_subset(Size,N,Ref,IX), Daniel@0: eval_dataset(subset(DS,N,IX), D2). Daniel@0: Daniel@0: eval_dataset(subset(DS,N,IX), D2) :- !, Daniel@0: eval_dataset(DS, D1), Daniel@0: length(IX,N), Daniel@0: maplist(\I^X^nth1(I,D1,X), IX, D2). Daniel@0: Daniel@0: eval_dataset(null,[]). Daniel@0: eval_dataset(DS,Items) :- Daniel@0: fileset_items(DS,Items). Daniel@0: Daniel@0: :- thread_local item_/1. Daniel@0: :- volatile_memo fileset_items( +ds:ground, -items:list(ground)). Daniel@0: %% fileset_items(+FS, -Items:list(dataset_item)) is det. Daniel@0: % FS can be a fileset or a term =|phrases(Fileset)|=, denoting the set of Daniel@0: % sequence resulting from segmenting each item in Fileset into phrases. Daniel@0: fileset_items(DS, Items) :- Daniel@0: setup_call_cleanup( Daniel@0: load(DS), Daniel@0: findall(Item,item_(Item),Items), Daniel@0: retractall(item_(_))), Daniel@0: insist(Items\=[]). Daniel@0: Daniel@0: load(phrases(FS)) :- fileset(FS,Spec), forall_kern(Spec,assert_phrases). Daniel@0: load(FS) :- fileset(FS,Spec), forall_kern(Spec,assert_whole). Daniel@0: Daniel@0: %% item_sequence(+Item:dataset_item, -Seq:list(integer)) is det. Daniel@0: % True when Seq is the list of note numbers for a given item. Daniel@0: Daniel@0: %% spine_nth_phrase(+Mod:module,+S:spine,-N:natural,-P:list(integer)) is nondet. Daniel@0: % Daniel@0: % True when P is the list of note numbers in the Nth phrase on spine S in the Daniel@0: % Humdrum file represented in module Mod. Phrases can be defined in two ways: Daniel@0: % 1. Using explicit Kern phrase marks Daniel@0: % 2. Using notes annotated with a pause mark to determine phrase endings. Daniel@0: spine_nth_phrase(Mod,Spine,N,Phrase) :- Daniel@0: Mod:spine(Spine), Daniel@0: ( once(spine_phrase(Mod,Spine,_,_)) Daniel@0: -> % spine has explicit phrases markings Daniel@0: kern_get_events(event_or_delim(spine_notenum,Mod,Spine), Events), Daniel@0: pairs_values(Events,Events1), Daniel@0: bagof(NNs, L^phrase(contains_group(L,NNs),Events1), Phrases), Daniel@0: nth1(N,Phrases,Phrase) Daniel@0: ; % no phrase markings - use pauses Daniel@0: kern_get_events(event_or_pause(spine_notenum,Mod,Spine), Events), Daniel@0: events_nth_phrase(Events, N, Phrase) Daniel@0: ). Daniel@0: Daniel@0: assert_whole(URI,Mod,Spec) :- Daniel@0: (Spec=extract(Spine); Spec=all), Daniel@0: forall( kern_get_events(spine_notenum(Mod,Spine), Events), Daniel@0: ( assert_id(item_sequence(whole(URI,Spine), Events)), Daniel@0: assert(item_(whole(URI,Spine))))). Daniel@0: Daniel@0: assert_whole(URI,Mod,merge) :- Daniel@0: forall( kern_get_events(top_notenum(Mod), Events), Daniel@0: ( assert_id(item_sequence(merged(URI), Events)), Daniel@0: assert(item_(merged(URI))))). Daniel@0: Daniel@0: assert_phrases(URI,Mod,Spec) :- Daniel@0: (Spec=extract(Spine); Spec=all), Daniel@0: forall( spine_nth_phrase(Mod,Spine,N,Phrase), Daniel@0: ( assert_id(item_sequence(phrase(URI,Spine,N), Phrase)), Daniel@0: assert(item_(phrase(URI,Spine,N))))). Daniel@0: Daniel@0: assert_id(Fact) :- call(Fact) -> true; assert(Fact). Daniel@0: Daniel@0: Daniel@0: contains_group(D,XX) --> arb, group(D,XX,[]), rem. Daniel@0: Daniel@0: group(D,X1,X2) --> Daniel@0: delimiter(D,open), Daniel@0: iterate(content(D),X1,X2), Daniel@0: delimiter(D,close). Daniel@0: Daniel@0: content(_,[X|XX],XX) --> [event(X)]. Daniel@0: content(D,XX,XX) --> {dif(D,D1)}, delimiter(D1,_). Daniel@0: content(D,X1,X2) --> group(D,X1,X2). Daniel@0: delimiter(D,T) --> [T/D]. Daniel@0: Daniel@0: Daniel@0: %% dataset_random_subsets(+DS:dataset,+K:nonneg,+L:nonneg,-DSX:list(dataset)) is det. Daniel@0: % Daniel@0: % Returns L random subsets of K sequences each from dataset DS. Daniel@0: % K is the size of each random subset. L is the number of subsets Daniel@0: % returned. Each subset is a term of the form =|subset(DS,K,Indices)|=. Daniel@0: dataset_random_subsets(DS,K,L,DSX) :- Daniel@0: dataset_size(DS,N), Daniel@0: numlist(1,L,SubsetIndices), Daniel@0: maplist(\I^subset(DS,K,S)^random_subset(N,K,I,S),SubsetIndices,DSX). Daniel@0: Daniel@0: Daniel@0: %% uri_spine_pitches(+URI:uri,+S:nonneg,-P:list(pitch)) is det. Daniel@0: %% uri_spine_pitches(+URI:uri,-S:nonneg,-P:list(pitch)) is nondet. Daniel@0: % Daniel@0: % True when Pis a list of the pitches of notes in a spine S Daniel@0: % of the Humdrum file pointed to by URI. Daniel@0: uri_spine_pitches(URI,Spine,Pitches) :- Daniel@0: with_kern_module(URI, Mod, Daniel@0: kern_get_events(spine_pitch(Mod,Spine), Pitches)). Daniel@0: Daniel@0: %% uri_spine_events(+URI:uri,+G:getter,+S:spine,-E:list(event(A))) is det. Daniel@0: %% uri_spine_events(+URI:uri,+G:getter,-S:spine,-E:list(event(A))) is nondet. Daniel@0: % Daniel@0: % Get list of events from a given spine in a Humdrum file. The kind of events extracted Daniel@0: % depends on the getter predicate G, which must be of type: Daniel@0: % == Daniel@0: % getter(A) == pred(+M:module,-S:spine,-T:time,-E:event(A)). Daniel@0: % event(A) ---> event(A) ; pause. Daniel@0: % == Daniel@0: Daniel@0: uri_spine_events(URI,Getter,Spine,Events) :- Daniel@0: with_kern_module(URI, Mod, Daniel@0: kern_get_events(event_or_pause(Getter,Mod,Spine), Events)). Daniel@0: Daniel@0: :- meta_predicate forall_kern(2,3). Daniel@0: forall_kern(Findspec,Pred) :- Daniel@0: with_status_line( Daniel@0: forall( call(Findspec,URI,SpineSpec), ( Daniel@0: status('Loading: ~s',[URI]), Daniel@0: with_kern_module(URI, Mod, call(Pred,URI,Mod,SpineSpec)) Daniel@0: ))), Daniel@0: format('Finished loading.\n',[]). Daniel@0: Daniel@0: %% with_kern_module(+URI:uri, -M:module, +Goal:pred) is nondet. Daniel@0: % Daniel@0: % Calls Goal with M set to the name of a temporary moduling containing Daniel@0: % the information in the Kern file specified by URI. Daniel@0: with_kern_module(URI,Mod,Goal) :- Daniel@0: hum_uri_path(URI,Path), Daniel@0: with_kern_module(Path,utf8,Mod,Goal). Daniel@0: Daniel@0: :- meta_predicate with_spine(+,1,-,-). Daniel@0: with_spine(Spine,Finder,URI,extract(Spine)) :- call(Finder,URI). Daniel@0: Daniel@0: :- meta_predicate all_spines(+,-,-). Daniel@0: all_spines(Finder,URI,all) :- call(Finder,URI). Daniel@0: Daniel@0: :- meta_predicate with_spec(+,+,-,-). Daniel@0: with_spec(SpineSpec,Finder,URI,SpineSpec) :- call(Finder,URI). Daniel@0: Daniel@0: %% kern_uri(+FS:find_spec, -URI:uri) is nondet. Daniel@0: % Daniel@0: % True when URI refers to a Humdrum file that satisfies the given Daniel@0: % specification. The specification type =|find_spec|= is defined in the Daniel@0: % module header comment. Daniel@0: kern_uri(in(Dir),URI) :- rdf(URI,hum:directory,literal(Dir)). Daniel@0: kern_uri(under(Dir),URI) :- rdf(URI,hum:directory,literal(prefix(Dir),_)). Daniel@0: kern_uri(A;B, URI) :- kern_uri(A,URI); kern_uri(B,URI). Daniel@0: kern_uri((A,B), URI) :- kern_uri(A,URI), kern_uri(B,URI). Daniel@0: kern_uri(Prop=Val,URI) :- rdf(URI,Prop,Val). Daniel@0: Daniel@0: %% spine_pitch(+Mod:module,-Spine:nonneg,-Time,-Pitch) is nondet. Daniel@0: spine_pitch(Mod,Spine,Time,P) :- Daniel@0: Mod:note(pitch(P),_,Time,Spine). Daniel@0: Daniel@0: spine_pitch_dur(Mod,Spine,Time,P-D) :- Daniel@0: Mod:note(pitch(P),D,Time,Spine). Daniel@0: Daniel@0: spine_notenum(Mod,Spine,Time,NN) :- Daniel@0: spine_pitch(Mod,Spine,Time,Pitch), Daniel@0: pitch_notenum(Pitch,NN). Daniel@0: Daniel@0: Daniel@0: %% get the highest pitch over all spines at each time slice. Daniel@0: top_notenum(Mod,Time,TopNN) :- Daniel@0: aggregate(max(NN),time_notenum(Mod,Time,NN),TopNN). Daniel@0: Daniel@0: time_notenum(Mod,Time,NN) :- Daniel@0: Mod:note(pitch(P),_,Time,_), Daniel@0: pitch_notenum(P,NN). Daniel@0: Daniel@0: spine_pause(Mod,Spine,Time,pause) :- spine_pause(Mod,Spine,Time). Daniel@0: spine_pause(Mod,Spine,Time) :- Daniel@0: Mod:articulation(pause,Spine,Rec), Daniel@0: Mod:time(T,Rec), Daniel@0: Mod:duration(D,Rec), Daniel@0: Time is T+D. Daniel@0: Daniel@0: spine_phrase(Mod,Spine,Time,Time-(OpenClose/Label)) :- Daniel@0: Mod:data(tok(Toks),Spine,Rec), Daniel@0: member(par(OpenClose,phrase-Label),Toks), Daniel@0: Mod:time(T,Rec), Daniel@0: ( OpenClose=open -> Time=T Daniel@0: ; OpenClose=close -> Mod:duration(D,Rec), Time is T+D Daniel@0: ). Daniel@0: Daniel@0: Daniel@0: twos(L) :- L=[2|L]. Daniel@0: Daniel@0: metre(4/4,1:M) :- twos(M). Daniel@0: metre(3/4,(3 rdiv 4):[3,2|M]) :- twos(M). Daniel@0: metre(6/8,(3 rdiv 4):[2,3|M]) :- twos(M). Daniel@0: metre(9/8,(9 rdiv 8):[3,3|M]) :- twos(M). Daniel@0: metre(12/8,(12 rdiv 8):[2,2,3|M]) :- twos(M). Daniel@0: Daniel@0: %% metpos( +Bar:rational, +Metre:list(nat), +T0:rational, -R:nat) is det. Daniel@0: metpos(Bar,Metre,TT,R) :- metpos_(TT,[1/Bar|Metre],0,R). Daniel@0: Daniel@0: metpos_(0,_,R,R) :- !. Daniel@0: metpos_(T0,[M0|MX],R0,R) :- Daniel@0: mod1(T0*M0,T1), succ(R0,R1), Daniel@0: metpos_(T1,MX,R1,R). Daniel@0: Daniel@0: mod1(X,Y) :- Z is floor(X), Y is X - Z. Daniel@0: Daniel@0: event_or_pause(Pred,Mod,Spine,Time,event(X)) :- call(Pred,Mod,Spine,Time,X). Daniel@0: event_or_pause(_,Mod,Spine,Time,pause) :- spine_pause(Mod,Spine,Time). Daniel@0: Daniel@0: event_or_delim(Pred,Mod,Spine,Time,2-event(X)) :- Daniel@0: call(Pred,Mod,Spine,Time,X). Daniel@0: event_or_delim(_,Mod,Spine,Time,Prio-Delim) :- Daniel@0: spine_phrase(Mod,Spine,Time,_-Delim), Daniel@0: delim_prio(Delim,Prio). Daniel@0: Daniel@0: delim_prio(open/_,1). Daniel@0: delim_prio(close/_,1). Daniel@0: Daniel@0: %% events_nth_phrase(+Events:list(event(A)), +N:natural, -P:list(A)) is det. Daniel@0: % Extract Nth phrase from a list of events or pauses. Daniel@0: events_nth_phrase(Events,N,Phrase) :- Daniel@0: phrase((seqmap_with_sep([pause],seqmap(event),Phrases), opt([pause])),Events,[]), Daniel@0: nth1(N,Phrases,Phrase). Daniel@0: Daniel@0: event(X) --> [event(X)].