module Music.Theory.Pitch.Spelling.Table where
import Data.Maybe
import qualified Music.Theory.Pitch as T
import Music.Theory.Pitch.Note
type Spelling_Table i = [(i,(Note,Alteration))]
pc_spell_natural_tbl :: Integral i => Spelling_Table i
pc_spell_natural_tbl :: forall i. Integral i => Spelling_Table i
pc_spell_natural_tbl =
[(i
0,(Note
C,Alteration
Natural))
,(i
2,(Note
D,Alteration
Natural))
,(i
4,(Note
E,Alteration
Natural))
,(i
5,(Note
F,Alteration
Natural))
,(i
7,(Note
G,Alteration
Natural))
,(i
9,(Note
A,Alteration
Natural))
,(i
11,(Note
B,Alteration
Natural))]
pc_spell_sharp_tbl :: Integral i => Spelling_Table i
pc_spell_sharp_tbl :: forall i. Integral i => Spelling_Table i
pc_spell_sharp_tbl =
[(i
1,(Note
C,Alteration
Sharp))
,(i
3,(Note
D,Alteration
Sharp))
,(i
6,(Note
F,Alteration
Sharp))
,(i
8,(Note
G,Alteration
Sharp))
,(i
10,(Note
A,Alteration
Sharp))]
pc_spell_flat_tbl :: Integral i => Spelling_Table i
pc_spell_flat_tbl :: forall i. Integral i => Spelling_Table i
pc_spell_flat_tbl =
[(i
1,(Note
D,Alteration
Flat))
,(i
3,(Note
E,Alteration
Flat))
,(i
6,(Note
G,Alteration
Flat))
,(i
8,(Note
A,Alteration
Flat))
,(i
10,(Note
B,Alteration
Flat))]
pc_spell_ks_tbl :: Integral i => Spelling_Table i
pc_spell_ks_tbl :: forall i. Integral i => Spelling_Table i
pc_spell_ks_tbl =
[(i
1,(Note
C,Alteration
Sharp))
,(i
3,(Note
E,Alteration
Flat))
,(i
6,(Note
F,Alteration
Sharp))
,(i
8,(Note
A,Alteration
Flat))
,(i
10,(Note
B,Alteration
Flat))]
pc_spell_tbl :: Integral i => Spelling_Table i -> T.Spelling i
pc_spell_tbl :: forall i. Integral i => Spelling_Table i -> Spelling i
pc_spell_tbl Spelling_Table i
tbl = forall a. a -> Maybe a -> a
fromMaybe (forall a. HasCallStack => [Char] -> a
error [Char]
"pc_spell_tbl") forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b c. (a -> b -> c) -> b -> a -> c
flip forall a b. Eq a => a -> [(a, b)] -> Maybe b
lookup Spelling_Table i
tbl
pc_spell_tbl_ks :: Integral i => Spelling_Table i -> T.Spelling i
pc_spell_tbl_ks :: forall i. Integral i => Spelling_Table i -> Spelling i
pc_spell_tbl_ks Spelling_Table i
tbl = forall i. Integral i => Spelling_Table i -> Spelling i
pc_spell_tbl (Spelling_Table i
tbl forall a. [a] -> [a] -> [a]
++ forall i. Integral i => Spelling_Table i
pc_spell_natural_tbl forall a. [a] -> [a] -> [a]
++ forall i. Integral i => Spelling_Table i
pc_spell_ks_tbl)
pc_spell_natural_m :: Integral i => T.Spelling_M i
pc_spell_natural_m :: forall i. Integral i => Spelling_M i
pc_spell_natural_m = forall a b c. (a -> b -> c) -> b -> a -> c
flip forall a b. Eq a => a -> [(a, b)] -> Maybe b
lookup forall i. Integral i => Spelling_Table i
pc_spell_natural_tbl
pc_spell_natural :: Integral i => T.Spelling i
pc_spell_natural :: forall i. Integral i => Spelling i
pc_spell_natural = forall i. Integral i => Spelling_Table i -> Spelling i
pc_spell_tbl forall i. Integral i => Spelling_Table i
pc_spell_natural_tbl
pc_spell_ks :: Integral i => T.Spelling i
pc_spell_ks :: forall i. Integral i => Spelling i
pc_spell_ks = forall i. Integral i => Spelling_Table i -> Spelling i
pc_spell_tbl_ks []
pc_spell_sharp :: Integral i => T.Spelling i
pc_spell_sharp :: forall i. Integral i => Spelling i
pc_spell_sharp = forall i. Integral i => Spelling_Table i -> Spelling i
pc_spell_tbl (forall i. Integral i => Spelling_Table i
pc_spell_sharp_tbl forall a. [a] -> [a] -> [a]
++ forall i. Integral i => Spelling_Table i
pc_spell_natural_tbl)
pc_spell_flat :: Integral i => T.Spelling i
pc_spell_flat :: forall i. Integral i => Spelling i
pc_spell_flat = forall i. Integral i => Spelling_Table i -> Spelling i
pc_spell_tbl (forall i. Integral i => Spelling_Table i
pc_spell_flat_tbl forall a. [a] -> [a] -> [a]
++ forall i. Integral i => Spelling_Table i
pc_spell_natural_tbl)
octpc_to_pitch_ks :: Integral i => T.Octave_PitchClass i -> T.Pitch
octpc_to_pitch_ks :: forall i. Integral i => Octave_PitchClass i -> Pitch
octpc_to_pitch_ks = forall i. Integral i => Spelling i -> Octave_PitchClass i -> Pitch
T.octpc_to_pitch forall i. Integral i => Spelling i
pc_spell_ks
midi_to_pitch_ks :: Integral i => i -> T.Pitch
midi_to_pitch_ks :: forall i. Integral i => i -> Pitch
midi_to_pitch_ks = forall i k. (Integral i, Integral k) => Spelling k -> i -> Pitch
T.midi_to_pitch (forall i. Integral i => Spelling i
pc_spell_ks :: T.Spelling Int)
fmidi_to_pitch_ks :: (Show n,RealFrac n) => n -> T.Pitch
fmidi_to_pitch_ks :: forall n. (Show n, RealFrac n) => n -> Pitch
fmidi_to_pitch_ks = forall n. (Show n, RealFrac n) => Spelling Int -> n -> Pitch
T.fmidi_to_pitch_err forall i. Integral i => Spelling i
pc_spell_ks
midi_detune_to_pitch_ks :: (Integral m,Real c) => (m,c) -> T.Pitch
midi_detune_to_pitch_ks :: forall m c. (Integral m, Real c) => (m, c) -> Pitch
midi_detune_to_pitch_ks = forall m c. (Integral m, Real c) => Spelling Int -> (m, c) -> Pitch
T.midi_detune_to_pitch forall i. Integral i => Spelling i
pc_spell_ks
midi_to_pitch_sharp :: Integral i => i -> T.Pitch
midi_to_pitch_sharp :: forall i. Integral i => i -> Pitch
midi_to_pitch_sharp = forall i k. (Integral i, Integral k) => Spelling k -> i -> Pitch
T.midi_to_pitch (forall i. Integral i => Spelling i
pc_spell_sharp :: T.Spelling Int)