\begin{code} module Music.Analysis.MusicXML.Level4 ( module Music.Analysis.MusicXML.Level4, )where import Music.Analysis.Base (IntegerNumber) import Music.Analysis.PF import qualified Music.Analysis.MusicXML.Level1 as Layer1 import qualified Music.Analysis.MusicXML.Level2 as Layer2 import qualified Music.Analysis.MusicXML.Level3 as Layer3 import Data.Maybe (catMaybes) import qualified Text.XML.MusicXML as MusicXML \end{code} \begin{code} -- | type Score_Partwise = (MusicXML.Document_Attributes, (MusicXML.Score_Header, [Part])) -- | type Part = [Measure] -- | type Measure = [Music_Data] -- | data Music_Data = Music_Data_1 Note | Music_Data_2 MusicXML.Backup | Music_Data_3 MusicXML.Forward | Music_Data_4 MusicXML.Direction | Music_Data_5 Attributes | Music_Data_6 MusicXML.Harmony | Music_Data_7 MusicXML.Figured_Bass | Music_Data_8 MusicXML.Print | Music_Data_9 MusicXML.Sound | Music_Data_10 MusicXML.Barline | Music_Data_11 MusicXML.Grouping | Music_Data_12 MusicXML.Link | Music_Data_13 MusicXML.Bookmark deriving (Eq, Show) -- | type Note = (Note_, Maybe Instrument, Editorial_Voice, Maybe Type, [Dot], Maybe Accidental, Maybe Time_Modification, Maybe Stem, Maybe Notehead, Maybe Staff, [Beam], [Notations], [Lyric]) -- | data Note_ = Note_1 (Grace, Full_Note, Maybe (Tie, Maybe Tie)) | Note_2 (Cue, Full_Note, Duration) | Note_3 (Full_Note, Duration, Maybe (Tie, Maybe Tie)) deriving (Eq, Show) -- | type Grace = MusicXML.Grace -- | type Cue = MusicXML.Cue -- | type Tie = MusicXML.Tie -- | type Full_Note = (Maybe MusicXML.Chord, Full_Note_) -- | data Full_Note_ = Full_Note_1 Layer2.Pitch | Full_Note_2 Unpitched | Full_Note_3 Rest deriving (Eq, Show) -- | type Unpitched = MusicXML.Unpitched -- | type Rest = MusicXML.Rest -- | type Duration = IntegerNumber -- | type Editorial_Voice = MusicXML.Editorial_Voice -- | type Instrument = MusicXML.Instrument -- | type Type = Layer1.Type_ -- | type Dot = MusicXML.Dot -- | type Accidental = Layer1.Accidental_ -- | type Time_Modification = MusicXML.Time_Modification -- | type Stem = MusicXML.Stem -- | type Notehead = MusicXML.Notehead -- | type Beam = MusicXML.Beam -- | positive number type Staff = IntegerNumber -- | type Lyric = MusicXML.Lyric -- | type Notations = MusicXML.Notations -- | type Attributes = (Editorial, Maybe Divisions, [Key], [Time], Maybe Staves, Maybe Part_Symbol, Maybe Instruments, [Clef], [Staff_Details], Maybe Transpose, [Directive], [Measure_Style]) -- | type Editorial = MusicXML.Editorial -- | type Divisions = IntegerNumber -- | type Key = (Key_, [Layer2.Key_Octave]) -- | data Key_ = Key_1 (Maybe MusicXML.Cancel, Layer2.Fifths, Maybe Layer2.Mode) | Key_2 [(Layer2.Key_Step, Layer2.Key_Alter)] deriving (Eq, Show) -- | type Time = Layer3.Time_B -- | type Staves = MusicXML.Staves -- | type Part_Symbol = MusicXML.Part_Symbol -- | type Instruments = MusicXML.Instruments -- | type Clef = (Layer2.Sign, Maybe Layer2.Line, Maybe Layer2.Clef_Octave_Change) -- | type Staff_Details = MusicXML.Staff_Details -- | type Transpose = MusicXML.Transpose -- | type Directive = MusicXML.Directive -- | type Measure_Style = MusicXML.Measure_Style \end{code} \begin{code} -- | abst_Score_Partwise :: Score_Partwise -> Layer3.Score_Partwise abst_Score_Partwise = (id >< (id >< map abst_Part)) -- | abst_Part :: Part -> Layer3.Part abst_Part = fmap abst_Measure -- | abst_Measure :: Measure -> Layer3.Measure abst_Measure = catMaybes . fmap abst_Music_Data -- | abst_Music_Data :: Music_Data -> Maybe Layer3.Music_Data abst_Music_Data (Music_Data_1 x) = do x' <- abst_Note x return (Layer3.Music_Data_1 x') abst_Music_Data (Music_Data_2 x) = Just (Layer3.Music_Data_2 x) abst_Music_Data (Music_Data_3 x) = Just (Layer3.Music_Data_3 x) abst_Music_Data (Music_Data_4 _) = Nothing abst_Music_Data (Music_Data_5 x) = Just (Layer3.Music_Data_5 (abst_Attributes x)) abst_Music_Data (Music_Data_6 _) = Nothing abst_Music_Data (Music_Data_7 _) = Nothing abst_Music_Data (Music_Data_8 _) = Nothing abst_Music_Data (Music_Data_9 _) = Nothing abst_Music_Data (Music_Data_10 x) = Just (Layer3.Music_Data_10 x) abst_Music_Data (Music_Data_11 _) = Nothing abst_Music_Data (Music_Data_12 _) = Nothing abst_Music_Data (Music_Data_13 _) = Nothing -- | abst_Note :: Note -> Maybe Layer3.Note abst_Note = (\(x1,x2,x3,x4,x5,x6,_,_,_,x10,_,_,_) -> do x1' <- abst_Note_ x1 return (x1',fmap abst_Instrument x2, abst_Editorial_Voice x3, fmap abst_Type x4, fmap abst_Dot x5, fmap abst_Accidental x6, fmap abst_Staff x10)) -- | abst_Note_ :: Note_ -> Maybe Layer3.Note_ abst_Note_ (Note_1 _) = Nothing abst_Note_ (Note_2 _) = Nothing abst_Note_ (Note_3 (x1,x2,_)) = do x1' <- abst_Full_Note x1 return (Layer3.Note_3 (x1', abst_Duration x2)) -- | abst_Full_Note :: Full_Note -> Maybe Layer3.Full_Note abst_Full_Note (a,b) = do b' <- abst_Full_Note_ b return (fmap id a, b') --abst_Full_Note :: Full_Note -> (Maybe Layer3.Chord, Maybe Layer3.Full_Note_) --abst_Full_Note = (fmap id >< abst_Full_Note_) --abst_Full_Note (x,y) = do -- y' <- abst_Full_Note_ y -- return (fmap id x >< fmap id y')) -- (fmap id >< (\x -> do -- y <- abst_Full_Note_ x -- )) -- | abst_Full_Note_ :: Full_Note_ -> Maybe Layer3.Full_Note_ abst_Full_Note_ (Full_Note_1 x) = Just (Layer3.Full_Note_1 x) abst_Full_Note_ (Full_Note_2 _) = Nothing abst_Full_Note_ (Full_Note_3 _) = Just (Layer3.Full_Note_3 ()) -- | abst_Duration :: Duration -> Layer3.Duration abst_Duration = id -- | abst_Editorial_Voice :: Editorial_Voice -> Layer3.Editorial_Voice abst_Editorial_Voice = id -- | abst_Instrument :: Instrument -> Layer3.Instrument abst_Instrument = id -- | abst_Type :: Type -> Layer3.Type abst_Type = id -- | abst_Dot :: Dot -> Layer3.Dot abst_Dot = id -- | abst_Accidental :: Accidental -> Layer3.Accidental abst_Accidental = id -- | abst_Staff :: Staff -> Layer3.Staff abst_Staff = id -- | abst_Editorial :: Editorial -> Layer3.Editorial abst_Editorial = id -- | abst_Divisions :: Divisions -> Layer3.Divisions abst_Divisions = id -- | abst_Staves :: Staves -> Layer3.Staves abst_Staves = id -- | abst_Attributes :: Attributes -> Layer3.Attributes abst_Attributes (_,x2,x3,x4,x5,_,x7,x8,_,x10,_,_) = (fmap abst_Divisions x2, fmap abst_Key x3, fmap abst_Time x4, fmap abst_Staves x5, fmap abst_Instruments x7, fmap abst_Clef x8, fmap abst_Transpose x10) -- | abst_Key :: Key -> Layer3.Key abst_Key = (abst_Key_ >< fmap id) -- | abst_Key_ :: Key_ -> Layer3.Key_ abst_Key_ (Key_1 x) = Layer3.Key_1 x abst_Key_ (Key_2 x) = Layer3.Key_2 x -- | abst_Time :: Time -> Layer3.Time abst_Time = id -- | abst_Part_Symbol :: Part_Symbol -> Layer3.Part_Symbol abst_Part_Symbol = id -- | abst_Instruments :: Instruments -> Layer3.Instruments abst_Instruments = id -- | abst_Clef :: Clef -> Layer3.Clef abst_Clef = id -- | abst_Staff_Details :: Staff_Details -> Layer3.Staff_Details abst_Staff_Details = id -- | abst_Transpose :: Transpose -> Layer3.Transpose abst_Transpose = id -- | abst_Directive :: Directive -> Layer3.Directive abst_Directive = id -- | abst_Measure_Style :: Measure_Style -> Layer3.Measure_Style abst_Measure_Style = id \end{code} \begin{code} -- | rep_Score_Partwise :: Layer3.Score_Partwise -> Score_Partwise rep_Score_Partwise = (id >< (id >< map rep_Part)) -- | rep_Part :: Layer3.Part -> Part rep_Part = fmap rep_Measure -- | rep_Measure :: Layer3.Measure -> Measure rep_Measure = fmap rep_Music_Data -- | rep_Music_Data :: Layer3.Music_Data -> Music_Data rep_Music_Data (Layer3.Music_Data_1 x) = (Music_Data_1 (rep_Note x)) -- x' <- rep_Note x -- return (Music_Data_1 x') -- Layer3.Music_Data_1 ((catMaybes . (fmap abst_Note)) x) rep_Music_Data (Layer3.Music_Data_2 x) = (Music_Data_2 x) rep_Music_Data (Layer3.Music_Data_3 x) = (Music_Data_3 x) --rep_Music_Data (Layer3.Music_Data_4 _) = Nothing rep_Music_Data (Layer3.Music_Data_5 x) = (Music_Data_5 (rep_Attributes x)) --rep_Music_Data (Layer3.Music_Data_6 _) = Nothing --rep_Music_Data (Layer3.Music_Data_7 _) = Nothing --rep_Music_Data (Layer3.Music_Data_8 _) = Nothing --rep_Music_Data (Layer3.Music_Data_9 _) = Nothing rep_Music_Data (Layer3.Music_Data_10 x) = (Music_Data_10 x) --rep_Music_Data (Layer3.Music_Data_11 _) = Nothing --rep_Music_Data (Layer3.Music_Data_12 _) = Nothing --rep_Music_Data (Layer3.Music_Data_13 _) = Nothing -- | rep_Note :: Layer3.Note -> Note rep_Note (x1,x2,x3,x4,x5,x6,x10) = (rep_Note_ x1, fmap rep_Instrument x2, rep_Editorial_Voice x3, fmap rep_Type x4, fmap rep_Dot x5, fmap rep_Accidental x6, Nothing, Nothing, Nothing, fmap rep_Staff x10, [], [], []) -- (\(x1,x2,x3,x4,x5,x6,_,_,_,x10,_,_,_) -> do -- x1' <- abst_Note_ x1 -- return (x1',fmap abst_Instrument x2, abst_Editorial_Voice x3, -- fmap abst_Type x4, fmap abst_Dot x5, -- fmap abst_Accidental x6, fmap abst_Staff x10)) -- | rep_Note_ :: Layer3.Note_ -> Note_ --rep_Note_ (Note_1 _) = Nothing -- Layer3.Note_1 (abst_Grace x1, abst_Full_Note x2, -- fmap (abst_Tie >< fmap abst_Tie) x3) --rep_Note_ (Note_2 _) = Nothing -- Layer3.Note_2 (abst_Cue x1, abst_Full_Note x2, abst_Duration x3) rep_Note_ (Layer3.Note_3 (x1,x2)) = (Note_3 (rep_Full_Note x1, rep_Duration x2, Nothing)) -- x1' <- abst_Full_Note x1 -- return (Layer3.Note_3 (x1', abst_Duration x2)) -- | rep_Full_Note :: Layer3.Full_Note -> Full_Note rep_Full_Note (a,b) = (a, rep_Full_Note_ b) -- b' <- rep_Full_Note_ b -- return (fmap id a, b') --abst_Full_Note :: Full_Note -> (Maybe Layer3.Chord, Maybe Layer3.Full_Note_) --abst_Full_Note = (fmap id >< abst_Full_Note_) --abst_Full_Note (x,y) = do -- y' <- abst_Full_Note_ y -- return (fmap id x >< fmap id y')) -- (fmap id >< (\x -> do -- y <- abst_Full_Note_ x -- )) -- | rep_Full_Note_ :: Layer3.Full_Note_ -> Full_Note_ rep_Full_Note_ (Layer3.Full_Note_1 x) = (Full_Note_1 x) --rep_Full_Note_ (Full_Note_2 _) = Nothing rep_Full_Note_ (Layer3.Full_Note_3 _) = (Full_Note_3 Nothing) -- | rep_Duration :: Layer3.Duration -> Duration rep_Duration = id -- | rep_Editorial_Voice :: Layer3.Editorial_Voice -> Editorial_Voice rep_Editorial_Voice = id -- | rep_Instrument :: Layer3.Instrument -> Instrument rep_Instrument = id -- | rep_Type :: Layer3.Type -> Type rep_Type = id -- | rep_Dot :: Layer3.Dot ->Dot rep_Dot = id -- | rep_Accidental :: Layer3.Accidental -> Accidental rep_Accidental = id -- | rep_Staff :: Layer3.Staff -> Staff rep_Staff = id -- | rep_Editorial :: Layer3.Editorial -> Editorial rep_Editorial = id -- | rep_Divisions :: Layer3.Divisions -> Divisions rep_Divisions = id -- | rep_Staves :: Layer3.Staves -> Staves rep_Staves = id -- | rep_Attributes :: Layer3.Attributes -> Attributes rep_Attributes (x2,x3,x4,x5,x7,x8,x10) = ((Nothing,Nothing), fmap rep_Divisions x2, fmap rep_Key x3, fmap rep_Time x4, fmap rep_Staves x5, Nothing, fmap rep_Instruments x7, fmap rep_Clef x8, [], fmap rep_Transpose x10, [], []) --(_,x2,x3,x4,x5,_,x7,x8,_,x10,_,_) = -- (fmap abst_Divisions x2, fmap abst_Key x3, -- fmap abst_Time x4, fmap abst_Staves x5, -- fmap abst_Instruments x7, fmap abst_Clef x8, -- fmap abst_Transpose x10) -- | rep_Key :: Layer3.Key -> Key rep_Key = (rep_Key_ >< fmap id) -- | rep_Key_ :: Layer3.Key_ -> Key_ rep_Key_ (Layer3.Key_1 x) = Key_1 x rep_Key_ (Layer3.Key_2 x) = Key_2 x -- | rep_Time :: Layer3.Time -> Time rep_Time = id -- | rep_Part_Symbol :: Layer3.Part_Symbol -> Part_Symbol rep_Part_Symbol = id -- | rep_Instruments :: Layer3.Instruments -> Instruments rep_Instruments = id -- | rep_Clef :: Layer3.Clef -> Clef rep_Clef = id -- | rep_Staff_Details :: Layer3.Staff_Details -> Staff_Details rep_Staff_Details = id -- | rep_Transpose :: Layer3.Transpose -> Transpose rep_Transpose = id -- | rep_Directive :: Layer3.Directive -> Directive rep_Directive = id -- | rep_Measure_Style :: Layer3.Measure_Style -> Measure_Style rep_Measure_Style = id \end{code} \begin{code} -- | map_Score_Partwise :: (Music_Data -> Music_Data) -> Score_Partwise -> Score_Partwise map_Score_Partwise f = (id >< (id >< fmap (map_Part f))) -- | map_Part :: (Music_Data -> Music_Data) -> Part -> Part map_Part f = fmap (map_Measure f) -- | map_Measure :: (Music_Data -> Music_Data) -> Measure -> Measure map_Measure f = fmap (map_Music_Data f) -- | map_Music_Data :: (Music_Data -> Music_Data) -> Music_Data -> Music_Data map_Music_Data f = f --map_Music_Data :: Music_Data -> Music_Data --map_Music_Data f (Music_Data_1 x) = Music_Data_1 x --map_Music_Data f (Music_Data_2 x) = Music_Data_2 x --map_Music_Data f (Music_Data_3 x) = Music_Data_3 x --map_Music_Data f (Music_Data_4 x) = Music_Data_4 x --map_Music_Data f (Music_Data_5 x) = Music_Data_5 x --map_Music_Data f (Music_Data_6 x) = Music_Data_6 x --map_Music_Data f (Music_Data_7 x) = Music_Data_7 x --map_Music_Data f (Music_Data_8 x) = Music_Data_8 x --map_Music_Data f (Music_Data_9 x) = Music_Data_9 x --map_Music_Data f (Music_Data_10 x) = Music_Data_10 x --map_Music_Data f (Music_Data_11 x) = Music_Data_11 x --map_Music_Data f (Music_Data_12 x) = Music_Data_12 x --map_Music_Data f (Music_Data_13 x) = Music_Data_13 x \end{code}