\begin{code}

module Music.Analysis.ABC where
import Data.List

data ABCMusic = ABCMusic ABCMetaData [ABCMusicData] 
    deriving (Eq)

data ABCMetaData = ABCMetaData ABCIndex ABCTitle ABCMeter ABCKey 
                   ABCL 
    deriving (Eq)

data ABCIndex = ABCIndex String deriving (Eq)
data ABCTitle = ABCTitle String deriving (Eq)
data ABCMeter = ABCMeter String deriving (Eq)
data ABCKey   = ABCKey   String deriving (Eq)
data ABCL     = ABCL            deriving (Eq)

data ABCMusicData = Single ABCNote 
                  | Tuplet Int [ABCMusicData]
                  | Chord [ABCMusicData]
                  | Tie ABCMusicData ABCMusicData
                  | Slur [ABCMusicData]
                  | Staccato ABCMusicData
                  | GraceNotes [ABCNote] ABCMusicData
                  | Symbol String ABCNote
                  | Bar
    deriving (Eq)

data ABCNote = Pitch Pitch Octave Accident Duration Dotted
             | Rest Bool Duration
    deriving (Eq)

data Pitch = C | D | E | F | G | A | B
    deriving (Show, Eq)
data Accident = Accident (Maybe Accidental)
    deriving Eq
data Accidental = Sharp Int | Natural | Flat Int
    deriving (Eq)

data Dotted = Increase Int | Decrease Int
    deriving (Eq)
data Octave = Octave Int
    deriving (Eq)

data Duration = Duration (Int, Int)
    deriving (Eq)

\end{code} \begin{code}
instance Show ABCMusic where
    show (ABCMusic x xs) =  show x ++ unwords (map show xs)

instance Show ABCMetaData where
    show (ABCMetaData a b c d e) = unlines [show a, show b, show c, show e, show d]

instance Show ABCIndex where
    show (ABCIndex x) = "X:" ++ x

instance Show ABCTitle where
    show (ABCTitle t) = "T:" ++ t

instance Show ABCMeter where
    show (ABCMeter m) = "M:" ++ m

instance Show ABCKey where
    show (ABCKey k) = "K:" ++ k

instance Show ABCL where
    show ABCL = "L: 1/4"

instance Show ABCMusicData where
    show (Single x) = show x
    show (Tuplet n xs) = "(" ++ show n ++ show xs
    show (Chord xs) = "[" ++ show xs ++ "]"
    show (Tie x y)  = show x ++ show y
    show (Slur xs) = "(" ++ show xs ++ ")"
    show (Staccato x) = "." ++ show x
    show (GraceNotes xs y) = "{" ++ show xs ++ "}" ++ show y
    show (Symbol _ y) = show y
    show (Bar) = "|\n"

instance Show ABCNote where
    show (Pitch a b c d e) = show c ++ show a ++ show b ++ show d ++ show e
    show (Rest True b) = "z" ++ show b
    show (Rest False b) = "x" ++ show b

instance Show Octave where
    show (Octave o) | o > 0 = replicate o '\''
                    | o < 0 = replicate o ','
                    | otherwise = []

instance Show Accident where
    show (Accident (Just x)) = show x
    show (Accident Nothing) = []

instance Show Accidental where
    show (Sharp n) = replicate n '^'
    show (Natural) = "=" 
    show (Flat n) = replicate n '_'

instance Show Dotted where
    show (Increase n) | n == 0 = []
                      | otherwise = ">" ++ show n
    show (Decrease n) | n == 0 = []
                      | otherwise = "<" ++ show n

instance Show Duration where
    show (Duration (1,1)) = []
    show (Duration (1,n)) = "/" ++ show n
    show (Duration (n,1)) = show n
    show (Duration (x,y)) = show x ++ "/" ++ show y
\end{code}