18
19:- module(dynam, []).
52:- use_module(library(dcg_core)). 53:- use_module(library(dcg_macros)). 54:- use_module(library(humdrum)). 55:- use_module(library(humdrum/humutils)). 56
57:- set_prolog_flag(double_quotes,codes). 58
59humdrum:hum_data_hook(dynam,Sigs) --> !, seqmap(dynam,Sigs).
60humdrum:hum_data_hook(db,DB) --> !, float(DB).
61
62dynam(st(f(N))) --> "f", !, rep_shared(M,"f"), {succ(M,N)}.
63dynam(st(p(N))) --> "p", !, rep_shared(M,"p"), {succ(M,N)}.
64dynam(st(mf)) --> "mf".
65dynam(st(mp)) --> "mp".
66
67dynam(rest) --> "r".
68dynam(accent) --> "v".
69dynam(subito) --> "s".
70dynam(sforz) --> "z".
71
72dynam(ed(explicit)) --> "X".
73dynam(ed(published)) --> "x".
74
75dynam(dy(begin,crescendo)) --> "<".
76dynam(dy(cont,crescendo)) --> "(".
77dynam(dy(end,crescendo)) --> "[".
78dynam(dy(begin,diminuendo)) --> ">".
79dynam(dy(cont,diminuendo)) --> ")".
80dynam(dy(end,diminuendo)) --> "]"
dynam spine format for Humdrum
This module provides the humdrum hook predicate hum_data_hook//2 to enable parsing of the dynam and db spine type.
The dynam interpretation provides the following data term type:
The db interpretation simply produces floating point numbers encoding loudness in decibels.
*/