\begin{code} module Music.Analysis.ABC where import Music.Analysis.Base import Data.List data ABCMusic = ABCMusic ABCMetaData [ABCMusicData] deriving (Eq) data ABCMetaData = ABCMetaData ABCIndex ABCTitle ABCMeter ABCKey deriving (Eq) data ABCIndex = ABCIndex deriving (Eq, Show) data ABCTitle = ABCTitle deriving (Eq, Show) data ABCMeter = ABCMeter deriving (Eq, Show) data ABCKey = ABCKey deriving (Eq, Show) data ABCMusicData = Single ABCNote | Tuplet Int [ABCMusicData] | Chord [ABCMusicData] | Tie ABCMusicData ABCMusicData | Slur [ABCMusicData] | Staccato ABCMusicData | GraceNotes [ABCNote] ABCMusicData | Symbol String ABCNote 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 (Number, Int) | Natural | Flat (Number, Int) deriving (Eq) data Dotted = Increase Int | Decrease Int deriving (Eq) type Octave = Int data Duration = Duration (Int, Int) deriving (Eq) \end{code} \begin{code} instance Show ABCMusic where show (ABCMusic _ xs) = concat (intersperse " " (map show xs)) 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 instance Show ABCNote where show (Pitch a b c d e) = show a ++ show b ++ show c ++ show d ++ show e show (Rest True b) = "z" ++ show b show (Rest False b) = "x" ++ show b instance Show Accident where show (Accident (Just x)) = show x show (Accident Nothing) = [] instance Show Accidental where show (Sharp n) = "^" ++ show n show (Natural) = "=" show (Flat n) = "_" ++ show 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 (n,0)) = show n show (Duration (1,n)) = "/" ++ show n show (Duration (0,n)) = "/" ++ show n show (Duration (x,y)) = show x ++ "/" ++ show y \end{code}