\begin{code} -- | -- Maintainer : silva.samuel@alumni.uminho.pt -- Stability : experimental -- Portability: portable -- This module implements module Music.Analysis.Abstract2ABC where -- import Music.Analysis.Base import Music.Analysis.PF import Music.Analysis.Abstract.Settings import qualified Music.Analysis.Abstract.Motive as Motive --import qualified Music.Analysis.Abstract.Zip as Abstract import qualified Music.Analysis.Abstract.Melodic as Melodic import qualified Music.Analysis.Abstract.Rhythm as Rhythm import Music.Analysis.ABC as ABC import Data.Ratio \end{code} \begin{code} mk_Music :: Motive.Motive (Melodic.MelodicClass, Rhythm.RhythmAbsolute) -> ABCMusic mk_Music = uncurry ABCMusic . split mk_Meta mk_Notes -- | mk_Meta :: Motive.Motive (Melodic.MelodicClass, Rhythm.RhythmAbsolute) -> ABCMetaData mk_Meta = mk_Meta_aux . p1 . Motive.fromMotive where mk_Meta_aux s = let a = const (ABCIndex []) s b = maybe (ABCTitle []) (const (ABCTitle [])) (getText "title" s) c = maybe (ABCMeter []) (const (ABCMeter [])) (getText "meter" s) d = maybe (ABCKey []) (const (ABCKey [])) (getText "key" s) in ABCMetaData a b c d ABC.ABCL -- | mk_Notes :: Motive.Motive (Melodic.MelodicClass, Rhythm.RhythmAbsolute) -> [ABC.ABCMusicData] mk_Notes = map (ABC.Single . mk_Note) . p2 . Motive.fromMotive -- | mk_Note :: (Melodic.MelodicClass, Rhythm.RhythmAbsolute) -> ABC.ABCNote mk_Note (x,y) = let (duration, dotted) = mk_Duration y in case mk_Note' x of Just (pitch, accidental) -> ABC.Pitch pitch (Octave 0) accidental duration dotted Nothing -> ABC.Rest True duration mk_Duration :: Rhythm.RhythmAbsolute -> (ABC.Duration, ABC.Dotted) mk_Duration (x,y) = (ABC.Duration (numerator x, denominator x), ABC.Increase y) mk_Note' :: Melodic.MelodicClass -> Maybe (ABC.Pitch, ABC.Accident) mk_Note' Nothing = Nothing mk_Note' (Just (x,y)) = Just (mk_Pitch x, mk_Accident y) mk_Pitch :: Melodic.PitchClass -> ABC.Pitch mk_Pitch Melodic.C = ABC.C mk_Pitch Melodic.D = ABC.D mk_Pitch Melodic.E = ABC.E mk_Pitch Melodic.F = ABC.F mk_Pitch Melodic.G = ABC.G mk_Pitch Melodic.A = ABC.A mk_Pitch Melodic.B = ABC.B mk_Accident :: Melodic.Accident -> ABC.Accident mk_Accident Nothing = ABC.Accident Nothing mk_Accident (Just n) | n > 0 = ABC.Accident (Just (ABC.Sharp (truncate n))) | n == 0 = ABC.Accident (Just (ABC.Natural)) | n < 0 = ABC.Accident (Just (ABC.Flat (truncate n))) | otherwise = ABC.Accident Nothing \end{code}