module Music.Theory.Pitch where
import Data.Char
import Data.Function
import Data.List
import qualified Music.Theory.List as T
import qualified Music.Theory.Math as T
import Music.Theory.Pitch.Note
import Music.Theory.Pitch.Spelling
type PitchClass = Int
type Octave = Int
type Octave_PitchClass i = (i,i)
type OctPC = (Octave,PitchClass)
data Pitch = Pitch {note :: Note_T
,alteration :: Alteration_T
,octave :: Octave}
deriving (Eq,Show)
instance Ord Pitch where
compare = pitch_compare
data Pitch' = Pitch' Note_T Alteration_T' Octave
deriving (Eq,Show)
pitch'_pp :: Pitch' -> String
pitch'_pp (Pitch' n (_,a) o) = show n ++ a ++ show o
pitch'_class_pp :: Pitch' -> String
pitch'_class_pp = T.dropWhileRight isDigit . pitch'_pp
pitch_clear_quarter_tone :: Pitch -> Pitch
pitch_clear_quarter_tone p =
let Pitch n a o = p
in Pitch n (alteration_clear_quarter_tone a) o
pitch_to_octpc :: Integral i => Pitch -> Octave_PitchClass i
pitch_to_octpc = midi_to_octpc . pitch_to_midi
pitch_is_12et :: Pitch -> Bool
pitch_is_12et = alteration_is_12et . alteration
pitch_to_midi :: Integral i => Pitch -> i
pitch_to_midi (Pitch n a o) =
let a' = alteration_to_diff_err a
n' = note_to_pc n
o' = fromIntegral o
in 12 + o' * 12 + n' + a'
pitch_to_fmidi :: Fractional n => Pitch -> n
pitch_to_fmidi (Pitch n a o) =
let a' = alteration_to_fdiff a
o' = fromIntegral o
n' = fromInteger (note_to_pc n)
in 12 + o' * 12 + n' + a'
pitch_to_pc :: Pitch -> PitchClass
pitch_to_pc (Pitch n a _) = note_to_pc n + alteration_to_diff_err a
pitch_compare :: Pitch -> Pitch -> Ordering
pitch_compare =
let f = pitch_to_fmidi :: Pitch -> Double
in compare `on` f
octpc_to_pitch :: Integral i => Spelling i -> Octave_PitchClass i -> Pitch
octpc_to_pitch sp (o,pc) =
let (n,a) = sp pc
in Pitch n a (fromIntegral o)
octpc_nrm :: Integral i => Octave_PitchClass i -> Octave_PitchClass i
octpc_nrm (o,pc) =
if pc > 11
then octpc_nrm (o+1,pc12)
else if pc < 0
then octpc_nrm (o1,pc+12)
else (o,pc)
octpc_trs :: Integral i => i -> Octave_PitchClass i -> Octave_PitchClass i
octpc_trs n (o,pc) =
let pc' = fromIntegral pc
k = pc' + n
(i,j) = k `divMod` 12
in (fromIntegral o + fromIntegral i,fromIntegral j)
octpc_to_midi :: Integral i => Octave_PitchClass i -> i
octpc_to_midi (o,pc) = 60 + ((fromIntegral o 4) * 12) + pc
octpc_to_fmidi :: (Integral i,Num n) => Octave_PitchClass i -> n
octpc_to_fmidi = fromIntegral . octpc_to_midi
midi_to_octpc :: Integral i => i -> Octave_PitchClass i
midi_to_octpc n = (n 12) `divMod` 12
octpc_range :: (OctPC,OctPC) -> [OctPC]
octpc_range (l,r) =
let (l',r') = (octpc_to_midi l,octpc_to_midi r)
in map midi_to_octpc [l' .. r']
midi_to_pitch :: Integral i => Spelling i -> i -> Pitch
midi_to_pitch sp = octpc_to_pitch sp . midi_to_octpc
fmidi_to_pitch :: RealFrac n => Spelling Int -> n -> Pitch
fmidi_to_pitch sp m =
let m' = round m
(Pitch n a o) = midi_to_pitch sp m'
q = m fromIntegral m'
in case alteration_edit_quarter_tone q a of
Nothing -> error "fmidi_to_pitch"
Just a' -> Pitch n a' o
pitch_tranpose :: RealFrac n => Spelling Int -> n -> Pitch -> Pitch
pitch_tranpose sp n p =
let m = pitch_to_fmidi p
in fmidi_to_pitch sp (m + n)
pitch_in_octave_nearest :: Pitch -> Pitch -> Pitch
pitch_in_octave_nearest p1 p2 =
let o1 = octave p1
p2' = map (\n -> p2 {octave = n}) [o1 1,o1,o1 + 1]
m1 = pitch_to_fmidi p1 :: Double
m2 = map (pitch_to_fmidi) p2'
d = map (abs . (m1 )) m2
z = sortBy (compare `on` snd) (zip p2' d)
in fst (head z)
pitch_note_raise :: Pitch -> Pitch
pitch_note_raise (Pitch n a o) =
if n == maxBound
then Pitch minBound a (o + 1)
else Pitch (succ n) a o
pitch_note_lower :: Pitch -> Pitch
pitch_note_lower (Pitch n a o) =
if n == minBound
then Pitch maxBound a (o 1)
else Pitch (pred n) a o
pitch_rewrite_threequarter_alteration :: Pitch -> Pitch
pitch_rewrite_threequarter_alteration (Pitch n a o) =
case a of
ThreeQuarterToneFlat -> pitch_note_lower (Pitch n QuarterToneSharp o)
ThreeQuarterToneSharp -> pitch_note_raise (Pitch n QuarterToneFlat o)
_ -> Pitch n a o
pitch_edit_octave :: (Octave -> Octave) -> Pitch -> Pitch
pitch_edit_octave f (Pitch n a o) = Pitch n a (f o)
midi_to_cps :: (Integral i,Floating f) => i -> f
midi_to_cps = fmidi_to_cps . fromIntegral
fmidi_to_cps :: Floating a => a -> a
fmidi_to_cps i = 440 * (2 ** ((i 69) * (1 / 12)))
pitch_to_cps :: Floating n => Pitch -> n
pitch_to_cps = fmidi_to_cps . pitch_to_fmidi
cps_to_midi :: (Integral i,Floating f,RealFrac f) => f -> i
cps_to_midi = round . cps_to_fmidi
cps_to_fmidi :: Floating a => a -> a
cps_to_fmidi a = (logBase 2 (a * (1 / 440)) * 12) + 69
type Midi_Detune = (Int,Double)
cps_to_midi_detune :: Double -> Midi_Detune
cps_to_midi_detune f =
let (n,c) = T.integral_and_fractional_parts (cps_to_fmidi f)
in (n,c * 100)
midi_detune_to_cps :: Midi_Detune -> Double
midi_detune_to_cps (m,c) = fmidi_to_cps (fromIntegral m + (c / 100))
octpc_to_cps :: (Integral i,Floating n) => Octave_PitchClass i -> n
octpc_to_cps = midi_to_cps . octpc_to_midi
cps_to_octpc :: (Floating f,RealFrac f,Integral i) => f -> Octave_PitchClass i
cps_to_octpc = midi_to_octpc . cps_to_midi
parse_iso_pitch_oct :: Octave -> String -> Maybe Pitch
parse_iso_pitch_oct def_o s =
let nte n = let tb = zip "cdefgab" [C,D,E,F,G,A,B]
in lookup (toLower n) tb
oct o = case o of
[] -> Just def_o
[n] -> if isDigit n
then Just (fromIntegral (digitToInt n))
else Nothing
_ -> Nothing
mk n a o = case nte n of
Nothing -> Nothing
Just n' -> fmap (Pitch n' a) (oct o)
in case s of
[] -> Nothing
n:'b':'b':o -> mk n DoubleFlat o
n:'#':'#':o -> mk n DoubleSharp o
n:'x':o -> mk n DoubleSharp o
n:'b':o -> mk n Flat o
n:'#':o -> mk n Sharp o
n:o -> mk n Natural o
parse_iso_pitch :: String -> Maybe Pitch
parse_iso_pitch = parse_iso_pitch_oct (error "parse_iso_pitch: no octave")
pitch_pp :: Pitch -> String
pitch_pp (Pitch n a o) =
let a' = if a == Natural then "" else [alteration_symbol a]
in show n ++ a' ++ show o
pitch_class_pp :: Pitch -> String
pitch_class_pp = T.dropWhileRight isDigit . pitch_pp
pitch_class_names_12et :: Integral n => n -> n -> [String]
pitch_class_names_12et k n =
let f = pitch_class_pp . midi_to_pitch pc_spell_ks
in map f [60 + k .. 60 + k + n 1]
pitch_pp_iso :: Pitch -> String
pitch_pp_iso (Pitch n a o) = show n ++ alteration_iso a ++ show o
pitch_pp_hly :: Pitch -> String
pitch_pp_hly (Pitch n a o) =
let n' = map toLower (show n)
in n' ++ alteration_tonh a ++ show o
pitch_pp_tonh :: Pitch -> String
pitch_pp_tonh (Pitch n a o) =
let o' = show o
in case (n,a) of
(B,Natural) -> "H" ++ o'
(B,Flat) -> "B" ++ o'
(B,DoubleFlat) -> "Heses" ++ o'
(A,Flat) -> "As" ++ o'
(E,Flat) -> "Es" ++ o'
_ -> show n ++ alteration_tonh a ++ o'