\begin{code}
module Music.Analysis.MusicXML.Level5 (
    module Music.Analysis.MusicXML.Level5,
    )where
import Music.Analysis.Base 
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 qualified Music.Analysis.MusicXML.Level4 as Layer4
import Data.Maybe ()
import qualified Text.XML.MusicXML as MusicXML
\end{code} \begin{code}
-- |
type Score_Partwise = 
    (MusicXML.Document_Attributes, (MusicXML.Score_Header, [Part]))
-- |
type Part = (MusicXML.ID, [Measure])
-- | 
type Measure = ((MusicXML.CDATA, Maybe MusicXML.Yes_No, 
    Maybe MusicXML.Yes_No, Maybe MusicXML.Tenths), [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 = 
    ((MusicXML.Print_Style, MusicXML.Printout, Maybe MusicXML.CDATA, 
        Maybe MusicXML.CDATA, Maybe MusicXML.CDATA, Maybe MusicXML.CDATA, 
        Maybe MusicXML.CDATA, Maybe MusicXML.Yes_No), 
    (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 Layer4.Unpitched
                | Full_Note_3 Layer4.Rest
                  deriving (Eq, Show)
-- |
type Duration = IntegerNumber
-- |
type Editorial_Voice = MusicXML.Editorial_Voice
-- |
type Instrument = MusicXML.Instrument
-- |
type Type = (Maybe MusicXML.Symbol_Size, Layer1.Type_)
-- |
type Dot = MusicXML.Dot
-- |
type Accidental = ((Maybe MusicXML.Yes_No, Maybe MusicXML.Yes_No,
    MusicXML.Level_Display, MusicXML.Print_Style), 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 = (
    (Maybe MusicXML.CDATA, MusicXML.Print_Style, MusicXML.Print_Object),
    (Key_, [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 Key_Octave = ((MusicXML.CDATA, Maybe MusicXML.Yes_No), Layer1.Octave)
-- |
type Time = ((Maybe MusicXML.CDATA, Maybe MusicXML.Time_A, 
    MusicXML.Print_Style, MusicXML.Print_Object), Layer3.Time_B)
-- |
type Staves = MusicXML.Staves
-- |
type Part_Symbol = MusicXML.Part_Symbol
-- |
type Instruments = MusicXML.Instruments
-- |
type Clef = (
    (Maybe MusicXML.CDATA, Maybe MusicXML.Yes_No, Maybe MusicXML.Symbol_Size, 
     MusicXML.Print_Style, MusicXML.Print_Object),
    (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 -> Layer4.Score_Partwise
abst_Score_Partwise = (id >< (id >< map abst_Part))
-- |
abst_Part :: Part -> Layer4.Part
abst_Part = map abst_Measure . p2
-- |
abst_Measure :: Measure -> Layer4.Measure
abst_Measure = map abst_Music_Data . p2
-- |
abst_Music_Data :: Music_Data -> Layer4.Music_Data
abst_Music_Data (Music_Data_1 x) = Layer4.Music_Data_1 (abst_Note x)
abst_Music_Data (Music_Data_2 x) = Layer4.Music_Data_2 x
abst_Music_Data (Music_Data_3 x) = Layer4.Music_Data_3 x
abst_Music_Data (Music_Data_4 x) = Layer4.Music_Data_4 x
abst_Music_Data (Music_Data_5 x) = Layer4.Music_Data_5 (abst_Attributes x)
abst_Music_Data (Music_Data_6 x) = Layer4.Music_Data_6 x
abst_Music_Data (Music_Data_7 x) = Layer4.Music_Data_7 x
abst_Music_Data (Music_Data_8 x) = Layer4.Music_Data_8 x
abst_Music_Data (Music_Data_9 x) = Layer4.Music_Data_9 x
abst_Music_Data (Music_Data_10 x) = Layer4.Music_Data_10 x
abst_Music_Data (Music_Data_11 x) = Layer4.Music_Data_11 x
abst_Music_Data (Music_Data_12 x) = Layer4.Music_Data_12 x
abst_Music_Data (Music_Data_13 x) = Layer4.Music_Data_13 x
-- |
abst_Note :: Note -> Layer4.Note
abst_Note = 
    (\(x1,x2,x3,x4,x5,x6,x7,x8,x9,x10,x11,x12,x13) -> 
        (abst_Note_ x1, fmap abst_Instrument x2, 
        abst_Editorial_Voice x3, fmap abst_Type x4, fmap abst_Dot x5,
        fmap abst_Accidental x6, fmap abst_Time_Modification x7,
        fmap abst_Stem x8, fmap abst_Notehead x9, fmap abst_Staff x10,
        fmap abst_Beam x11, fmap abst_Notations x12, fmap abst_Lyric x13)) . 
    p2
-- |
abst_Note_ :: Note_ -> Layer4.Note_
abst_Note_ (Note_1 (x1,x2,x3)) = 
    Layer4.Note_1 (abst_Grace x1, abst_Full_Note x2, 
                    fmap (abst_Tie >< fmap abst_Tie) x3)
abst_Note_ (Note_2 (x1,x2,x3)) = 
    Layer4.Note_2 (abst_Cue x1, abst_Full_Note x2, abst_Duration x3)
abst_Note_ (Note_3 (x1,x2,x3)) = 
    Layer4.Note_3 (abst_Full_Note x1, abst_Duration x2, 
                    fmap (abst_Tie >< fmap abst_Tie) x3)
-- |
abst_Grace :: Grace -> Layer4.Grace 
abst_Grace = id
-- |
abst_Cue :: Cue -> Layer4.Cue
abst_Cue = id
-- |
abst_Tie :: Tie -> Layer4.Tie
abst_Tie = id
-- |
abst_Full_Note :: Full_Note -> Layer4.Full_Note
abst_Full_Note = (fmap id >< abst_Full_Note_)
-- |
abst_Full_Note_ :: Full_Note_ -> Layer4.Full_Note_
abst_Full_Note_ (Full_Note_1 x) = Layer4.Full_Note_1 x
abst_Full_Note_ (Full_Note_2 x) = Layer4.Full_Note_2 x
abst_Full_Note_ (Full_Note_3 x) = Layer4.Full_Note_3 x
-- |
abst_Duration :: Duration -> Layer4.Duration
abst_Duration = id
-- |
abst_Editorial_Voice :: Editorial_Voice -> Layer4.Editorial_Voice
abst_Editorial_Voice = id
-- |
abst_Instrument :: Instrument -> Layer4.Instrument
abst_Instrument = id
-- |
abst_Type :: Type -> Layer4.Type
abst_Type = p2
-- |
abst_Dot :: Dot -> Layer4.Dot
abst_Dot = id
-- |
abst_Accidental :: Accidental -> Layer4.Accidental
abst_Accidental = p2
-- |
abst_Time_Modification :: Time_Modification -> Layer4.Time_Modification
abst_Time_Modification = id
-- |
abst_Stem :: Stem -> Layer4.Stem
abst_Stem = id
-- |
abst_Notehead :: Notehead -> Layer4.Notehead
abst_Notehead = id
-- |
abst_Beam :: Beam -> Layer4.Beam
abst_Beam = id
-- |
abst_Staff :: Staff -> Layer4.Staff
abst_Staff = id
-- |
abst_Notations :: Notations -> Layer4.Notations
abst_Notations = id
-- |
abst_Editorial :: Editorial -> Layer4.Editorial
abst_Editorial = id
-- |
abst_Divisions :: Divisions -> Layer4.Divisions
abst_Divisions = id
-- |
abst_Key_Octave :: Key_Octave -> Layer2.Key_Octave
abst_Key_Octave = p2
-- |
abst_Staves :: Staves -> Layer4.Staves
abst_Staves = id
-- |
abst_Attributes :: Attributes -> Layer4.Attributes
abst_Attributes (x1,x2,x3,x4,x5,x6,x7,x8,x9,x10,x11,x12) = 
    (abst_Editorial x1, fmap abst_Divisions x2, fmap abst_Key x3,
     fmap abst_Time x4, fmap abst_Staves x5, fmap abst_Part_Symbol x6,
     fmap abst_Instruments x7, fmap abst_Clef x8, fmap abst_Staff_Details x9,
     fmap abst_Transpose x10, fmap abst_Directive x11, 
     fmap abst_Measure_Style x12)
-- |
abst_Lyric :: Lyric -> Layer4.Lyric
abst_Lyric = id
-- |
abst_Key :: Key -> Layer4.Key
abst_Key = (abst_Key_ >< fmap abst_Key_Octave) . p2
-- |
abst_Key_ :: Key_ -> Layer4.Key_
abst_Key_ (Key_1 x) = Layer4.Key_1 x
abst_Key_ (Key_2 x) = Layer4.Key_2 x
-- |
abst_Time :: Time -> Layer4.Time
abst_Time = p2
-- |
abst_Part_Symbol :: Part_Symbol -> Layer4.Part_Symbol
abst_Part_Symbol = id
-- |
abst_Instruments :: Instruments -> Layer4.Instruments
abst_Instruments = id
-- |
abst_Clef :: Clef -> Layer4.Clef
abst_Clef = p2
-- |
abst_Staff_Details :: Staff_Details -> Layer4.Staff_Details
abst_Staff_Details = id
-- |
abst_Transpose :: Transpose -> Layer4.Transpose
abst_Transpose = id
-- |
abst_Directive :: Directive -> Layer4.Directive
abst_Directive = id
-- |
abst_Measure_Style :: Measure_Style -> Layer4.Measure_Style
abst_Measure_Style = id
\end{code} \begin{code}

empty_Print_Style :: MusicXML.Print_Style
empty_Print_Style = 
    ((Nothing, Nothing, Nothing, Nothing), 
     (Nothing, Nothing, Nothing, Nothing), 
     Nothing)
empty_Printout :: MusicXML.Printout
empty_Printout = (Nothing,Nothing,Nothing,Nothing)     
empty_Level_Display :: MusicXML.Level_Display
empty_Level_Display = (Nothing,Nothing,Nothing)
\end{code} \begin{code}
-- |
rep_Score_Partwise :: Layer4.Score_Partwise -> Score_Partwise
rep_Score_Partwise = (id >< (id >< 
    (fmap ((("P"++) . show) >< id) . 
     uncurry zip . (const ([1..]::[Int]) >< id) . unzip . 
     fmap rep_Part)))
-- |
rep_Part :: Layer4.Part -> Part
rep_Part = split (const "P1") (
    uncurry zip .
    ((fmap f2 . uncurry zip . 
        ((fmap show . const ([1..]::[Int])) >< id) . 
        unzip . fmap f1) >< id) . 
    unzip . fmap rep_Measure)
    where f1 (a,b,c,d) = (a,(b,c,d))
          f2 (a,(b,c,d)) = (a,b,c,d)
-- |
rep_Measure :: Layer4.Measure -> Measure
rep_Measure = split (const ("1", Nothing, Nothing, Nothing)) (fmap rep_Music_Data) 
-- |
rep_Music_Data :: Layer4.Music_Data -> Music_Data
rep_Music_Data (Layer4.Music_Data_1 x) = Music_Data_1 (rep_Note x)
rep_Music_Data (Layer4.Music_Data_2 x) = Music_Data_2 x
rep_Music_Data (Layer4.Music_Data_3 x) = Music_Data_3 x
rep_Music_Data (Layer4.Music_Data_4 x) = Music_Data_4 x
rep_Music_Data (Layer4.Music_Data_5 x) = Music_Data_5 (rep_Attributes x)
rep_Music_Data (Layer4.Music_Data_6 x) = Music_Data_6 x
rep_Music_Data (Layer4.Music_Data_7 x) = Music_Data_7 x
rep_Music_Data (Layer4.Music_Data_8 x) = Music_Data_8 x
rep_Music_Data (Layer4.Music_Data_9 x) = Music_Data_9 x
rep_Music_Data (Layer4.Music_Data_10 x) = Music_Data_10 x
rep_Music_Data (Layer4.Music_Data_11 x) = Music_Data_11 x
rep_Music_Data (Layer4.Music_Data_12 x) = Music_Data_12 x
rep_Music_Data (Layer4.Music_Data_13 x) = Music_Data_13 x
-- |
rep_Note :: Layer4.Note -> Note
rep_Note (x1,x2,x3,x4,x5,x6,x7,x8,x9,x10,x11,x12,x13) = 
        (emptyAttrs,
        (rep_Note_ x1, fmap rep_Instrument x2, 
         rep_Editorial_Voice x3, fmap rep_Type x4, fmap rep_Dot x5,
         fmap rep_Accidental x6, fmap rep_Time_Modification x7,
         fmap rep_Stem x8, fmap rep_Notehead x9, fmap rep_Staff x10,
         fmap rep_Beam x11, fmap rep_Notations x12, fmap rep_Lyric x13))
    where emptyAttrs = (empty_Print_Style, empty_Printout,
                        Nothing,Nothing,Nothing,Nothing,Nothing,Nothing)
    
--    (\(x1,x2,x3,x4,x5,x6,x7,x8,x9,x10,x11,x12,x13) -> 
--        (abst_Note_ x1, fmap abst_Instrument x2, 
--        abst_Editorial_Voice x3, fmap abst_Type x4, fmap abst_Dot x5,
--        fmap abst_Accidental x6, fmap abst_Time_Modification x7,
--        fmap abst_Stem x8, fmap abst_Notehead x9, fmap abst_Staff x10,
--        fmap abst_Beam x11, fmap abst_Notations x12, fmap abst_Lyric x13)) . 
--    p2
-- |
rep_Note_ :: Layer4.Note_ -> Note_
rep_Note_ (Layer4.Note_1 (x1,x2,x3)) = 
    Note_1 (rep_Grace x1, rep_Full_Note x2, 
                    fmap (rep_Tie >< fmap rep_Tie) x3)
rep_Note_ (Layer4.Note_2 (x1,x2,x3)) = 
    Note_2 (rep_Cue x1, rep_Full_Note x2, rep_Duration x3)
rep_Note_ (Layer4.Note_3 (x1,x2,x3)) = 
    Note_3 (rep_Full_Note x1, rep_Duration x2, 
                    fmap (rep_Tie >< fmap rep_Tie) x3)
-- |
rep_Grace :: Layer4.Grace -> Grace
rep_Grace = id
-- |
rep_Cue :: Layer4.Cue -> Cue
rep_Cue = id
-- |
rep_Tie :: Layer4.Tie -> Tie
rep_Tie = id
-- |
rep_Full_Note :: Layer4.Full_Note -> Full_Note
rep_Full_Note = (fmap id >< rep_Full_Note_)
-- |
rep_Full_Note_ :: Layer4.Full_Note_ -> Full_Note_
rep_Full_Note_ (Layer4.Full_Note_1 x) = Full_Note_1 x
rep_Full_Note_ (Layer4.Full_Note_2 x) = Full_Note_2 x
rep_Full_Note_ (Layer4.Full_Note_3 x) = Full_Note_3 x
-- |
rep_Duration :: Layer4.Duration -> Duration
rep_Duration = id
-- |
rep_Editorial_Voice :: Layer4.Editorial_Voice -> Editorial_Voice
rep_Editorial_Voice = id
-- |
rep_Instrument :: Layer4.Instrument -> Instrument
rep_Instrument = id
-- |
rep_Type :: Layer4.Type -> Type
rep_Type = split (const Nothing) id
-- |
rep_Dot :: Dot -> Layer4.Dot
rep_Dot = id
-- |
rep_Accidental :: Layer4.Accidental -> Accidental
rep_Accidental = 
    split (const (Nothing, Nothing, empty_Level_Display, empty_Print_Style))
--            ((Nothing,Nothing,Nothing,Nothing),
--             (Nothing,Nothing,Nothing,Nothing),Nothing))) 
        id
-- |
rep_Time_Modification :: Layer4.Time_Modification -> Time_Modification
rep_Time_Modification = id
-- |
rep_Stem :: Layer4.Stem -> Stem
rep_Stem = id
-- |
rep_Notehead :: Layer4.Notehead -> Notehead
rep_Notehead = id
-- |
rep_Beam :: Layer4.Beam -> Beam
rep_Beam = id
-- |
rep_Staff :: Layer4.Staff -> Staff
rep_Staff = id
-- |
rep_Notations :: Layer4.Notations -> Notations
rep_Notations = id
-- |
rep_Editorial :: Layer4.Editorial -> Editorial
rep_Editorial = id
-- |
rep_Divisions :: Layer4.Divisions -> Divisions
rep_Divisions = id
-- |
rep_Key_Octave :: Layer2.Key_Octave -> Key_Octave
rep_Key_Octave = split (const ("0",Nothing)) id
-- |
rep_Staves :: Layer4.Staves -> Staves
rep_Staves = id
-- |
rep_Attributes :: Layer4.Attributes -> Attributes
rep_Attributes (x1,x2,x3,x4,x5,x6,x7,x8,x9,x10,x11,x12) = 
    (rep_Editorial x1, fmap rep_Divisions x2, fmap rep_Key x3,
     fmap rep_Time x4, fmap rep_Staves x5, fmap rep_Part_Symbol x6,
     fmap rep_Instruments x7, fmap rep_Clef x8, fmap rep_Staff_Details x9,
     fmap rep_Transpose x10, fmap rep_Directive x11, 
     fmap rep_Measure_Style x12)
-- |
rep_Lyric :: Layer4.Lyric -> Lyric
rep_Lyric = id
-- |
rep_Key :: Layer4.Key -> Key
rep_Key = 
    split (const (Nothing,empty_Print_Style, Nothing)) 
        (rep_Key_ >< fmap rep_Key_Octave) 
-- |
rep_Key_ :: Layer4.Key_ -> Key_
rep_Key_ (Layer4.Key_1 x) = Key_1 x
rep_Key_ (Layer4.Key_2 x) = Key_2 x
-- |
rep_Time :: Layer4.Time -> Time
rep_Time = 
    split (const (Nothing,Nothing, empty_Print_Style, Nothing))
        id
-- |
rep_Part_Symbol :: Layer4.Part_Symbol -> Part_Symbol
rep_Part_Symbol = id
-- |
rep_Instruments :: Layer4.Instruments -> Instruments
rep_Instruments = id
-- |
rep_Clef :: Layer4.Clef -> Clef
rep_Clef = 
    split (const (Nothing,Nothing,Nothing,empty_Print_Style,Nothing))
        id
-- |
rep_Staff_Details :: Layer4.Staff_Details -> Staff_Details
rep_Staff_Details = id
-- |
rep_Transpose :: Layer4.Transpose -> Transpose
rep_Transpose = id
-- |
rep_Directive :: Layer4.Directive -> Directive
rep_Directive = id
-- |
rep_Measure_Style :: Layer4.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 = (id >< fmap (map_Measure f))
-- |
map_Measure :: (Music_Data -> Music_Data) -> Measure -> Measure
map_Measure f = (id >< 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_1 x) =  Music_Data_1 x
--map_Music_Data (Music_Data_2 x) =  Music_Data_2 x
--map_Music_Data (Music_Data_3 x) =  Music_Data_3 x
--map_Music_Data (Music_Data_4 x) =  Music_Data_4 x
--map_Music_Data (Music_Data_5 x) =  Music_Data_5 x
--map_Music_Data (Music_Data_6 x) =  Music_Data_6 x
--map_Music_Data (Music_Data_7 x) =  Music_Data_7 x
--map_Music_Data (Music_Data_8 x) =  Music_Data_8 x
--map_Music_Data (Music_Data_9 x) =  Music_Data_9 x
--map_Music_Data (Music_Data_10 x) = Music_Data_10 x
--map_Music_Data (Music_Data_11 x) = Music_Data_11 x
--map_Music_Data (Music_Data_12 x) = Music_Data_12 x
--map_Music_Data (Music_Data_13 x) = Music_Data_13 x

--map_Score_Partwise :: (Layer4.Score_Partwise -> Layer4.Score_Partwise) -> 
--    Score_Partwise -> Score_Partwise
--map_Score_Partwise f = (id >< (id >< f))
--map_Part :: (Layer4.Part -> Layer4.Part) -> Part -> Part
--map_Part f = split p1 (f . abst_Part)
--( >< f)
--map_Measure :: (Layer4.Measure -> Layer4.Measure) -> Measure -> Measure
--map_Measure f = (id >< f )
\end{code}