hmt-0.16: Haskell Music Theory

Safe HaskellSafe
LanguageHaskell98

Music.Theory.Key

Description

Common music keys.

Synopsis

Documentation

data Mode_T Source #

Enumeration of common music notation modes.

Constructors

Minor_Mode 
Major_Mode 

mode_pp :: Mode_T -> String Source #

Pretty printer for Mode_T.

mode_parallel :: Mode_T -> Mode_T Source #

There are two modes, given one return the other.

mode_pc_seq :: Num t => Mode_T -> [t] Source #

type Key = (Note_T, Alteration_T, Mode_T) Source #

A common music notation key is a Note_T, Alteration_T, Mode_T triple.

key_sequence_42 :: [Key] Source #

Enumeration of 42 CMN keys.

length key_sequence_42 == 7 * 3 * 2

key_sequence_30 :: [Key] Source #

Subset of key_sequence not including very eccentric keys (where there are more than 7 alterations).

length key_sequence_30 == 30

key_parallel :: Key -> Key Source #

Parallel key, ie. mode_parallel of Key.

key_transpose :: Key -> Int -> Key Source #

Transposition of Key.

key_relative :: Key -> Key Source #

Relative key (ie. mode_parallel with the same number of and type of alterations.

let k = [(T.C,T.Natural,Major_Mode),(T.E,T.Natural,Minor_Mode)]
in map (key_lc_uc_pp . key_relative) k == ["a♮","G♮"]

key_mediant :: Key -> Maybe Key Source #

Mediant minor of major key.

key_mediant (T.C,T.Natural,Major_Mode) == Just (T.E,T.Natural,Minor_Mode)

key_pc_set :: Integral i => Key -> [i] Source #

key_lc_pp :: (Alteration_T -> String) -> Key -> String Source #

Pretty-printer where Minor_Mode is written in lower case (lc) and alteration symbol is shown using indicated function.

key_lc_uc_pp :: Key -> String Source #

key_lc_pp with unicode (uc) alteration.

map key_lc_uc_pp [(C,Sharp,Minor_Mode),(E,Flat,Major_Mode)] == ["c♯","E♭"]

key_lc_iso_pp :: Key -> String Source #

key_lc_pp with ISO alteration.

key_lc_tonh_pp :: Key -> String Source #

key_lc_pp with tonh alteration.

map key_lc_tonh_pp [(T.C,T.Sharp,Minor_Mode),(T.E,T.Flat,Major_Mode)]

key_identifier_pp :: (Show a, Show a1) => (a, a1, Mode_T) -> [Char] Source #

key_lc_uc_parse :: String -> Maybe Key Source #

Parse Key from lc-uc string.

import Data.Maybe
let k = mapMaybe key_lc_uc_parse ["c","E","f♯","ab","G#"]
in map key_lc_uc_pp k == ["c♮","E♮","f♯","a♭","G♯"]

key_fifths :: Key -> Maybe Int Source #

Distance along circle of fifths path of indicated Key. A positive number indicates the number of sharps, a negative number the number of flats.

key_fifths (T.A,T.Natural,Minor_Mode) == Just 0
key_fifths (T.A,T.Natural,Major_Mode) == Just 3
key_fifths (T.C,T.Natural,Minor_Mode) == Just (-3)
key_fifths (T.B,T.Sharp,Minor_Mode) == Just 9
key_fifths (T.E,T.Sharp,Major_Mode) == Just 11
key_fifths (T.B,T.Sharp,Major_Mode) == Nothing
zip (map key_lc_iso_pp key_sequence_42) (map key_fifths key_sequence_42)

key_fifths_tbl :: [(Key, Int)] Source #

Table mapping Key to key_fifths value.

fifths_to_key :: Mode_T -> Int -> Maybe Key Source #

Lookup key_fifths value in key_fifths_tbl.

let a = [0,1,-1,2,-2,3,-3,4,-4,5,-5]
let f md = map key_lc_iso_pp . mapMaybe (fifths_to_key md)
f Minor_Mode a
f Major_Mode a

implied_key :: Integral i => Mode_T -> [i] -> Maybe Key Source #

Given sorted pitch-class set, find simplest implied key in given mode.

mapMaybe (implied_key Major_Mode) [[0,2,4],[1,3],[4,10],[3,9],[8,9]]
map (implied_key Major_Mode) [[0,1,2],[0,1,3,4]] == [Nothing,Nothing]