1/* notes.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-12
   20*/
   21
   22:- module(notes, [
   23              note_order/1,
   24              notenum/2,
   25              sum_semitones/3,
   26              sum_tones/3,
   27              tone/2,
   28              semitone/2,
   29              semitones/3,
   30              interval/2,
   31              interval/3,
   32              second/3,
   33              third/3,
   34              fourth/2,
   35              fifth/2,
   36              sixth/3,
   37              seventh/3,
   38              eighth/2,
   39              octave/2,
   40              transpose/3,
   41              transpose/4
   42          ]).

notes: Simple notes representation and calculation.

Predicates that calculates semitones, tones, and intervals in notes.

Names

In order to create a more convenient way to programming with Prolog, name of notes, intervals, and othe possible concepts are different from literature. It may be different from Lilypond or other software too.

For instance, C3 is not used to represent C note in Prolog in third octave because the it would be interpreted as a Prolog variable. Also, 'C3' or c3 wolud requier extra processing to separate the octave number from the C/c. However, the c-3 term would represent the C note at 3 octave effectively, and the octave number is already separated from the note name. A simmilar approach is implemented for intervals and other concepts.

Note representation

Notes are terms with the following possible representations:

Intervals

Interval calculations can be achieved by the interval/2 and interval/3 predicates, or by using sum_semitones/3 with the specific amount of semitones. There are also aliases for second/3, third/3, etc.

Intervals are represented as: Nth-Type. Where Nth is the number of interval, and the Type is one of the atoms: perfect, major, minor, or extra. The 4-extra atom is used to assign a name to the interval between the P4 (perfect 4th) and P5 (perfect 5th) which has 6 semitones of distance. This interval name does not exists in the literature, and is used to complete the names to a semitone distance in case the calculations results in that number.

author
- Christian Gimenez
license
- GPLv3 */
   93:- license(gplv3).
 note_order(-L:list) is det
The order of the musical notes in this implementation.
   98note_order([c, cs, d, ds, e, f, fs, g, gs, a, as, b]).
 notenum(+Note:atom, -Num:integer) is det
notenum(-Note:atom, +Num:integer) is det
Represent the given note as number, or the number as a note. When calculating the number, only the first number is given (is determinate). For instance, notenum(c, R) will result in R = 0, and without more results. But notenum(c, 12) is also true (indicating that C note is also represented as 12).

Representing notes in numbers are easy for calculations. Adding an amount of semitones to a given note represented as a number instead as a Prolog atom is more efficient.

If Num is a negative number or greater than 11, it is calculated to be between 0 (c note) to 11 (b note).

  115notenum(c,  0) :- !.
  116notenum(cs, 1) :- !.
  117notenum(d,  2) :- !.
  118notenum(ds, 3) :- !.
  119notenum(e,  4) :- !.
  120notenum(f,  5) :- !.
  121notenum(fs, 6) :- !.
  122notenum(g,  7) :- !.
  123notenum(gs, 8) :- !.
  124notenum(a,  9) :- !.
  125notenum(as, 10) :- !.
  126notenum(b,  11) :- !.
  127notenum(Note, Num) :-
  128    % Case: Num is not between 0 and 11 semitones.
  129    (Num > 11 ; Num < 0), !,
  130
  131    ResultNum is Num mod 12,
  132    notenum(Note, ResultNum).
 sum_semitones(+StartNote:atom, +Semitones:integer, -EndNote:atom)
sum_semitones(+StartNote:term, +Semitones:integer, -EndNote:term)
Calculate the ending note after adding the given semitones.
Arguments:
StartNote- can be an atom with the note, or a Note-Octave term.
  141sum_semitones(Note-Octave, Semitones, ResultNote-ResultOctave) :- !,
  142    notenum(Note, Num),
  143    ResultNum is Num + Semitones,
  144    notenum(ResultNote, ResultNum),
  145
  146    Diff is (ResultNum div 12),
  147    
  148    ResultOctave is Octave + Diff.
  149sum_semitones(Note, Semitones, ResultNote) :-
  150    atom(Note),
  151    notenum(Note, Num),
  152    ResultNum is Num + Semitones,
  153    notenum(ResultNote, ResultNum).
 sum_tones(+StartNote:atom, +Tones:integer, -ResultNote:atom)
sum_tones(+StartNote:term, +Tones:integer, -ResultNote:term)
Same as sum_semitones/3 but using tones as unit.
Arguments:
StartNote- can be an atom with the note, or a Note-Octave term.
  161sum_tones(Note, Tones, ResultNote) :-
  162    Semitones is Tones * 2,
  163    sum_semitones(Note, Semitones, ResultNote).
 tone(+StartNote:atom, -ResultNote:atom)
tone(+StartNote:term, -ResultNote:term)
Add a tone to StartNote.
Arguments:
StartNote- can be an atom with the note, or a Note-Octave term.
  171tone(Note, ResultNote) :-
  172    sum_semitones(Note, 2, ResultNote).
 semitone(+StartNote:atom, -ResultNote:atom)
semitone(+StartNote:term, -ResultNote:term)
Add a semitone to StartNote.
Arguments:
StartNote- can be an atom with the note, or a Note-Octave term.
  180semitone(Note, ResultNote) :-
  181    sum_semitones(Note, 1, ResultNote).
 semitones(+FromNote:atom, +ToNote:atom, -Diff:integer)
