module Music.Pitch.Clef
(
StaffLines,
HalfSpaces,
ClefLine,
ClefSymbol(..),
ClefOctave,
Clef(..),
symbolName,
symbolPitch,
positionPitch,
pitchPosition,
isModernClef,
isHistoricalClef,
isVoiceClef,
trebleClef,
bassClef,
sopranoClef,
mezzoSopranoClef,
altoClef,
tenorClef,
baritoneClef,
) where
import Data.Typeable
import Music.Pitch.Common
import Music.Pitch.Literal
newtype StaffLines = StaffLines { getStaffLines :: Integer }
deriving (Eq, Ord, Read, Show, Enum,
Num, Real, Integral, Typeable)
newtype HalfSpaces = HalfSpaces { getHalfSpaces :: Integer }
deriving (Eq, Ord, Read, Show, Enum,
Num, Real, Integral, Typeable)
data ClefSymbol = GClef | CClef | FClef | PercClef | NeutralClef
deriving (Eq, Ord, Show, Typeable)
type ClefOctave = Integer
type ClefLine = StaffLines
newtype Clef = Clef { getClef :: (ClefSymbol, ClefOctave, ClefLine) }
deriving (Eq, Ord, Typeable)
instance Show Clef where
show x@(Clef a)
| x == trebleClef = "trebleClef"
| x == bassClef = "bassClef"
| x == sopranoClef = "sopranoClef"
| x == mezzoSopranoClef = "mezzoSopranoClef"
| x == altoClef = "altoClef"
| x == tenorClef = "tenorClef"
| x == baritoneClef = "baritoneClef"
|otherwise = show a
symbolName :: ClefSymbol -> String
symbolName GClef = "G clef"
symbolName CClef = "C clef"
symbolName FClef = "F clef"
symbolName PercClef = "Percussion clef"
symbolName NeutralClef = "Neutral clef"
symbolPitch :: ClefSymbol -> Maybe Pitch
symbolPitch GClef = Just b'
symbolPitch CClef = Just c
symbolPitch FClef = Just d_
symbolPitch _ = Nothing
pitchPosition :: Clef -> Pitch -> Maybe StaffLines
pitchPosition (Clef (s,o,l)) x = undefined
where
numbersPerOctave = 7
referencePitch = symbolPitch s :: Maybe Pitch
positionPitch :: Clef -> StaffLines -> Maybe Pitch
positionPitch (Clef (s,o,l)) x = fmap (upDiatonic relativePosition) referencePitch
where
numbersPerOctave = 7
referencePitch = symbolPitch s :: Maybe Pitch
relativePosition = fromIntegral $ (x l) + fromIntegral (o*7)
upDiatonic :: Number -> Pitch -> Pitch
upDiatonic = upDiatonicP c . fromIntegral
trebleClef :: Clef
bassClef :: Clef
sopranoClef :: Clef
mezzoSopranoClef :: Clef
altoClef :: Clef
tenorClef :: Clef
baritoneClef :: Clef
trebleClef = Clef (GClef, 1 :: ClefOctave, 1 :: ClefLine)
bassClef = Clef (FClef, 1 :: ClefOctave, 1 :: ClefLine)
sopranoClef = Clef (CClef, 0 :: ClefOctave, 2 :: ClefLine)
mezzoSopranoClef = Clef (CClef, 0 :: ClefOctave, 1 :: ClefLine)
altoClef = Clef (CClef, 0 :: ClefOctave, 0 :: ClefLine)
tenorClef = Clef (CClef, 0 :: ClefOctave, 1 :: ClefLine)
baritoneClef = Clef (CClef, 0 :: ClefOctave, 2 :: ClefLine)
isModernClef :: Clef -> Bool
isModernClef x |x == trebleClef = True
isModernClef x |x == bassClef = True
isModernClef x |x == altoClef = True
isModernClef x |x == tenorClef = True
isModernClef x |otherwise = False
isHistoricalClef :: Clef -> Bool
isHistoricalClef _ = False
isVoiceClef :: Clef -> Bool
isVoiceClef x |x == altoClef = True
isVoiceClef x |x == tenorClef = True
isVoiceClef x |otherwise = False