\begin{code}
-- | 
-- Maintainer : silva.samuel@alumni.uminho.pt
-- Stability  : experimental
-- Portability: HaXml
-- This module make interface with MusicXML using HaXML library.
module Music.Analysis.MusicXML 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 qualified Music.Analysis.MusicXML.Level5 as Layer5
import qualified Music.Analysis.MusicXML.Level6 as Layer6 ()

import qualified Text.XML.MusicXML as MusicXML 
import qualified Text.XML.MusicXML.Partwise as Partwise
import qualified Text.XML.MusicXML.Timewise as Timewise

import Data.Function (on)
import Data.List (groupBy, sortBy)
import Data.Maybe (isJust)
import Data.Char (isDigit)
import Prelude 
\end{code} \begin{code}
-- |
toTimewise :: Partwise.Score_Partwise -> Timewise.Score_Timewise
toTimewise = (id >< (id >< transpose))
-- |
toPartwise :: Timewise.Score_Timewise -> Partwise.Score_Partwise
toPartwise = (id >< (id >< transpose))
-- |
transpose :: [(a,[(b,c)])] -> [(b,[(a,c)])]
transpose [] = []
transpose ((_, []) : xss) = transpose xss
transpose ((a, ((b,x):xs)) : xss) = 
    (b, (a, x) : [(a, h) | (_, (_,h):_) <- xss]) : 
    (transpose ((a, xs) : [t | t <- xss]))
\end{code} \begin{code}
-- |
abst_Score_Partwise :: MusicXML.Score_Partwise -> Layer5.Score_Partwise
abst_Score_Partwise = (id >< (id >< fmap abst_Part))
-- |
abst_Part :: Partwise.Part -> Layer5.Part
abst_Part = (id >< fmap abst_Measure)
-- |
abst_Measure :: Partwise.Measure -> Layer5.Measure
abst_Measure = (id >< fmap abst_Music_Data)
-- |
abst_Music_Data :: MusicXML.Music_Data_ -> Layer5.Music_Data
abst_Music_Data (MusicXML.Music_Data_1 x) = Layer5.Music_Data_1 (abst_Note x)
abst_Music_Data (MusicXML.Music_Data_2 x) = Layer5.Music_Data_2 x
abst_Music_Data (MusicXML.Music_Data_3 x) = Layer5.Music_Data_3 x
abst_Music_Data (MusicXML.Music_Data_4 x) = Layer5.Music_Data_4 x
abst_Music_Data (MusicXML.Music_Data_5 x) = 
    Layer5.Music_Data_5 (abst_Attributes x)
