1/* Part of plumdrum
    2	Copyright 2012-2015 Samer Abdallah (Queen Mary University of London; UCL)
    3	 
    4	This program is free software; you can redistribute it and/or
    5	modify it under the terms of the GNU Lesser General Public License
    6	as published by the Free Software Foundation; either version 2
    7	of the License, or (at your option) any later version.
    8
    9	This program is distributed in the hope that it will be useful,
   10	but WITHOUT ANY WARRANTY; without even the implied warranty of
   11	MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
   12	GNU Lesser General Public License for more details.
   13
   14	You should have received a copy of the GNU Lesser General Public
   15	License along with this library; if not, write to the Free Software
   16	Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA  02110-1301  USA
   17*/
   18
   19:- module(interps,[]).

Hooks for parsing Humdrum spine interpretations

This module defines the hook predicate hum_interp_hook//1 for recognising when a Humdrum spine contains interpretation data.

It currently produces interpretation terms with the following type:

interp ---> section(secname)
          ; section(atom,atom)
          ; explist(list(atom))
          ; explist(atom,list(atom))
          ; tb(natural)               % timebase
          ; metre(natural,natural)    % metre num and denom
          ; metro(float)              % metronome
          ; metro(range(float))       % metronome range
          ; tempo(atom)               % tempo marking (verbal)
          ; staff(list(natural))      % staff number
          ; clef(atom)                % clef type name
          ; instr(atom)               % instrument name
          ; igroup(atom)              % instrument group
          ; iclass(atom)              % instrument class
          ; keysig(list(pitch_class)) % key signature
          ; key(pitch_class,mode)     % key as major/minor
          ; trans                     % transposed?
          .

range(A) ---> A--A.

See humutils.pl for definition of pitch_class type. */

   52:- use_module(library(dcg_core)).   53:- use_module(library(dcg_codes)).   54:- use_module(library(dcg_macros)).   55:- use_module(library(humdrum/humutils)).   56:- op(550,xfx,--).   57
   58:- set_prolog_flag(double_quotes,codes).   59% ------------- standard interpretations -------------
   60
   61
   62% tandem interpretations
   63% kern, solfg, pc, mint: M metre
   64% kern, solfg, degree, pc, mint : k[...] key signature
   65% kern, solfg, degree, pc, mint :<note>: key
   66% kern, solfg, pc: MM tempo
   67% pc: tb timebase
   68% > sectioning
   69% specC: *pure, *complex
   70% *H harmonic number
   71
   72humdrum:hum_interp_hook(Term) --> interp(Term).
   73
   74
   75
   76secname(A) --> atom_chars_ex(text,"",">[,",A).
   77
   78% sectioning
   79interp(section(A))   --> ">", secname(A).
   80interp(section(B,A)) --> ">", secname(B), ">", secname(A).
   81interp(explist(A))   --> ">", sqbr(seqmap_with_sep(",",secname,A)).
   82interp(explist(B,A)) --> ">", secname(B), sqbr(seqmap_with_sep(",",secname,A)).
   83
   84% timing
   85interp(tb(R))        --> "tb", nat(R). % time base
   86interp(metre(N,D))   --> "M", nat(N), "/", nat(D).
   87interp(metro(M))     --> "MM", float(M).
   88interp(metro(M1--M2))--> "MM", float(M1), "-", float(M2).
   89interp(tempo(W))     --> "MM", sqbr(charsex(alpha,[],[],WW)),
   90	{atom_codes(W,WW)}.
   91
   92
   93% other
   94interp(staff(S))  --> "staff", staff_numbers(S).
   95interp(clef(C))   --> "clef", atom_chars_ex(graph,[],[],C).
   96interp(instr(I))  --> "I",    atom_chars_ex(graph,"CGT",[],I).
   97interp(igroup(I)) --> "IG",   atom_chars_ex(graph,[],[],I).
   98interp(iclass(I)) --> "IC",   atom_chars_ex(graph,[],[],I).
   99
  100interp(keysig(K)) --> "k", sqbr(seqmap(pitchclass(lower),K)).
  101interp(key(P,maj))--> pitchclass(upper,P), ":".
  102interp(key(P,min))--> pitchclass(lower,P), ":".
  103interp(trans)     --> "ITr".
  104
  105staff_numbers(S) --> seqmap_with_sep("/",nat,S).
  106
  107% read non-empty list of chars of type Type, first character not in Ex1, 
  108% remaining characters not in Ex, and convert to atom.
  109atom_chars_ex(Type,Ex1,Ex,A) --> 
  110	charsex(Type,Ex1,Ex,Codes), 
  111	{Codes\=[], atom_codes(A,Codes)}