semitones(+FromNote:term, +ToNote:term, -Diff:integer)
Calculate the semitones between FromNote and ToNote.
Arguments:
FromNote- A Note-Octave or a note name.
ToNote- A Note-Octave or a note name.
Diff- The amount of semitones between FromNote and ToNote.
  191semitones(FromNote-FromOctave, ToNote-ToOctave, Diff) :- !,
  192    semitones(FromNote, ToNote, Diff1),
  193    Diff is Diff1 + (ToOctave - FromOctave) * 12.
  194semitones(FromNote, ToNote, Diff) :-
  195    notenum(FromNote, Num),
  196    notenum(ToNote, Num2),
  197    Diff is Num2 - Num.
 interval(+Interval:term, -Semitones:integer) is det
Calculate the semitones of the given interval.

In the literature, the interval between 4-perfect and 5-perfect (6 semitones) has no name. In this implementation, the term 4-extra is assigned to this interval.

Arguments:
Interval- a Number-Type term where Number is the nth interval, and the type can be the perfect, minor, or major atom.
Semitones- the amount of semitones for that interval.
  210interval(1-perfect, 0) :- !.
  211interval(2-minor,   1) :- !.
  212interval(2-major,   2) :- !.
  213interval(3-minor,   3) :- !.
  214interval(3-major,   4) :- !.
  215interval(4-perfect, 5) :- !.
  216interval(4-extra,   6) :- !. % 6 semitones interval has no name actually.
  217interval(5-perfect, 7) :- !.
  218interval(6-minor,   8) :- !.
  219interval(6-major,   9) :- !.
  220interval(7-minor,   10) :- !.
  221interval(7-major,   11) :- !.
  222interval(Num-Type, Semitones) :-
  223    (Num > 7 ; Num < 1), !,
  224    
  225    Octave is Num div 8,
  226    Num2 is Num mod 7,
  227    interval(Num2-Type, Semitones1),
  228
  229    Semitones is (Octave * 11) + Semitones1 + 1.
 interval(+Interval:term, +StartNote:atom, -EndNote:atom)
Calculate the interval notes.
  234interval(Interval, StartNote, EndNote) :-
  235    interval(Interval, Semitones),
  236    sum_semitones(StartNote, Semitones, EndNote).
 second(+Type:atom, +StartNote:atom, -EndNote:atom)
Calculate the major/minor second interval (M2/m2) of StartNote.
Arguments:
Type- is the type of interval. Can be the atom major, or minor.
  243second(Type, A, B) :-
  244    interval(2-Type, Semitones),
  245    sum_semitones(A, Semitones, B).
 third(+Type:atom, +StartNote:atom, -EndNote:atom)
Calculate the major/minor third interval (M3/m3) of StartNote.
Arguments:
Type- is the type of interval. Can be the atom major, or minor.
  252third(Type, A, B) :-
  253    interval(3-Type, Semitones),
  254    sum_semitones(A, Semitones, B).
 fourth(+StartNote:atom, -EndNote:atom)
Calculate the perfect fourth interval (P4) of StartNote.
  259fourth(A, B) :-
  260    sum_semitones(A, 5, B).
 fifth(+StartNote:atom, -EndNote:atom)
Calculate the perfect fifth interval (P5) of StartNote.
  265fifth(A, B) :-
  266    sum_semitones(A, 7, B).
 sixth(+Type:atom, +StartNote:atom, -EndNote:atom)
Calculate the major/minor sixth interval (M6/m6) of StartNote.
Arguments:
Type- is the type of interval. Can be the atom major, or minor.
  273sixth(Type, A, B) :-
  274    interval(6-Type, Semitones),
  275    sum_semitones(A, Semitones, B).
 seventh(+Type:atom, +StartNote:atom, -EndNote:atom)
Calculate the major/minor seventh interval (M7/m7) of StartNote.
Arguments:
Type- is the type of interval. Can be the atom major, or minor.
  282seventh(Type, A, B) :-
  283    interval(7-Type, Semitones),
  284    sum_semitones(A, Semitones, B).
 eighth(+StartNote:atom, -EndNote:atom)
Calculate the perfect eighth interval (P8 or octave) of StartNote.

Same as octave/2.

  291eighth(A, B) :-
  292    sum_semitones(A, 12, B).
 octave(+StartNote:atom, -EndNote:atom)
Calculate the octave of StartNote.

Same as eighth/2.

  299octave(A, B) :-
  300    sum_semitones(A, 12, B).
  301
  302sum_semitones_int(Semitones, Note, Note2) :-
  303    sum_semitones(Note, Semitones, Note2).
 transpose(+Notes:list, +Semitones:integer, -NewNotes:list) is det
Transpose a list notes adding the given semitones.
  308transpose(Notes, Semitones, NewNotes) :-
  309    maplist(sum_semitones_int(Semitones), Notes, NewNotes).
 transpose(+Notes:list, +FromNote:atom, +ToNote:atom, -NewNotes:list) is det
Transpose a list notes from the FromNote scale to ToNote scale.
Arguments:
Notes- A list of notes (all notation accepted). The Notes list is considered to be in FromNote scale or tuning.
FromNote- The source tuning note name. No Note-Octave notation is accepted.
ToNote- The destination tuning note name. No Note-Octave notation is accepted.
NewNotes- A list of notes with the calculated tuning.
  320transpose(Notes, FromNote, ToNote, NewNotes) :-
  321    semitones(FromNote, ToNote, Diff),
  322    
  323    transpose(Notes, Diff, NewNotes)