abst_Music_Data (MusicXML.Music_Data_6 x) = Layer5.Music_Data_6 x
abst_Music_Data (MusicXML.Music_Data_7 x) = Layer5.Music_Data_7 x
abst_Music_Data (MusicXML.Music_Data_8 x) = Layer5.Music_Data_8 x
abst_Music_Data (MusicXML.Music_Data_9 x) = Layer5.Music_Data_9 x
abst_Music_Data (MusicXML.Music_Data_10 x) = Layer5.Music_Data_10 x
abst_Music_Data (MusicXML.Music_Data_11 x) = Layer5.Music_Data_11 x
abst_Music_Data (MusicXML.Music_Data_12 x) = Layer5.Music_Data_12 x
abst_Music_Data (MusicXML.Music_Data_13 x) = Layer5.Music_Data_13 x
-- |
abst_Note :: MusicXML.Note -> Layer5.Note
abst_Note = (id >< ((\(x1,x2,x3,x4,x5,x6,x7,x8,x9,x10,x11,x12,x13) -> 
--    x4' <- fmap abst_Type x4
        (abst_Note_ x1, fmap abst_Instrument x2, 
             abst_Editorial_Voice x3,
             (maybe Nothing id . fmap abst_Type) x4, fmap abst_Dot x5, 
             (maybe Nothing id . 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))))
-- |
abst_Note_ :: MusicXML.Note_ -> Layer5.Note_
abst_Note_ (MusicXML.Note_1 (x1,x2,x3)) = 
    Layer5.Note_1 (abst_Grace x1, abst_Full_Note x2, 
                    fmap (abst_Tie >< fmap abst_Tie) x3)
abst_Note_ (MusicXML.Note_2 (x1,x2,x3)) = 
    Layer5.Note_2 (abst_Cue x1, abst_Full_Note x2, abst_Duration x3)
abst_Note_ (MusicXML.Note_3 (x1,x2,x3)) =
    Layer5.Note_3 (abst_Full_Note x1, abst_Duration x2, 
                    fmap (abst_Tie >< fmap abst_Tie) x3)
-- |
abst_Grace :: MusicXML.Grace -> Layer5.Grace
abst_Grace = id
-- |
abst_Cue :: MusicXML.Cue -> Layer5.Cue
abst_Cue = id
-- |
abst_Instrument :: MusicXML.Instrument -> Layer5.Instrument
abst_Instrument = id
-- |
abst_Duration :: MusicXML.Duration -> Layer5.Duration
abst_Duration = maybe 1 id . read_IntegerNumber
-- |
abst_Full_Note :: MusicXML.Full_Note -> Layer5.Full_Note
abst_Full_Note = fmap id >< abst_Full_Note_
-- |
abst_Full_Note_ :: MusicXML.Full_Note_ -> Layer5.Full_Note_
abst_Full_Note_ (MusicXML.Full_Note_1 x) = Layer5.Full_Note_1 (abst_Pitch x)
abst_Full_Note_ (MusicXML.Full_Note_2 x) = Layer5.Full_Note_2 (abst_Unpitched x)
abst_Full_Note_ (MusicXML.Full_Note_3 x) = Layer5.Full_Note_3 (abst_Rest x)
-- |
abst_Pitch :: MusicXML.Pitch -> Layer2.Pitch
abst_Pitch (a,b,c) = 
    ((maybe Layer1.C id . abst_Step) a, 
     (maybe Nothing id . fmap abst_Alter) b, abst_Octave c)
-- |
abst_Step :: MusicXML.Step -> Maybe Layer1.Step
abst_Step "A" = Just Layer1.A
abst_Step "B" = Just Layer1.B
abst_Step "C" = Just Layer1.C
abst_Step "D" = Just Layer1.D
abst_Step "E" = Just Layer1.E
abst_Step "F" = Just Layer1.F
abst_Step "G" = Just Layer1.G
abst_Step _   = Nothing
-- |
abst_Alter :: MusicXML.Alter -> Maybe Layer1.Alter
abst_Alter = read_Number
-- |
abst_Octave :: MusicXML.Octave -> Layer1.Octave
abst_Octave = maybe 4 id . read_IntegerNumber
-- |
abst_Unpitched :: MusicXML.Unpitched -> Layer4.Unpitched
abst_Unpitched = id
-- |
abst_Rest :: MusicXML.Rest -> Layer4.Rest
abst_Rest = id
-- |
abst_Tie :: MusicXML.Tie -> Layer5.Tie
abst_Tie = id
-- |
abst_Editorial_Voice :: MusicXML.Editorial_Voice -> Layer5.Editorial_Voice
abst_Editorial_Voice = id
-- |
abst_Type :: MusicXML.Type -> Maybe Layer5.Type
abst_Type (a,b) = do -- (id >< abst_Type_)
    b' <- abst_Type_ b
    return (a,b')
-- |
abst_Type_ :: MusicXML.PCDATA -> Maybe Layer1.Type_
abst_Type_ "long"    = Just Layer1.Long
abst_Type_ "breve"   = Just Layer1.Breve
abst_Type_ "whole"   = Just Layer1.Whole
abst_Type_ "half"    = Just Layer1.Half
abst_Type_ "quarter" = Just Layer1.Quarter
abst_Type_ "eighth"  = Just Layer1.Eighth
abst_Type_ "16th"    = Just Layer1.Th16
abst_Type_ "32nd"    = Just Layer1.Th32
abst_Type_ "64th"    = Just Layer1.Th64
abst_Type_ "128th"   = Just Layer1.Th128
abst_Type_ "256th"   = Just Layer1.Th256
abst_Type_ _         = Nothing

-- |
abst_Dot :: MusicXML.Dot -> Layer5.Dot
abst_Dot = id
-- |
abst_Accidental :: MusicXML.Accidental -> Maybe Layer5.Accidental
abst_Accidental (a,b) = do
    b' <- abst_Accidental_ b
    return (a,b')

abst_Accidental_ :: MusicXML.PCDATA -> Maybe Layer1.Accidental_
abst_Accidental_ "sharp"                = Just Layer1.Sharp
abst_Accidental_ "natural"              = Just Layer1.Natural
abst_Accidental_ "flat"                 = Just Layer1.Flat
abst_Accidental_ "double-sharp"         = Just Layer1.Double_Sharp
abst_Accidental_ "sharp-sharp"          = Just Layer1.Sharp_Sharp
abst_Accidental_ "flat-flat"            = Just Layer1.Flat_Flat
abst_Accidental_ "natural-sharp"        = Just Layer1.Natural_Sharp
abst_Accidental_ "natural-flat"         = Just Layer1.Natural_Flat
abst_Accidental_ "quarter-sharp"        = Just Layer1.Quarter_Sharp
abst_Accidental_ "quarter-flat"         = Just Layer1.Quarter_Flat
abst_Accidental_ "three-quarters-sharp" = Just Layer1.Three_Quarters_Sharp
abst_Accidental_ "three-quarters-flat"  = Just Layer1.Three_Quarters_Flat
abst_Accidental_ _                      = Nothing 
-- |
abst_Time_Modification :: MusicXML.Time_Modification -> Layer5.Time_Modification
abst_Time_Modification = id
-- |
abst_Stem :: MusicXML.Stem -> Layer5.Stem
abst_Stem = id
-- |
abst_Notehead :: MusicXML.Notehead -> Layer5.Notehead
abst_Notehead = id
-- |
abst_Staff :: MusicXML.Staff -> Layer5.Staff
abst_Staff = maybe 1 id . read_IntegerNumber
-- |
abst_Beam :: MusicXML.Beam -> Layer5.Beam
abst_Beam = id
-- |
abst_Notations :: MusicXML.Notations -> Layer5.Notations
abst_Notations = id
-- |
abst_Lyric :: MusicXML.Lyric -> Layer5.Lyric
abst_Lyric = id 

-- |
abst_Attributes :: MusicXML.Attributes -> Layer5.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_Editorial :: MusicXML.Editorial -> Layer5.Editorial
abst_Editorial = id
-- |
abst_Divisions :: MusicXML.Divisions -> Layer5.Divisions
abst_Divisions = maybe 1 id . read_IntegerNumber
-- |
abst_Key :: MusicXML.Key -> Layer5.Key
abst_Key = id >< (abst_Key_ >< fmap abst_Key_Octave)
-- |
abst_Key_ :: MusicXML.Key_ -> Layer5.Key_
abst_Key_ (MusicXML.Key_1 (x1,x2,x3)) = 
    Layer5.Key_1 (x1, abst_Fifths x2, (maybe Nothing id . fmap abst_Mode) x3)
abst_Key_ (MusicXML.Key_2 x) = 
    Layer5.Key_2 (fmap (abst_Key_Step >< abst_Key_Alter) x)
-- |
abst_Fifths :: MusicXML.Fifths -> Layer2.Fifths
abst_Fifths = maybe 0 id . read_IntegerNumber
-- |
abst_Mode :: MusicXML.Mode -> Maybe Layer2.Mode
abst_Mode "major"      = Just Layer2.Major
abst_Mode "minor"      = Just Layer2.Minor
abst_Mode "dorian"     = Just Layer2.Dorian
abst_Mode "phrygian"   = Just Layer2.Phrygian
abst_Mode "lydian"     = Just Layer2.Lydian
abst_Mode "mixolydian" = Just Layer2.Mixolydian
abst_Mode "aeolian"    = Just Layer2.Aeolian
abst_Mode "ionian"     = Just Layer2.Ionian
abst_Mode "locrian"    = Just Layer2.Locrian
abst_Mode _            = Nothing 
-- |
abst_Key_Step :: MusicXML.Key_Step -> Layer2.Key_Step
abst_Key_Step = maybe Layer1.C id . abst_Step
-- |
abst_Key_Alter :: MusicXML.Key_Alter -> Layer2.Key_Alter
abst_Key_Alter = maybe 0 id . abst_Alter
-- |
abst_Key_Octave :: MusicXML.Key_Octave -> Layer5.Key_Octave
abst_Key_Octave = id >< abst_Octave 
-- |
abst_Time :: MusicXML.Time -> Layer5.Time
abst_Time = id >< abst_Time_B
-- |
abst_Time_B :: MusicXML.Time_B -> Layer3.Time_B
abst_Time_B (MusicXML.Time_5 x) = 
    Layer3.Time_5 (fmap (abst_Beats >< abst_Beat_Type) x)
abst_Time_B (MusicXML.Time_6 x) = Layer3.Time_6 x
-- |
abst_Beats :: MusicXML.Beats -> Layer3.Beats
abst_Beats = 
    maybe (4, Nothing) id .
    (\(a,b) -> maybe Nothing (\a' -> Just (a',b)) a) .
    (read_IntegerNumber >< 
        (either (const Nothing) (read_IntegerNumber . tail) . grd null)) . 
    span (/='+')
-- |
abst_Beat_Type :: MusicXML.Beat_Type -> Layer3.Beat_Type
abst_Beat_Type = 
    maybe 4 id .
    maybe Nothing (e2m . (const () -|- id) . grd (<0)) .
    read_IntegerNumber
-- |
abst_Staves :: MusicXML.Staves -> Layer5.Staves
abst_Staves = id
-- |
abst_Part_Symbol :: MusicXML.Part_Symbol -> Layer5.Part_Symbol
abst_Part_Symbol = id
-- |
abst_Instruments :: MusicXML.Instruments -> Layer5.Instruments
abst_Instruments = id
-- |
abst_Clef :: MusicXML.Clef -> Layer5.Clef
abst_Clef = 
    id >< (flatl . 
            ((maybe Layer2.Clef_Sign_None id . abst_Sign >< 
                fmap abst_Line) >< fmap abst_Clef_Octave_Change) . 
        unflatl)
-- |
abst_Sign :: MusicXML.Sign -> Maybe Layer2.Sign
abst_Sign "G"          = Just Layer2.Clef_Sign_G
abst_Sign "F"          = Just Layer2.Clef_Sign_F
abst_Sign "C"          = Just Layer2.Clef_Sign_C
abst_Sign "percussion" = Just Layer2.Clef_Sign_Percussion
abst_Sign "TAB"        = Just Layer2.Clef_Sign_TAB
abst_Sign "none"       = Just Layer2.Clef_Sign_None
abst_Sign _            = Nothing
-- |
abst_Line :: MusicXML.Line -> Layer2.Line
abst_Line = maybe 1 id . read_IntegerNumber
-- |
abst_Clef_Octave_Change :: 
    MusicXML.Clef_Octave_Change -> Layer2.Clef_Octave_Change
abst_Clef_Octave_Change = maybe 0 id . read_IntegerNumber

-- |
abst_Staff_Details :: MusicXML.Staff_Details -> Layer5.Staff_Details
abst_Staff_Details = id
-- |
abst_Transpose :: MusicXML.Transpose -> Layer5.Transpose
abst_Transpose = id
-- |
abst_Directive :: MusicXML.Directive -> Layer5.Directive
abst_Directive = id
-- |
abst_Measure_Style :: MusicXML.Measure_Style -> Layer5.Measure_Style
abst_Measure_Style = id

\end{code} \begin{code}
-- |
rep_Score_Partwise :: Layer5.Score_Partwise -> MusicXML.Score_Partwise 
rep_Score_Partwise = (id >< (id >< fmap rep_Part))
-- |
rep_Part :: Layer5.Part -> Partwise.Part
rep_Part = (id >< fmap rep_Measure)
-- |
rep_Measure :: Layer5.Measure -> Partwise.Measure
rep_Measure = (id >< fmap rep_Music_Data)
-- |
rep_Music_Data :: Layer5.Music_Data -> MusicXML.Music_Data_
rep_Music_Data (Layer5.Music_Data_1 x) = MusicXML.Music_Data_1 (rep_Note x)
rep_Music_Data (Layer5.Music_Data_2 x) = MusicXML.Music_Data_2 x
rep_Music_Data (Layer5.Music_Data_3 x) = MusicXML.Music_Data_3 x
rep_Music_Data (Layer5.Music_Data_4 x) = MusicXML.Music_Data_4 x
rep_Music_Data (Layer5.Music_Data_5 x) = 
    MusicXML.Music_Data_5 (rep_Attributes x)
rep_Music_Data (Layer5.Music_Data_6 x) =  MusicXML.Music_Data_6 x
rep_Music_Data (Layer5.Music_Data_7 x) =  MusicXML.Music_Data_7 x
rep_Music_Data (Layer5.Music_Data_8 x) =  MusicXML.Music_Data_8 x
rep_Music_Data (Layer5.Music_Data_9 x) =  MusicXML.Music_Data_9 x
rep_Music_Data (Layer5.Music_Data_10 x) = MusicXML.Music_Data_10 x
rep_Music_Data (Layer5.Music_Data_11 x) = MusicXML.Music_Data_11 x
rep_Music_Data (Layer5.Music_Data_12 x) = MusicXML.Music_Data_12 x
rep_Music_Data (Layer5.Music_Data_13 x) = MusicXML.Music_Data_13 x
-- |
rep_Note :: Layer5.Note -> MusicXML.Note
rep_Note = (id >< ((\(x1,x2,x3,x4,x5,x6,x7,x8,x9,x10,x11,x12,x13) -> 
--    x4' <- fmap abst_Type x4
        (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))))
-- |
rep_Note_ :: Layer5.Note_ -> MusicXML.Note_
rep_Note_ (Layer5.Note_1 (x1,x2,x3)) = 
    MusicXML.Note_1 (rep_Grace x1, rep_Full_Note x2, 
                    fmap (rep_Tie >< fmap rep_Tie) x3)
rep_Note_ (Layer5.Note_2 (x1,x2,x3)) = 
    MusicXML.Note_2 (rep_Cue x1, rep_Full_Note x2, rep_Duration x3)
rep_Note_ (Layer5.Note_3 (x1,x2,x3)) =
    MusicXML.Note_3 (rep_Full_Note x1, rep_Duration x2, 
                    fmap (rep_Tie >< fmap rep_Tie) x3)
-- |
rep_Grace :: Layer5.Grace -> MusicXML.Grace
rep_Grace = id
-- |
rep_Cue :: Layer5.Cue -> MusicXML.Cue
rep_Cue = id
-- |
rep_Instrument :: Layer5.Instrument -> MusicXML.Instrument
rep_Instrument = id
-- |
rep_Duration :: Layer5.Duration -> MusicXML.Duration
rep_Duration = show
-- |
rep_Full_Note :: Layer5.Full_Note -> MusicXML.Full_Note
rep_Full_Note = fmap id >< rep_Full_Note_
-- |
rep_Full_Note_ :: Layer5.Full_Note_ -> MusicXML.Full_Note_
rep_Full_Note_ (Layer5.Full_Note_1 x) = MusicXML.Full_Note_1 (rep_Pitch x)
rep_Full_Note_ (Layer5.Full_Note_2 x) = MusicXML.Full_Note_2 (rep_Unpitched x)
rep_Full_Note_ (Layer5.Full_Note_3 x) = MusicXML.Full_Note_3 (rep_Rest x)
-- |
rep_Pitch :: Layer2.Pitch -> MusicXML.Pitch
rep_Pitch (a,b,c) = 
    (rep_Step a, fmap rep_Alter b, rep_Octave c)
-- |
rep_Step :: Layer1.Step -> MusicXML.Step
rep_Step Layer1.A = "A"
rep_Step Layer1.B = "B"
rep_Step Layer1.C = "C"
rep_Step Layer1.D = "D"
rep_Step Layer1.E = "E"
rep_Step Layer1.F = "F"
rep_Step Layer1.G = "G"
-- |
rep_Alter :: Layer1.Alter -> MusicXML.Alter
rep_Alter = show
-- |
rep_Octave :: Layer1.Octave -> MusicXML.Octave
rep_Octave = show
-- |
rep_Unpitched :: Layer4.Unpitched -> MusicXML.Unpitched
rep_Unpitched = id
-- |
rep_Rest :: Layer4.Rest -> MusicXML.Rest
rep_Rest = id
-- |
rep_Tie :: Layer5.Tie -> MusicXML.Tie
rep_Tie = id
-- |
rep_Editorial_Voice :: MusicXML.Editorial_Voice -> Layer5.Editorial_Voice
rep_Editorial_Voice = id
-- |
rep_Type :: Layer5.Type -> MusicXML.Type
rep_Type = id >< rep_Type_ 
-- |
rep_Type_ :: Layer1.Type_ -> MusicXML.PCDATA
rep_Type_ Layer1.Long       = "long"
rep_Type_ Layer1.Breve      = "breve"
rep_Type_ Layer1.Whole      = "whole"
rep_Type_ Layer1.Half       = "half"
rep_Type_ Layer1.Quarter    = "quarter"
rep_Type_ Layer1.Eighth     = "eighth"
rep_Type_ Layer1.Th16       = "16th"
rep_Type_ Layer1.Th32       = "32nd"
rep_Type_ Layer1.Th64       = "64th"
rep_Type_ Layer1.Th128      = "128th"
rep_Type_ Layer1.Th256      = "256th"
-- |
rep_Dot :: Layer5.Dot -> MusicXML.Dot
rep_Dot = id
-- |
rep_Accidental :: Layer5.Accidental -> MusicXML.Accidental
rep_Accidental = id >< rep_Accidental_ 
-- |
rep_Accidental_ :: Layer1.Accidental_ -> MusicXML.PCDATA
rep_Accidental_ Layer1.Sharp                = "sharp"
rep_Accidental_ Layer1.Natural              = "natural"
rep_Accidental_ Layer1.Flat                 = "flat"
rep_Accidental_ Layer1.Double_Sharp         = "double-sharp"
rep_Accidental_ Layer1.Sharp_Sharp          = "sharp-sharp"
rep_Accidental_ Layer1.Flat_Flat            = "flat-flat"
rep_Accidental_ Layer1.Natural_Sharp        = "natural-sharp"
rep_Accidental_ Layer1.Natural_Flat         = "natural-flat"
rep_Accidental_ Layer1.Quarter_Sharp        = "quarter-sharp"
rep_Accidental_ Layer1.Quarter_Flat         = "quarter-flat"
rep_Accidental_ Layer1.Three_Quarters_Sharp = "three-quarters-sharp"
rep_Accidental_ Layer1.Three_Quarters_Flat  = "three-quarters-flat"
-- |
rep_Time_Modification :: MusicXML.Time_Modification -> Layer5.Time_Modification
rep_Time_Modification = id
-- |
rep_Stem :: Layer5.Stem -> MusicXML.Stem
rep_Stem = id
-- |
rep_Notehead :: Layer5.Notehead -> MusicXML.Notehead
rep_Notehead = id
-- |
rep_Staff :: Layer5.Staff -> MusicXML.Staff
rep_Staff = show
-- |
rep_Beam :: Layer5.Beam -> MusicXML.Beam
rep_Beam = id
-- |
rep_Notations :: Layer5.Notations -> MusicXML.Notations
rep_Notations = id
-- |
rep_Lyric :: Layer5.Lyric -> MusicXML.Lyric
rep_Lyric = id 

-- |
rep_Attributes :: Layer5.Attributes -> MusicXML.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_Editorial :: Layer5.Editorial -> MusicXML.Editorial
rep_Editorial = id
-- |
rep_Divisions :: Layer5.Divisions -> MusicXML.Divisions
rep_Divisions = show
-- |
rep_Key :: Layer5.Key -> MusicXML.Key
rep_Key = id >< (rep_Key_ >< fmap rep_Key_Octave)
-- |
rep_Key_ :: Layer5.Key_ -> MusicXML.Key_
rep_Key_ (Layer5.Key_1 (x1,x2,x3)) = 
    MusicXML.Key_1 (x1, rep_Fifths x2, fmap rep_Mode x3)
rep_Key_ (Layer5.Key_2 x) = 
    MusicXML.Key_2 (fmap (rep_Key_Step >< rep_Key_Alter) x)
-- |
rep_Fifths :: Layer2.Fifths -> MusicXML.Fifths
rep_Fifths = show
-- |
rep_Mode :: Layer2.Mode -> MusicXML.Mode
rep_Mode Layer2.Major       = "major"
rep_Mode Layer2.Minor       = "minor"
rep_Mode Layer2.Dorian      = "dorian"
rep_Mode Layer2.Phrygian    = "phrygian"
rep_Mode Layer2.Lydian      = "lydian"
rep_Mode Layer2.Mixolydian  = "mixolydian"
rep_Mode Layer2.Aeolian     = "aeolian"
rep_Mode Layer2.Ionian      = "ionian"
rep_Mode Layer2.Locrian     = "locrian"
-- |
rep_Key_Step :: Layer2.Key_Step -> MusicXML.Key_Step
rep_Key_Step = rep_Step
-- |
rep_Key_Alter :: Layer2.Key_Alter -> MusicXML.Key_Alter
rep_Key_Alter = rep_Alter
-- |
rep_Key_Octave :: Layer5.Key_Octave -> MusicXML.Key_Octave
rep_Key_Octave = id >< rep_Octave 
-- |
rep_Time :: Layer5.Time -> MusicXML.Time
rep_Time = id >< rep_Time_B
-- |
rep_Time_B :: Layer3.Time_B -> MusicXML.Time_B
rep_Time_B (Layer3.Time_5 x) = 
    MusicXML.Time_5 (fmap (rep_Beats >< rep_Beat_Type) x)
rep_Time_B (Layer3.Time_6 x) = MusicXML.Time_6 x
-- |
rep_Beats :: Layer3.Beats -> MusicXML.Beats
rep_Beats = uncurry (++) . swap . (show >< maybe "" ((++"+").show))
--    maybe (4, Nothing) id .
--    (\(a,b) -> maybe Nothing (\a' -> Just (a',b)) a) .
--    (read_IntegerNumber >< 
--        (either (const Nothing) (read_IntegerNumber . tail) . grd null)) . 
--    span (/='+')
-- |
rep_Beat_Type :: Layer3.Beat_Type -> MusicXML.Beat_Type
rep_Beat_Type = show
--    maybe 4 id .
--    maybe Nothing (e2m . (const () -|- id) . grd (<0)) .
--    read_IntegerNumber
-- |
rep_Staves :: Layer5.Staves -> MusicXML.Staves
rep_Staves = id
-- |
rep_Part_Symbol :: Layer5.Part_Symbol -> MusicXML.Part_Symbol
rep_Part_Symbol = id
-- |
rep_Instruments :: Layer5.Instruments -> MusicXML.Instruments
rep_Instruments = id
-- |
rep_Clef :: Layer5.Clef -> MusicXML.Clef
rep_Clef = 
    id >< (flatl . 
            ((rep_Sign >< fmap rep_Line) >< fmap rep_Clef_Octave_Change) . 
        unflatl)
-- |
rep_Sign :: Layer2.Sign -> MusicXML.Sign
rep_Sign Layer2.Clef_Sign_G          = "G"
rep_Sign Layer2.Clef_Sign_F          = "F"
rep_Sign Layer2.Clef_Sign_C          = "C"
rep_Sign Layer2.Clef_Sign_Percussion = "percussion"
rep_Sign Layer2.Clef_Sign_TAB        = "TAB"
rep_Sign Layer2.Clef_Sign_None       = "none"
-- |
rep_Line :: Layer2.Line -> MusicXML.Line
rep_Line = show
-- |
rep_Clef_Octave_Change :: 
    Layer2.Clef_Octave_Change -> MusicXML.Clef_Octave_Change
rep_Clef_Octave_Change = show

-- |
rep_Staff_Details :: Layer5.Staff_Details -> MusicXML.Staff_Details
rep_Staff_Details = id
-- |
rep_Transpose :: Layer5.Transpose -> MusicXML.Transpose
rep_Transpose = id
-- |
rep_Directive :: Layer5.Directive -> MusicXML.Directive
rep_Directive = id
-- |
rep_Measure_Style :: Layer5.Measure_Style -> MusicXML.Measure_Style
rep_Measure_Style = id

\end{code} \begin{code}

dur_Duration :: String -> IntegerNumber
dur_Duration = maybe 0 id . read_IntegerNumber
dur_Backup :: MusicXML.Backup -> IntegerNumber -> IntegerNumber
dur_Backup (x,_) = \y -> y - (dur_Duration x)
dur_Forward :: MusicXML.Forward -> IntegerNumber -> IntegerNumber
dur_Forward (x,_,_) = \y -> y + (dur_Duration x)

dur_Note_ :: MusicXML.Note_ -> IntegerNumber -> IntegerNumber
dur_Note_ (MusicXML.Note_1 _) = id
dur_Note_ (MusicXML.Note_2 (_,_,x)) = \y -> y + dur_Duration x
dur_Note_ (MusicXML.Note_3 (_,x,_)) = \y -> y + dur_Duration x

dur_Note :: MusicXML.Note -> IntegerNumber -> IntegerNumber
dur_Note (_,(x,_,_,_,_,_,_,_,_,_,_,_,_)) = dur_Note_ x 

dur_Attributes :: MusicXML.Attributes -> Maybe MusicXML.Divisions
dur_Attributes (_,x,_,_,_,_,_,_,_,_,_,_) = dur_Divisions x

dur_Divisions :: Maybe a -> Maybe a
dur_Divisions (Nothing) = Nothing
dur_Divisions (Just x) = Just x

dur_Music_Data_ :: MusicXML.Music_Data_ -> 
    (MusicXML.Divisions, IntegerNumber) -> (MusicXML.Divisions, IntegerNumber)
dur_Music_Data_ (MusicXML.Music_Data_1 x) (a,b) = (a, dur_Note x b)
dur_Music_Data_ (MusicXML.Music_Data_2 x) (a,b) = (a, dur_Backup x b)
dur_Music_Data_ (MusicXML.Music_Data_3 x) (a,b) = (a, dur_Forward x b)
dur_Music_Data_ (MusicXML.Music_Data_5 x) (a,b) = (maybe a id (dur_Attributes x), b)
dur_Music_Data_ (_) (a,b) = (a,b)


\end{code} \begin{code}
-- |
map_Score_Partwise' :: (MusicXML.Music_Data_ -> MusicXML.Music_Data_) -> 
    MusicXML.Score_Partwise -> MusicXML.Score_Partwise 
map_Score_Partwise' f = (id >< (id >< fmap (map_Part' f)))
-- |
map_Part' :: (MusicXML.Music_Data_ -> MusicXML.Music_Data_) -> 
    Partwise.Part -> Partwise.Part
