hmt-0.15: Haskell Music Theory

Safe HaskellSafe-Inferred
LanguageHaskell98

Music.Theory.Tuning.ET

Contents

Description

Equal temperament tuning tables.

Synopsis

Documentation

tbl_12et :: [(Pitch, Double)] Source

12-tone equal temperament table equating Pitch and frequency over range of human hearing, where A4 = 440hz.

length tbl_12et == 132
let min_max l = (minimum l,maximum l)
min_max (map (round . snd) tbl_12et) == (16,31609)

tbl_24et :: [(Pitch, Double)] Source

24-tone equal temperament variant of tbl_12et.

length tbl_24et == 264
min_max (map (round . snd) tbl_24et) == (16,32535)

bounds_et_table :: Ord s => [(t, s)] -> s -> Maybe ((t, s), (t, s)) Source

Given an ET table (or like) find bounds of frequency.

let r = Just (at_pair octpc_to_pitch_cps ((3,11),(4,0)))
in bounds_et_table tbl_12et 256 == r

bounds_12et_tone :: Double -> Maybe ((Pitch, Double), (Pitch, Double)) Source

bounds_et_table of tbl_12et.

map bounds_12et_tone (hsn 17 55)

type HS_R p = (Double, p, Double, Double, Cents) Source

Tuple indicating nearest Pitch to frequency with ET frequency, and deviation in hertz and Cents.

ndp :: Int -> Double -> String Source

n-decimal places.

ndp 3 (1/3) == "0.333"

hs_r_pp :: (p -> String) -> Int -> HS_R p -> [String] Source

Pretty print HS_R.

nearest_et_table_tone :: [(p, Double)] -> Double -> HS_R p Source

Form HS_R for frequency by consulting table.

let {f = 256
    ;f' = octpc_to_cps (4,0)
    ;r = (f,Pitch C Natural 4,f',f-f',fratio_to_cents (f/f'))}
in nearest_et_table_tone tbl_12et 256 == r

nearest_24et_tone :: Double -> HS_R Pitch Source

nearest_et_table_tone for tbl_24et.

let r = "55.0 A1 55.0 0.0 0.0"
in unwords (hs_r_pitch_pp 1 (nearest_24et_tone 55)) == r

72ET

alteration_72et_monzo :: Integral n => n -> String Source

Monzo 72-edo HEWM notation. The domain is (-9,9). http://www.tonalsoft.com/enc/number/72edo.aspx

let r = ["+",">","^","#<","#-","#","#+","#>","#^"]
in map alteration_72et_monzo [1 .. 9] == r
let r = ["-","<","v","b>","b+","b","b-","b<","bv"]
in map alteration_72et_monzo [-1,-2 .. -9] == r

pitch_72et :: (Int, Int) -> (Pitch', Double) Source

Given a midi note number and 1/6 deviation determine Pitch' and frequency.

let {f = pitch'_pp . fst . pitch_72et
    ;r = "C4 C+4 C>4 C^4 C#<4 C#-4 C#4 C#+4 C#>4 C#^4"}
in unwords (map f (zip (repeat 60) [0..9])) == r
let {f = pitch'_pp . fst . pitch_72et
    ;r = "A4 A+4 A>4 A^4 Bb<4 Bb-4 Bb4 Bb+4 Bb>4 Bv4"}
in unwords (map f (zip (repeat 69) [0..9]))
let {f = pitch'_pp . fst . pitch_72et
    ;r = "Bb4 Bb+4 Bb>4 Bv4 B<4 B-4 B4 B+4 B>4 B^4"}
in unwords (map f (zip (repeat 70) [0..9])) == r

tbl_72et :: [(Pitch', Double)] Source

72-tone equal temperament table equating Pitch' and frequency over range of human hearing, where A4 = 440hz.

length tbl_72et == 792
min_max (map (round . snd) tbl_72et) == (16,33167)

nearest_72et_tone :: Double -> HS_R Pitch' Source

nearest_et_table_tone for tbl_72et.

let r = "324.0 E<4 323.3 0.7 3.5"
in unwords (hs_r_pp pitch'_pp 1 (nearest_72et_tone 324))
let {f = take 2 . hs_r_pp pitch'_pp 1 . nearest_72et_tone . snd}
in mapM_ (print . unwords . f) tbl_72et

Detune

type Pitch_Detune = (Pitch, Cents) Source

Pitch with 12-ET/24-ET tuning deviation given in Cents.

nearest_pitch_detune_12et :: Double -> Pitch_Detune Source

Nearest 12-ET Pitch_Detune to indicated frequency (hz).

nearest_pitch_detune_12et 452.8929841231365

nearest_pitch_detune_24et :: Double -> Pitch_Detune Source

Nearest 24-ET Pitch_Detune to indicated frequency (hz).

nearest_pitch_detune_24et 452.8929841231365

ratio_to_pitch_detune :: (Double -> HS_R Pitch) -> OctPC -> Rational -> Pitch_Detune Source

Given near function, f0 and ratio derive Pitch_Detune.

pitch_detune_to_cps :: Floating n => Pitch_Detune -> n Source

Frequency (hz) of Pitch_Detune.

pitch_detune_to_cps (octpc_to_pitch pc_spell_ks (4,9),50)

pitch_detune_md :: Pitch_Detune -> String Source

Markdown pretty-printer for Pitch_Detune.