21
22:- module(scales, [
23 scale_type/1,
24 scale/3,
25 arpeggio_type/1,
26 arpeggio/3,
27 tonic/2, supertonic/2, mediant/2,
28 subdominant/2, dominant/2,
29 submediant/2, leading/2, leading_tone/2
30 ]).
40:- use_module(library(music/notes)).
45scale_type(major).
46scale_type(minor).
48
52scale(major, C, [C, D, E, F, G, A, B, C]) :-
53 tone(C, D),
54 tone(D, E),
55 semitone(E, F),
56 tone(F, G),
57 tone(G, A),
58 tone(A, B),
59 semitone(B, C).
60scale(minor, A, [A, B, C, D, E, F, G, A]) :-
61 tone(A, B),
62 semitone(B, C),
63 tone(C, D),
64 tone(D, E),
65 semitone(E, F),
66 tone(F, G),
67 tone(G, A).
68
69tonic([Note|_], Note).
70supertonic([_, Note|_], Note).
71mediant([_, _, Note|_], Note).
72subdominant([_, _, _, Note|_], Note).
73dominant([_, _, _, _, Note|_], Note).
74submediant([_, _, _, _, _, Note|_], Note).
75leading_tone([_, _, _, _, _, _, Note|_], Note).
76leading(List, Note) :-
77 leading_tone(List, Note).
82arpeggio_type(major).
83arpeggio_type(minor).
88arpeggio(Type, C, [C, E, G]) :-
89 arpeggio_type(Type), !,
90 third(Type, C, E),
91 fifth(C, G).
scales: Scales calculation.
Calculate notes for different scale tipes and any scale-refered concepts.