map_Part' f = (id >< fmap (map_Measure' f))
-- |
map_Measure' :: (MusicXML.Music_Data_ -> MusicXML.Music_Data_) -> 
    Partwise.Measure -> Partwise.Measure
map_Measure' f = (id >< fmap (map_Music_Data' f))
-- |
map_Music_Data' :: (MusicXML.Music_Data_ -> MusicXML.Music_Data_) -> 
    MusicXML.Music_Data_ -> MusicXML.Music_Data_
map_Music_Data' f = f
--map_Music_Data (MusicXML.Music_Data_1 x) = MusicXML.Music_Data_1 x
--map_Music_Data (MusicXML.Music_Data_2 x) = MusicXML.Music_Data_2 x
--map_Music_Data (MusicXML.Music_Data_3 x) = MusicXML.Music_Data_3 x
--map_Music_Data (MusicXML.Music_Data_4 x) = MusicXML.Music_Data_4 x
--map_Music_Data (MusicXML.Music_Data_5 x) = MusicXML.Music_Data_5 x
--map_Music_Data (MusicXML.Music_Data_6 x) = MusicXML.Music_Data_6 x
--map_Music_Data (MusicXML.Music_Data_7 x) = MusicXML.Music_Data_7 x
--map_Music_Data (MusicXML.Music_Data_8 x) = MusicXML.Music_Data_8 x
--map_Music_Data (MusicXML.Music_Data_9 x) = MusicXML.Music_Data_9 x
--map_Music_Data (MusicXML.Music_Data_10 x) = MusicXML.Music_Data_10 x
--map_Music_Data (MusicXML.Music_Data_11 x) = MusicXML.Music_Data_11 x
--map_Music_Data (MusicXML.Music_Data_12 x) = MusicXML.Music_Data_12 x
--map_Music_Data (MusicXML.Music_Data_13 x) = MusicXML.Music_Data_13 x
\end{code} \begin{code}
-- |
read_Number :: String -> Maybe Number
read_Number = 
    e2m . (const () -|- read) . 
    grd (\x -> null x || not (all isDigit x))    
