module Music.Theory.Pitch.Note where
import Data.Maybe
data Note_T = C | D | E | F | G | A | B
deriving (Eq,Enum,Bounded,Ord,Show)
note_to_pc :: Integral i => Note_T -> i
note_to_pc n =
case n of
C -> 0
D -> 2
E -> 4
F -> 5
G -> 7
A -> 9
B -> 11
note_t_transpose :: Note_T -> Int -> Note_T
note_t_transpose x n =
let x' = fromEnum x
n' = fromEnum (maxBound::Note_T) + 1
in toEnum ((x' + n) `mod` n')
data Alteration_T = DoubleFlat
| ThreeQuarterToneFlat | Flat | QuarterToneFlat
| Natural
| QuarterToneSharp | Sharp | ThreeQuarterToneSharp
| DoubleSharp
deriving (Eq,Enum,Bounded,Ord,Show)
generic_alteration_to_diff :: Integral i => Alteration_T -> Maybe i
generic_alteration_to_diff a =
case a of
DoubleFlat -> Just (2)
Flat -> Just (1)
Natural -> Just 0
Sharp -> Just 1
DoubleSharp -> Just 2
_ -> Nothing
alteration_to_diff :: Alteration_T -> Maybe Int
alteration_to_diff = generic_alteration_to_diff
alteration_is_12et :: Alteration_T -> Bool
alteration_is_12et = isJust . alteration_to_diff
alteration_to_diff_err :: Integral i => Alteration_T -> i
alteration_to_diff_err =
let err = error "alteration_to_diff: quarter tone"
in fromMaybe err . generic_alteration_to_diff
alteration_to_fdiff :: Fractional n => Alteration_T -> n
alteration_to_fdiff a =
case a of
ThreeQuarterToneFlat -> 1.5
QuarterToneFlat -> 0.5
QuarterToneSharp -> 0.5
ThreeQuarterToneSharp -> 1.5
_ -> fromInteger (alteration_to_diff_err a)
fdiff_to_alteration :: (Fractional n,Eq n) => n -> Maybe Alteration_T
fdiff_to_alteration d =
case d of
2 -> Just DoubleFlat
1.5 -> Just ThreeQuarterToneFlat
1 -> Just Flat
0.5 -> Just QuarterToneFlat
0 -> Just Natural
0.5 -> Just QuarterToneSharp
1 -> Just Sharp
1.5 -> Just ThreeQuarterToneSharp
2 -> Just DoubleSharp
_ -> undefined
alteration_raise_quarter_tone :: Alteration_T -> Maybe Alteration_T
alteration_raise_quarter_tone a =
if a == maxBound then Nothing else Just (toEnum (fromEnum a + 1))
alteration_lower_quarter_tone :: Alteration_T -> Maybe Alteration_T
alteration_lower_quarter_tone a =
if a == minBound then Nothing else Just (toEnum (fromEnum a 1))
alteration_edit_quarter_tone :: (Fractional n,Eq n) =>
n -> Alteration_T -> Maybe Alteration_T
alteration_edit_quarter_tone n a =
case n of
0.5 -> alteration_lower_quarter_tone a
0 -> Just a
0.5 -> alteration_raise_quarter_tone a
_ -> Nothing
alteration_clear_quarter_tone :: Alteration_T -> Alteration_T
alteration_clear_quarter_tone x =
case x of
ThreeQuarterToneFlat -> Flat
QuarterToneFlat -> Flat
QuarterToneSharp -> Sharp
ThreeQuarterToneSharp -> Sharp
_ -> x
alteration_symbol :: Alteration_T -> Char
alteration_symbol a = case a of
DoubleFlat -> '𝄫'
ThreeQuarterToneFlat -> '𝄭'
Flat -> '♭'
QuarterToneFlat -> '𝄳'
Natural -> '♮'
QuarterToneSharp -> '𝄲'
Sharp -> '♯'
ThreeQuarterToneSharp -> '𝄰'
DoubleSharp -> '𝄪'
alteration_iso_m :: Alteration_T -> Maybe String
alteration_iso_m a =
case a of
DoubleFlat -> Just "bb"
ThreeQuarterToneFlat -> Nothing
Flat -> Just "b"
QuarterToneFlat -> Nothing
Natural -> Just ""
QuarterToneSharp -> Nothing
Sharp -> Just "#"
ThreeQuarterToneSharp -> Nothing
DoubleSharp -> Just "x"
alteration_iso :: Alteration_T -> String
alteration_iso =
let qt = error "alteration_iso: quarter tone"
in fromMaybe qt . alteration_iso_m
alteration_tonh :: Alteration_T -> String
alteration_tonh a =
case a of
DoubleFlat -> "eses"
ThreeQuarterToneFlat -> "eseh"
Flat -> "es"
QuarterToneFlat -> "eh"
Natural -> ""
QuarterToneSharp -> "ih"
Sharp -> "is"
ThreeQuarterToneSharp -> "isih"
DoubleSharp -> "isis"
type Alteration_T' = (Rational,String)
alteration_t' :: Alteration_T -> Alteration_T'
alteration_t' a = (alteration_to_fdiff a,[alteration_symbol a])
type Spelling n = n -> (Note_T,Alteration_T)