Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Equal temperament tuning tables.
Synopsis
- octpc_to_pitch_cps_k0 :: Floating n => (n, n) -> OctPc -> (Pitch, n)
- octpc_to_pitch_cps :: Floating n => OctPc -> (Pitch, n)
- tbl_12et_k0 :: (Double, Double) -> [(Pitch, Double)]
- tbl_12et :: [(Pitch, Double)]
- tbl_24et_k0 :: (Double, Double) -> [(Pitch, Double)]
- tbl_24et :: [(Pitch, Double)]
- bounds_et_table :: Ord s => [(t, s)] -> s -> Maybe ((t, s), (t, s))
- bounds_12et_tone :: Double -> Maybe ((Pitch, Double), (Pitch, Double))
- type HS_R p = (Double, p, Double, Double, Cents)
- ndp :: Int -> Double -> String
- hs_r_pp :: (p -> String) -> Int -> HS_R p -> [String]
- hs_r_pitch_pp :: Int -> HS_R Pitch -> [String]
- nearest_et_table_tone :: [(p, Double)] -> Double -> HS_R p
- nearest_12et_tone_k0 :: (Double, Double) -> Double -> HS_R Pitch
- nearest_24et_tone_k0 :: (Double, Double) -> Double -> HS_R Pitch
- alteration_72et_monzo :: Integral n => n -> String
- pitch_72et_k0 :: (Double, Double) -> (Midi, Int) -> (Pitch_R, Double)
- tbl_72et_k0 :: (Double, Double) -> [(Pitch_R, Double)]
- nearest_72et_tone_k0 :: (Double, Double) -> Double -> HS_R Pitch_R
- type Pitch_Detune = (Pitch, Cents)
- hsr_to_pitch_detune :: HS_R Pitch -> Pitch_Detune
- nearest_pitch_detune_12et_k0 :: (Double, Double) -> Double -> Pitch_Detune
- nearest_pitch_detune_24et_k0 :: (Double, Double) -> Double -> Pitch_Detune
- ratio_to_pitch_detune :: (Double -> HS_R Pitch) -> OctPc -> Rational -> Pitch_Detune
- pitch_detune_to_cps :: Floating n => Pitch_Detune -> n
- ratio_to_pitch_detune_12et_k0 :: (Double, Double) -> OctPc -> Rational -> Pitch_Detune
- ratio_to_pitch_detune_24et_k0 :: (Double, Double) -> OctPc -> Rational -> Pitch_Detune
- pitch_detune_in_octave_nearest :: Pitch -> Pitch_Detune -> Pitch_Detune
- pitch_detune_md :: Pitch_Detune -> String
- pitch_detune_html :: Pitch_Detune -> String
- pitch_class_detune_md :: Pitch_Detune -> String
- pitch_class_detune_html :: Pitch_Detune -> String
Documentation
octpc_to_pitch_cps :: Floating n => OctPc -> (Pitch, n) Source #
octpc_to_pitch_cps_k0
of (69,440)
tbl_12et_k0 :: (Double, Double) -> [(Pitch, Double)] Source #
12-tone equal temperament table equating Pitch
and frequency
over range of human hearing, where A4
has given frequency.
tbl_12et_k0 (69,440)
tbl_12et :: [(Pitch, Double)] Source #
tbl_12et_k0
(69,440)
.
length tbl_12et == 192 T.minmax (map (round . snd) tbl_12et) == (1,31609)
tbl_24et_k0 :: (Double, Double) -> [(Pitch, Double)] Source #
24-tone equal temperament variant of tbl_12et_k0
.
tbl_24et :: [(Pitch, Double)] Source #
tbl_24et_k0
(69,440)
.
length tbl_24et == 360 T.minmax (map (round . snd) tbl_24et) == (1,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.
import qualified Music.Theory.Tuple as T let r = Just (T.t2_map octpc_to_pitch_cps ((3,11),(4,0))) bounds_et_table tbl_12et 256 == r
bounds_12et_tone :: Double -> Maybe ((Pitch, Double), (Pitch, Double)) Source #
import qualified Music.Theory.Tuning.Hs as T map bounds_12et_tone (T.harmonic_series_cps_n 17 55)
hs_r_pp :: (p -> String) -> Int -> HS_R p -> [String] Source #
Pretty print HS_R
. This discards the cps-deviation field, ie. it has only four fields.
nearest_et_table_tone :: [(p, Double)] -> Double -> HS_R p Source #
Form HS_R
for frequency by consulting table.
let f = 256 let f' = octpc_to_cps (4,0) let r = (f,Pitch C Natural 4,f',f-f',fratio_to_cents (f/f')) nearest_et_table_tone tbl_12et 256 == r
nearest_24et_tone_k0 :: (Double, Double) -> Double -> HS_R Pitch Source #
nearest_et_table_tone
for tbl_24et
.
let r = "55.0 A1 55.0 0.0" unwords (hs_r_pitch_pp 1 (nearest_24et_tone_k0 (69,440) 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 = ["+",">","^","#<","#-","#","#+","#>","#^"] map alteration_72et_monzo [1 .. 9] == r
let r = ["-","<","v","b>","b+","b","b-","b<","bv"] map alteration_72et_monzo [-1,-2 .. -9] == r
pitch_72et_k0 :: (Double, Double) -> (Midi, Int) -> (Pitch_R, Double) Source #
Given a midi note number and 1/6
deviation determine Pitch'
and frequency.
let f = pitch_r_pp . fst . pitch_72et_k0 (69,440) let r = "C4 C+4 C>4 C^4 C#<4 C#-4 C#4 C#+4 C#>4 C#^4" unwords (map f (zip (repeat 60) [0..9])) == r
let r = "A4 A+4 A>4 A^4 Bb<4 Bb-4 Bb4 Bb+4 Bb>4 Bv4" unwords (map f (zip (repeat 69) [0..9])) == r
let r = "Bb4 Bb+4 Bb>4 Bv4 B<4 B-4 B4 B+4 B>4 B^4" unwords (map f (zip (repeat 70) [0..9])) == r
tbl_72et_k0 :: (Double, Double) -> [(Pitch_R, Double)] Source #
72-tone equal temperament table equating Pitch'
and frequency
over range of human hearing, where A4
= 440
hz.
length (tbl_72et_k0 (69,440)) == 792 T.minmax (map (round . snd) (tbl_72et_k0 (69,440))) == (16,33167)
nearest_72et_tone_k0 :: (Double, Double) -> Double -> HS_R Pitch_R Source #
nearest_et_table_tone
for tbl_72et
.
let r = "324.0 E<4 323.3 0.7 3.5" unwords (hs_r_pp pitch_r_pp 1 (nearest_72et_tone_k0 (69,440) 324))
let f = take 2 . hs_r_pp pitch_r_pp 1 . nearest_72et_tone_k0 (69,440) . snd mapM_ (print . unwords . f) (tbl_72et_k0 (69,440))
Detune
hsr_to_pitch_detune :: HS_R Pitch -> Pitch_Detune Source #
Extract Pitch_Detune
from HS_R
.
nearest_pitch_detune_12et_k0 :: (Double, Double) -> Double -> Pitch_Detune Source #
Nearest 12-Et Pitch_Detune
to indicated frequency (hz).
nearest_pitch_detune_12et_k0 (69,440) 452.8929841231365
nearest_pitch_detune_24et_k0 :: (Double, Double) -> Double -> Pitch_Detune Source #
Nearest 24-Et Pitch_Detune
to indicated frequency (hz).
nearest_pitch_detune_24et_k0 (69,440) 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)
ratio_to_pitch_detune_12et_k0 :: (Double, Double) -> OctPc -> Rational -> Pitch_Detune Source #
ratio_to_pitch_detune
of nearest_12et_tone
ratio_to_pitch_detune_24et_k0 :: (Double, Double) -> OctPc -> Rational -> Pitch_Detune Source #
ratio_to_pitch_detune
of nearest_24et_tone
pitch_detune_md :: Pitch_Detune -> String Source #
Markdown pretty-printer for Pitch_Detune
.
pitch_detune_html :: Pitch_Detune -> String Source #
HTML pretty-printer for Pitch_Detune
.
pitch_class_detune_md :: Pitch_Detune -> String Source #
No-octave variant of pitch_detune_md
.
pitch_class_detune_html :: Pitch_Detune -> String Source #
No-octave variant of pitch_detune_html
.