-- |
read_IntegerNumber :: String -> Maybe IntegerNumber
read_IntegerNumber ('-':str) = 
    ((e2m . (const () -|- negate) . m2e) . read_IntegerNumber) str
read_IntegerNumber str = 
    (e2m . (const () -|- read) . 
        grd (\x -> null x || not (all isDigit x))) str 
-- |
coread_Number :: String -> Either Number String
coread_Number = 
    coswap . (id -|- read) . grd (\x -> null x || not (all isDigit x))
-- |
coread_IntegerNumber :: String -> Either IntegerNumber String
coread_IntegerNumber = 
    coswap . (id -|- read) . grd (\x -> null x || not (all isDigit x))
\end{code} \begin{nocode} --run :: [MusicXML.Music_Data_] -> [MusicXML.Music_Data_] -> -- ([MusicXML.Music_Data_],[MusicXML.Music_Data_]) run [] s = (s,[]) run ((h@(MusicXML.Music_Data_1 _)):t) s = run t (s++[h]) run ((h@(MusicXML.Music_Data_2 _)):t) s = run t (s++[h]) run ((h@(MusicXML.Music_Data_3 _)):t) s = run t (s++[h]) run (h:t) s = run t (s++[h]) \end{nocode} \begin{nocode} runOffSet :: MusicXML.Music_Data -> IntegerNumber -> [IntegerNumber] runOffSet [] = \_ -> [] --runOffSet ((h@(MusicXML.Music_Data_1 _)):_) = \n -> (n+) (getOffSet h) --runOffSet ((h@(MusicXML.Music_Data_2 _)):_) = \n -> (n-) (getOffSet h) --runOffSet ((h@(MusicXML.Music_Data_3 _)):_) = \n -> (n+) (getOffSet h) runOffSet (h:t) = \n -> (n + getOffSet h) : runOffSet t (n + getOffSet h) --runOffSet _ = \n -> n runOffSet' :: MusicXML.Music_Data -> [IntegerNumber] runOffSet' = flip (foldr (\h t -> \n -> (n + getOffSet h) : t (n + getOffSet h)) (const [])) 0 --getIndex :: MusicXML.Music_Data -> [(Int, MusicXML.Music_Data_)] --getIndex = zip [1..] struct :: MusicXML.Music_Data -> [[(Int, MusicXML.Music_Data_)]] struct = fmap (fmap snd) . groupBy ((==) `on` fst) . sortBy (compare `on` fst) . uncurry zip . split (flip runOffSet 0) (zip [1..]) \end{nocode} \begin{code}
-- * Architecture of MusicXML
-- | get offset from music_data elements
getOffSet :: MusicXML.Music_Data_ -> IntegerNumber
getOffSet (MusicXML.Music_Data_1 (_,(x,_,_,_,_,_,_,_,_,_,_,_,_))) = 
    getOffSet_ x where
    getOffSet_ (MusicXML.Note_1 (_,_,_)) = 0
    getOffSet_ (MusicXML.Note_2 (_,(a,_),y)) =
        if isJust a then 0 else maybe 0 id (read_IntegerNumber y)
    getOffSet_ (MusicXML.Note_3 ((a,_),y,_)) = 
        if isJust a then 0 else maybe 0 id (read_IntegerNumber y)
