module Music.Pitch.Relative.Accidental (
        
        Alterable(..),
        
        Accidental,
        doubleFlat, 
        flat, 
        natural, 
        sharp, 
        doubleSharp,
  ) where
import Music.Pitch.Literal
class Alterable a where
    
    
    
    sharpen :: a -> a
    
    
    
    flatten :: a -> a
newtype Accidental = Accidental { getAccidental :: Integer }
    deriving (Eq, Ord, Num, Enum, Real, Integral)
    
instance Show Accidental where
    show n | n == 0 = "natural"
           | n > 0  = replicate' n 's'
           | n < 0  = replicate' (negate n) 'b'
instance Alterable Accidental where
    sharpen = succ
    flatten = pred
instance Alterable Double where
    sharpen = (+ 1)
    flatten = (subtract 1)
instance Alterable Integer where
    sharpen = (+ 1)
    flatten = (subtract 1)
instance (IsPitch a, Alterable a) => IsPitch (Accidental -> a) where
    fromPitch l acc
        | acc == sharp  = sharpen (fromPitch l)
        | acc == flat   = flatten (fromPitch l)
sharp, flat, natural, doubleFlat, doubleSharp :: Accidental
doubleSharp = 2
sharp       = 1
natural     = 0
flat        = 1
doubleFlat  = 2
replicate' n = replicate (fromIntegral n)