-------------------------------------------------------------------------------- -- | -- Module : HarmTrace.Song -- Copyright : (c) 2010-2012 Universiteit Utrecht, 2012 University of Oxford -- License : GPL3 -- -- Maintainer : bash@cs.uu.nl, jpm@cs.ox.ac.uk -- Stability : experimental -- Portability : non-portable -- -- Summary: A song combines a melody with chords -------------------------------------------------------------------------------- module HarmTrace.Song where import HarmTrace.Base.MusicRep import Data.List ( elemIndex ) -- Each chord can have multiple melody notes data Song = Song Key [(ChordLabel, [MelodyNote])] deriving Show data Melody = Melody Key [MelodyNote] deriving Show data MelodyNote = MelodyNote { mnRoot :: Root , mnOctave :: Octave } deriving Eq type Octave = Int instance Show MelodyNote where show (MelodyNote r o) = show r ++ show o octaveDown, octaveUp :: MelodyNote -> MelodyNote octaveDown (MelodyNote r n) = MelodyNote r (n - 1) octaveUp (MelodyNote r n) = MelodyNote r (n + 1) instance Ord MelodyNote where compare (MelodyNote r1 o1) (MelodyNote r2 o2) = if compare o1 o2 == EQ then compareRoot r1 r2 else compare o1 o2 compareRoot :: Root -> Root -> Ordering compareRoot n1 n2 = case (elemIndex n1 roots, elemIndex n2 roots) of (Just i1, Just i2) -> compare i1 i2 _ -> compare n1 n2 -- probably wrong allMelodyNotes :: [MelodyNote] allMelodyNotes = [ MelodyNote r o | o <- [2..4], r <- roots ] -- from harmtrace-base roots :: [ Root ] roots = [ Note Nothing C , Note (Just Sh) C , Note Nothing D , Note (Just Fl) E , Note Nothing E , Note Nothing F , Note (Just Sh) F , Note Nothing G , Note (Just Fl) A , Note Nothing A , Note (Just Fl) B , Note Nothing B ]