module Music.Lilypond.Pitch (
        Pitch(..),
        PitchClass(..),
        Accidental(..),
        Octaves(..),
        Mode(..),
        OctaveCheck(..),
  ) where
import Text.Pretty hiding (Mode)
import Music.Pitch.Literal
data PitchClass = C | D | E | F | G | A | B
    deriving (Eq, Ord, Show, Enum)
newtype Pitch = Pitch { getPitch :: (PitchClass, Accidental, Octaves) }
    deriving (Eq, Ord, Show)
instance Pretty Pitch where
    pretty (Pitch (c,a,o)) = string $ pc c ++ acc a ++ oct (o4)
        where
            pc C = "c" ; pc D = "d" ; pc E = "e" ; pc F = "f"
            pc G = "g" ; pc A = "a" ; pc B = "b"            
            acc n | n <  0  =  concat $ replicate (negate n) "es"
                  | n == 0  =  ""
                  | n >  0  =  concat $ replicate (n) "is"
            oct n | n <  0  =  concat $ replicate (negate n) ","
                  | n == 0  =  ""
                  | n >  0  =  concat $ replicate n "'"
instance IsPitch Pitch where
    fromPitch (PitchL (c, Nothing, o)) = Pitch (toEnum c, 0,       o)                 
    fromPitch (PitchL (c, Just a, o))  = Pitch (toEnum c, round a, o)
type Accidental = Int 
type Octaves    = Int 
data Mode = Major | Minor
    deriving (Eq, Show)
instance Pretty Mode where
    pretty Major = "\\major"
    pretty Minor = "\\minor"
data OctaveCheck = OctaveCheck
    deriving (Eq, Show)