getOffSet (MusicXML.Music_Data_2 (x,_)) = maybe 0 negate (read_IntegerNumber x)
getOffSet (MusicXML.Music_Data_3 (x,_,_)) = maybe 0 id (read_IntegerNumber x)
getOffSet _ = 0
-- | generic sort of Music_Data
arrangeBy :: (Ord b, Num b) => (a -> b) -> [a] -> [[((b,Integer), a)]]
arrangeBy f = fmap (fmap assocl) .
    groupBy ((==) `on` p1) . sortBy (compare `on` p1) . 
    uncurry zip . 
    split (flip (foldr (\h t -> \n -> (n + f h) : t (n + f h)) 
                (const [])) 0) 
          (zip [1..])
-- | sort of Music_Data
arrange :: MusicXML.Music_Data -> 
    [[((IntegerNumber, Integer), MusicXML.Music_Data_)]]
arrange = arrangeBy getOffSet
\end{code} \begin{nocode} filepath :: FilePath --filepath = "E:/estudos/mi-1/dissertacao/svn/work/MusicXML/examples/Recordare/partwise/elite.xml" --filepath = "E:/estudos/mi-1/dissertacao/svn/work/MusicXML/examples/Recordare/partwise/ActorPreludeSample.xml" filepath = "E:/estudos/mi-1/dissertacao/svn/work/MusicXML/examples/Recordare/partwise/Binchois.xml" --filepath = "E:/estudos/mi-1/dissertacao/svn/work/MusicXML/examples/Recordare/partwise/Chant.xml" ex1, ex2 :: IO () ex1 = do x <- MusicXML.read_FILE MusicXML.read_MusicXML_Partwise filepath case MusicXML.isOK x of False -> putStrLn ("parsing error at " ++ show filepath) True -> print ((fmap (fmap (flip runOffSet 0 .snd)) . fmap snd . snd . snd . MusicXML.fromOK) x) -- True -> print ((fmap (fmap ((\y -> y == sort y) . flip runOffSet 0 .snd)) . fmap snd . snd . snd . MusicXML.fromOK) x) ex2 = do x <- MusicXML.read_FILE MusicXML.read_MusicXML_Partwise filepath case MusicXML.isOK x of False -> putStrLn ("parsing error at " ++ show filepath) True -> do let a = ((fmap (fmap (flip runOffSet 0 .snd)) . fmap snd . snd . snd . MusicXML.fromOK) x) let b = ((fmap (fmap (runOffSet' . snd)) . fmap snd . snd . snd . MusicXML.fromOK) x) print (a == b) \end{nocode}