Did you know ... Search Documentation:
Pack plumdrum -- prolog/humdrum/kern_rules.pl
PublicShow source

Usage

This module is designed to be called from a module containing a database describing a humdrum object, which may be created from a Humdrum file by using assert_humdrum/3 in humdrum_world.pl

The following predicates must be defined in the calling module.

        spine/4          % spine( xinterp, spine, record, record).
        ref/3            % ref(refcode, lang, text).
        duration/1       % duration( duration).
        num_spines/1     % num_spines( natural).
        num_records/1    % num_records( natural).

        time/2           % time( time, record).
        duration/2       % duration( duration, record).
        new_spine/2      % new_spine( spine, record).
        init_spine/3     % init_spine( xinterp, spine, record).
        change_spine/5   % change_spine( xinterp, xinterp, spine, spine, record).
        term_spine/3     % term_spine( xinterp, spine, record).
        join_spines/4    % join_spines( spine, spine, spine, record).
        split_spines/4   % split_spines( spine, spine, spine, record).

        interp/3         % interp( interp, spine, record).
        data/3           % data( data, spine, record).

Performance interpretation

dynamics

  • p, f, mp, mf etc - static level
  • crescendo, diminuendo - dynamic process
  • sforzando - loud then quiet
  • subito - suddenly phrasing, compound events
  • tied notes
  • slur (open, close)
  • phrase (open, close)
  • glissando (open, close)
  • elision? articulation
  • staccato
  • spiccato
  • pizzicato
  • attacca
  • tenuto
  • accent
  • harmonic
  • sordino
  • sforzando
  • up_bow
  • down_bow
  • arpeggio
  • generic
  • pause
  • breath ornament(_)
  • trill(whole)
  • trill(semi)
    Check date of composition. If before 1800, start on pitch above and trill \/\/\/\ If after 1800, start on notated pitch /\/\/\/ Speed?
  • mordent(whole) /\___
  • mordent(semi) /\___
  • inv_mordent(whole) \/---
  • inv_mordent(semi) \/--- Speed?
  • turn \\/
  • wagnerian_turn
  • ending_turn
  • generic grace(_)
  • acciaccutura - does not steal time, very short, just before ot on the beat
  • appoggiatura - steal time from next note (post_appoggiatura?)
  • groupetto
  • post_appoggiatura

TODO (these are from the kern player - what are they doing here?)

  • slurs, glissandi, phrasing (using supercollider?)
  • grace notes, groupettos etc.
  • elided phrases and slurs
  • expansion lists
  • live intervention
  • trail stack and local stack size growth
 spine(+S:spine, +R:record) is semidet
spine(-S:spine, -R:record) is nondet
True if spine S exists at record R. Enumerates all spines at all records on backtracking.
 spine(+S:spine) is semidet
spine(-S:spine) is nondet
True if spine S exists anywhere in the current database. Enumerates all spines on backtracking.
 all_spines(P:pred(spine,record), +R:record) is semidet
all_spines(P:pred(spine,record), -R:record) is nondet
True if P is true for all spines of record R.
 colinear(+S1:spine, +S2:spine) is semidet
colinear(+S1:spine, -S2:spine) is nondet
Succeeds if S2 is either the same spine as S1 or can be reached going forward in time via splits, joins, or representation changes.
 next_spine(-S1:spine, -S2:spine) is nondet
True if spine S1 evolves into S2 without any intervening spines.
 fwd(+Pos:position, -Pos:position) is nondet
Step forwards one record following current spine.
position ---> (spine,record).
 xinterp(-X:xinterp, +S:spine, +R:record) is semidet
xinterp(-X:xinterp, -S:spine, -R:record) is nondet
True if X is the exclusive interpretation for spine S which must exists at record R.
 interp(-S:spine, -R:record) is nondet
True if record R is an interpretation record and S is a spine that exists at record R.
 barline(-B:bar_attr, +S:spine, +R:record) is semidet
barline(-B:bar_attr, -S:spine, -R:record) is nondet
True if spine S at record R is a bar line with attributes B.
 barlines(-B:bar_attr, +R:record) is semidet
barlines(-B:bar_attr, -R:record) is nondet
True if all spines at record R are bar lines with attributes B.
 articulation(-A:artic, +S:spine, +R:record) is semidet
articulation(-A:artic, -S:spine, -R:record) is nondet
True if spine S at record R includes articulation marking A.
 tempo(-T:nonneg, +R:record) is semidet
tempo(-T:nonneg, -R:record) is nondet
True if all spines at record R are metronome interpretations with tempo T beats per second.
 barline(+S:spine, +R:record) is semidet
barline(-S:spine, -R:record) is nondet
True if spine S at record R is a bar line.
 data(+S:spine, +R:record) is semidet
data(-S:spine, -R:record) is nondet
True if spine S at record R is a data token.
 note(-P:kern_note, -D:duration, -T:time, -S:spine) is nondet
True if a note with pitch P and duration D is initiated at time T in spine S. This also applies to tied notes which may continue in the same spine or a colinear spine. If a tied note continues in a non-colinear spine, a warning is printed.
See also
- colinear/2
 kern_note(-P:kern_note, -D:duration, -T:tie, -S:spine, -R:record) is nondet
True if data token at spine S in record R is a kern note with pitch P and duration D. T indicates whether the note is part of a tie as follows:
kern_note ---> rest; pitch(pitch).

tie ---> not_tied   % atomic note, not part of a tie
       ; open       % onset of tied note
       ; cont       % continuation of tied note
       ; close      % final segment of tied note
       .
 data_token(+D:data, -T:token) is nondet
True when T is a token or subtoken in the given data term.
 metre_to_bar_duration(+M:metre, -D:duration) is det
Compute duration in whole notes of a bar in the given metre.
 time(-Time:rational, +Loc:spine_rec, -Loc:spine_rec) is det
 token(-Token, +Loc:spine_rec, -Loc:spine_rec) is det