1/* lilypond.pl
    2Author: Gimenez, Christian.
    3
    4Copyright (C) 2025 Gimenez, Christian
    5
    6This program is free software: you can redistribute it and/or modify
    7it under the terms of the GNU General Public License as published by
    8the Free Software Foundation, either version 3 of the License, or
    9at your option) any later version.
   10
   11This program is distributed in the hope that it will be useful,
   12but WITHOUT ANY WARRANTY; without even the implied warranty of
   13MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
   14GNU General Public License for more details.
   15
   16You should have received a copy of the GNU General Public License
   17along with this program.  If not, see <http://www.gnu.org/licenses/>.
   18
   192025-10-14
   20*/
   21
   22:- module(lilypond, [
   23              notelily//1,
   24              lily//1
   25          ]).

lilypond: generate or parse Lilypond code.

Parse Prolog note representations from Lilypond code. Or generate Lilypond code from Prolog notes. This is achieved by DCG rules.

Examples

Generating Lilypond code:

?- phrase(lily([c, d, e, f, g]), L, []), format('~s', [L]).
c d e f g

Parsing from Lilypond code:

?- phrase(lily(L1), `c cis   d dis e`, R).
L1 = [c, cs, d, ds, e],
R = [].
author
- Christian Gimenez
license
- GPLv3 */
   52:- license(gplv3).   53
   54:- use_module(library(dcg/basics)).
Parse a Prolog note representation from a Lilypond note. Or generate Lilypond code from a Prolog note.
Arguments:
Note- An atom with the note name or a Note-Octave-Duration term.
   63notelily(cs) --> `cis`,
   64               % sharp notes must be before natural notes!
   65               % this allows recognising them because of the string length.
   66               !. 
   67notelily(c) --> `c`, !.
   68notelily(ds) --> `dis`, !.
   69notelily(d) --> `d`, !.
   70notelily(e) --> `e`, !.
   71notelily(fs) --> `fis`, !.
   72notelily(f) --> `f`, !.
   73notelily(gs) --> `gis`, !.
   74notelily(g) --> `g`, !.
   75notelily(as) --> `ais`, !.
   76notelily(a) --> `a`, !.
   77notelily(b) --> `b`, !.
   78            
   79notelily(Note-Octave-Duration) --> notelily(Note), octavelily(Octave), number(Duration).
 octavelily(+Number:integer)//
Convert the octave number to a Lilypond phrase.
To be done
- Implement octavelily//1
   86octavelily(_) --> [].
Parse Prolog notes from Lilypond code, or generate Lilypond code from Prolog notes.
Arguments:
Notes- A list of the following elements:
  • an atom with the note name or,
  • a Note-Octave-Duration term.
   97lily([Note|Rest]) -->
   98    % Case: parsing Lilypond string with multiple blanks. But cannot be used to
   99    % generate Lilypond strings, because blank//0 and blanks//0 will fail.
  100    notelily(Note), blank, blanks, !, lily(Rest). 
  101lily([Note|Rest]) -->
  102    % Case: useful to generate Lilypond strings.
  103    notelily(Note), ` `, !, lily(Rest).
  104lily([Note]) --> notelily(Note), !.
  105lily([]) --> []