\begin{code}
-- |  
-- Maintainer : silva.samuel@alumni.uminho.pt
-- Stability  : experimental
-- Portability: HaXML
-- 
module Text.XML.MusicXML.Direction where
import Text.XML.MusicXML.Common 
import Text.XML.MusicXML.Layout hiding (Tenths, read_Tenths, show_Tenths)
import Text.XML.HaXml.Types (Content)
import Control.Monad (MonadPlus(..))
import Prelude (Maybe(..), Show,Eq, Monad(..), (++), (.))
import qualified Data.Char (String)
\end{code} \begin{musicxml} This direction DTD module contains the direction element and its children. Directions are not note-specific, but instead are associated with a part or the overall score. Harmony indications and general print and sound suggestions are likewise not necessarily attached to particular note elements, and are included here as well. A direction is a musical indication that is not attached to a specific note. Two or more may be combined to indicate starts and stops of wedges, dashes, etc. By default, a series of direction-type elements and a series of child elements of a direction-type within a single direction element follow one another in sequence visually. For a series of direction-type children, non- positional formatting attributes are carried over from the previous element by default. \end{musicxml} \begin{code}
-- * Direction
-- |
type Direction = ((Placement, Directive), 
    ([Direction_Type], Maybe Offset, Editorial_Voice, 
    Maybe Staff, Maybe Sound))
-- |
read_Direction :: Eq i => StateT Result [Content i] Direction
read_Direction = do
    y <- read_ELEMENT "direction"
    y1 <- read_2 read_Placement read_Directive (attributes y)
    y2 <- read_5 (read_LIST1 read_Direction_Type) (read_MAYBE read_Offset)
                 (read_Editorial_Voice) (read_MAYBE read_Staff)
                 (read_MAYBE read_Sound) (childs y)
    return (y1,y2)
-- |
show_Direction :: Direction -> [Content ()]
show_Direction ((a,b),(c,d,e,f,g)) = 
    show_ELEMENT "direction" (show_Placement a ++ show_Directive b)
                             (show_LIST show_Direction_Type c ++ 
                             show_MAYBE show_Offset d ++
                             show_Editorial_Voice e ++ 
                             show_MAYBE show_Staff f ++ 
                             show_MAYBE show_Sound g)
\end{code} \begin{musicxml} Textual direction types may have more than 1 component due to multiple fonts. The dynamics element may also be used in the notations element, and is defined in the common.mod file. \end{musicxml} \begin{code}
-- ** Direction_Type
-- |
type Direction_Type = Direction_Type_
-- |
read_Direction_Type :: Eq i => StateT Result [Content i] Direction_Type
read_Direction_Type = do
    y <- read_ELEMENT "direction-type"
    read_1 read_Direction_Type_ (childs y)
-- |
show_Direction_Type :: Direction_Type -> [Content ()]
show_Direction_Type a = 
    show_ELEMENT "direction-type" [] (show_Direction_Type_ a)
-- |
data Direction_Type_ = Direction_Type_1 [Rehearsal]
                     | Direction_Type_2 [Segno]
                     | Direction_Type_3 [Words]
                     | Direction_Type_4 [Coda]
                     | Direction_Type_5 Wedge
                     | Direction_Type_6 [Dynamics]
                     | Direction_Type_7 Dashes
                     | Direction_Type_8 Bracket
                     | Direction_Type_9 Pedal
                     | Direction_Type_10 Metronome
                     | Direction_Type_11 Octave_Shift
                     | Direction_Type_12 Harp_Pedals
                     | Direction_Type_13 Damp
                     | Direction_Type_14 Damp_All
                     | Direction_Type_15 Eyeglasses
                     | Direction_Type_16 Scordatura
                     | Direction_Type_17 Image
                     | Direction_Type_18 Accordion_Registration
                     | Direction_Type_19 Other_Direction
                       deriving (Eq, Show)
-- |
read_Direction_Type_ :: Eq i => StateT Result [Content i] Direction_Type_
read_Direction_Type_ = 
    (read_LIST1 read_Rehearsal >>= return . Direction_Type_1) `mplus`
    (read_LIST1 read_Segno >>= return . Direction_Type_2) `mplus`
    (read_LIST1 read_Words >>= return . Direction_Type_3) `mplus`
    (read_LIST1 read_Coda >>= return . Direction_Type_4) `mplus`
    (read_Wedge >>= return . Direction_Type_5) `mplus`
    (read_LIST1 read_Dynamics >>= return . Direction_Type_6) `mplus`
    (read_Dashes >>= return . Direction_Type_7) `mplus`
    (read_Bracket >>= return . Direction_Type_8) `mplus`
    (read_Pedal >>= return . Direction_Type_9) `mplus`
    (read_Metronome >>= return . Direction_Type_10) `mplus`
    (read_Octave_Shift >>= return . Direction_Type_11) `mplus`
    (read_Harp_Pedals >>= return . Direction_Type_12) `mplus`
    (read_Damp >>= return . Direction_Type_13) `mplus`
    (read_Damp_All >>= return . Direction_Type_14) `mplus`
    (read_Eyeglasses >>= return . Direction_Type_15) `mplus`
    (read_Scordatura >>= return . Direction_Type_16) `mplus`
    (read_Image >>= return . Direction_Type_17) `mplus`
    (read_Accordion_Registration >>= return . Direction_Type_18) `mplus`
    (read_Other_Direction >>= return . Direction_Type_19) 
-- |
show_Direction_Type_ :: Direction_Type_ -> [Content ()]
show_Direction_Type_ (Direction_Type_1 a) = show_LIST1 show_Rehearsal a
show_Direction_Type_ (Direction_Type_2 a) = show_LIST1 show_Segno a
show_Direction_Type_ (Direction_Type_3 a) = show_LIST1 show_Words a
show_Direction_Type_ (Direction_Type_4 a) = show_LIST1 show_Coda a
show_Direction_Type_ (Direction_Type_5 a) = show_Wedge a
show_Direction_Type_ (Direction_Type_6 a) = show_LIST1 show_Dynamics a
show_Direction_Type_ (Direction_Type_7 a) = show_Dashes a
show_Direction_Type_ (Direction_Type_8 a) = show_Bracket a
show_Direction_Type_ (Direction_Type_9 a) = show_Pedal a
show_Direction_Type_ (Direction_Type_10 a) = show_Metronome a
show_Direction_Type_ (Direction_Type_11 a) = show_Octave_Shift a
show_Direction_Type_ (Direction_Type_12 a) = show_Harp_Pedals a
show_Direction_Type_ (Direction_Type_13 a) = show_Damp a
show_Direction_Type_ (Direction_Type_14 a) = show_Damp_All a
show_Direction_Type_ (Direction_Type_15 a) = show_Eyeglasses a
show_Direction_Type_ (Direction_Type_16 a) = show_Scordatura a
show_Direction_Type_ (Direction_Type_17 a) = show_Image a
show_Direction_Type_ (Direction_Type_18 a) = show_Accordion_Registration a
show_Direction_Type_ (Direction_Type_19 a) = show_Other_Direction a
\end{code} \begin{musicxml} Entities related to print suggestions apply to the individual direction-type, not to the overall direction. Language is Italian ("it") by default. Enclosure is square by default. \end{musicxml} \begin{code}
-- |
type Rehearsal = ((Print_Style, Text_Decoration,
        Maybe CDATA, Text_Direction, Text_Rotation,
        Maybe Rehearsal_), PCDATA)
-- |
read_Rehearsal :: StateT Result [Content i] Rehearsal
read_Rehearsal = do
    y <- read_ELEMENT "rehearsal" 
    y1 <- read_6 read_Print_Style read_Text_Decoration
                 (read_IMPLIED "xml:lang" read_CDATA)
                 read_Text_Direction read_Text_Rotation
                 (read_IMPLIED "enclosure" read_Rehearsal_)
                 (attributes y)
    y2 <- read_1 read_PCDATA (childs y)
    return (y1,y2)
-- |
show_Rehearsal :: Rehearsal -> [Content ()]
show_Rehearsal ((a,b,c,d,e,f),g) = 
    show_ELEMENT "rehearsal" (show_Print_Style a ++ show_Text_Decoration b ++
                              show_IMPLIED "xml:lang" show_CDATA c ++
                              show_Text_Direction d ++ show_Text_Rotation e ++
                              show_IMPLIED "enclosure" show_Rehearsal_ f)
                             (show_PCDATA g)
-- |
data Rehearsal_ = Rehearsal_1 | Rehearsal_2 | Rehearsal_3
                  deriving (Eq, Show)
-- |
read_Rehearsal_ :: Data.Char.String -> Result Rehearsal_
read_Rehearsal_ "square" = return Rehearsal_1
read_Rehearsal_ "circle" = return Rehearsal_2
read_Rehearsal_ "none"   = return Rehearsal_3
read_Rehearsal_ x = fail x
-- |
show_Rehearsal_ :: Rehearsal_ -> Data.Char.String
show_Rehearsal_ Rehearsal_1 = "square"
show_Rehearsal_ Rehearsal_2 = "circle"
show_Rehearsal_ Rehearsal_3 = "none"
\end{code} \begin{musicxml} Left justification is assumed if not specified. Language is Italian ("it") by default. Enclosure is none by default. \end{musicxml} \begin{code}
-- |
type Words = (Text_Formatting, PCDATA)
-- |
read_Words :: StateT Result [Content i] Words
read_Words = do
    y <- read_ELEMENT "words"
    y1 <- read_1 read_Text_Formatting (attributes y)
    y2 <- read_1 read_PCDATA (childs y)
    return (y1,y2)
-- |
show_Words :: Words -> [Content ()]
show_Words (a,b) = 
    show_ELEMENT "words" (show_Text_Formatting a) (show_PCDATA b)
\end{code} \begin{musicxml} Wedge spread is measured in tenths of staff line space. The type is crescendo for the start of a wedge that is closed at the left side, and diminuendo for the start of a wedge that is closed on the right side. Spread values at the start of a crescendo wedge or end of a diminuendo wedge are ignored. \end{musicxml} \begin{code}
type Wedge = ((Wedge_, Maybe Number_Level, Maybe CDATA,
        Position, Color), ())
-- |
read_Wedge :: StateT Result [Content i] Wedge
read_Wedge = do
    y <- read_ELEMENT "wedge"
    y1 <- read_5 (read_REQUIRED "type" read_Wedge_)
                 (read_IMPLIED  "number" read_Number_Level)
                 (read_IMPLIED "spread" read_CDATA)
                 read_Position read_Color (attributes y)
    return (y1,())
-- |
show_Wedge :: Wedge -> [Content ()]
show_Wedge ((a,b,c,d,e),_) = 
    show_ELEMENT "wedge" (show_REQUIRED "type" show_Wedge_ a ++
                          show_IMPLIED "number" show_Number_Level b ++
                          show_IMPLIED "spread" show_CDATA c ++
                          show_Position d ++ show_Color e) []
-- |
data Wedge_ = Wedge_1 | Wedge_2 | Wedge_3
              deriving (Eq, Show)
-- |
read_Wedge_ :: Data.Char.String -> Result Wedge_
read_Wedge_ "crescendo" = return Wedge_1
read_Wedge_ "diminuendo" = return Wedge_2
read_Wedge_ "stop" = return Wedge_3
read_Wedge_ x = fail x
-- |
show_Wedge_ :: Wedge_ -> Data.Char.String
show_Wedge_ Wedge_1 = "crescendo"
show_Wedge_ Wedge_2 = "diminuendo"
show_Wedge_ Wedge_3 = "stop"
\end{code} \begin{musicxml} Dashes, used for instance with cresc. and dim. marks. \end{musicxml} \begin{code}
-- |
type Dashes = ((Start_Stop, Maybe Number_Level, 
        Position, Color), ())
-- |
read_Dashes :: StateT Result [Content i] Dashes
read_Dashes = do
    y <- read_ELEMENT "dashes"
    y1 <- read_4 (read_REQUIRED "type" read_Start_Stop)
                 (read_IMPLIED "number" read_Number_Level)
                 read_Position read_Color (attributes y)
    return (y1,())
-- |
show_Dashes :: Dashes -> [Content ()]
show_Dashes ((a,b,c,d),_) = 
    show_ELEMENT "dashes" (show_REQUIRED "type" show_Start_Stop a ++ 
                           show_IMPLIED "number" show_Number_Level b ++
                           show_Position c ++ show_Color d) []
\end{code} \begin{musicxml} Brackets are combined with words in a variety of modern directions. The line-end attribute specifies if there is a jog up or down (or both), an arrow, or nothing at the start or end of the bracket. If the line-end is up or down, the length of the jog can be specified using the end-length attribute. The line-type is solid by default. \end{musicxml} \begin{code}
-- |
type Bracket = ((Start_Stop, Maybe Number_Level, 
        Bracket_, Maybe Tenths, Line_Type, Position, Color), ())
-- |
read_Bracket :: StateT Result [Content i] Bracket
read_Bracket = do
    y <- read_ELEMENT "bracket"
    y1 <- read_7 (read_REQUIRED "type" read_Start_Stop)
                 (read_IMPLIED "number" read_Number_Level)
                 (read_REQUIRED "line-end" read_Bracket_)
                 (read_IMPLIED "end-length" read_Tenths)
                 read_Line_Type read_Position read_Color 
                 (attributes y)
    return (y1,())
-- |
show_Bracket :: Bracket -> [Content ()]
show_Bracket ((a,b,c,d,e,f,g),_) = 
    show_ELEMENT "bracket" (show_REQUIRED "type" show_Start_Stop a ++ 
                            show_IMPLIED "number" show_Number_Level b ++
                            show_REQUIRED "line-end" show_Bracket_ c ++
                            show_IMPLIED "end-length" show_Tenths d ++
                            show_Line_Type e ++ show_Position f ++ 
                            show_Color g) []
-- |
data Bracket_ = Bracket_1 | Bracket_2 | Bracket_3 | Bracket_4 | Bracket_5
                deriving (Eq, Show)
-- |
read_Bracket_ :: Data.Char.String -> Result Bracket_
read_Bracket_ "up" = return Bracket_1
read_Bracket_ "down" = return Bracket_2
read_Bracket_ "both" = return Bracket_3
read_Bracket_ "arrow" = return Bracket_4
read_Bracket_ "none" = return Bracket_5
read_Bracket_ x = fail x
-- |
show_Bracket_ :: Bracket_ -> Data.Char.String
show_Bracket_ Bracket_1 = "up"
show_Bracket_ Bracket_2 = "down"
show_Bracket_ Bracket_3 = "both"
show_Bracket_ Bracket_4 = "arrow"
show_Bracket_ Bracket_5 = "none"
\end{code} \begin{musicxml} Piano pedal marks. The line attribute is yes if pedal lines are used, no if Ped and * signs are used. The change type is used with line set to yes. \end{musicxml} \begin{code}
-- |
type Pedal = ((Pedal_, Maybe Yes_No, Print_Style), ())
-- |
read_Pedal :: StateT Result [Content i] Pedal
read_Pedal = do
    y <- read_ELEMENT "pedal"
    y1 <- read_3 (read_REQUIRED "type" read_Pedal_)
                 (read_IMPLIED "line" read_Yes_No)
                 read_Print_Style (attributes y)
    return (y1,())
-- |
show_Pedal :: Pedal -> [Content ()]
show_Pedal ((a,b,c),_) = 
    show_ELEMENT "pedal" (show_REQUIRED "type" show_Pedal_ a ++
                          show_IMPLIED "line" show_Yes_No b ++
                          show_Print_Style c) []
-- |
data Pedal_ = Pedal_1 | Pedal_2 | Pedal_3
              deriving (Eq, Show)
read_Pedal_ :: Data.Char.String -> Result Pedal_
read_Pedal_ "start" = return Pedal_1
read_Pedal_ "stop" = return Pedal_2
read_Pedal_ "change" = return Pedal_3
read_Pedal_ x = fail x
-- |
show_Pedal_ :: Pedal_ -> Data.Char.String
show_Pedal_ Pedal_1 = "start"
show_Pedal_ Pedal_2 = "stop"
show_Pedal_ Pedal_3 = "change"
-- |
\end{code} \begin{musicxml} Metronome marks and other metric relationships. The beat-unit values are the same as for a type element, and the beat-unit-dot works like the dot element. The per-minute element can be a number, or a text description including numbers. The parentheses attribute indicates whether or not to put the metronome mark in parentheses; its value is no if not specified. If a font is specified for the per-minute element, it overrides the font specified for the overall metronome element. This allows separate specification of a music font for beat-unit and a text font for the numeric value in cases where a single metronome font is not used. The metronome-note and metronome-relation elements allow for the specification of more complicated metric relationships, such as swing tempo marks where two eighths are equated to a quarter note / eighth note triplet. The metronome-type, metronome-beam, and metronome-dot elements work like the type, beam, and dot elements. The metronome-tuplet element uses the same element structure as the time-modification element along with some attributes from the tuplet element. The metronome-relation element describes the relationship symbol that goes between the two sets of metronome-note elements. The currently allowed value is equals, but this may expand in future versions. If the element is empty, the equals value is used. The metronome-relation and the following set of metronome-note elements are optional to allow display of an isolated Grundschlagnote. \end{musicxml} \begin{code}
-- |
type Metronome = ((Print_Style, Maybe Yes_No), Metronome_A)
-- |
read_Metronome :: Eq i => StateT Result [Content i] Metronome
read_Metronome = do
    y <- read_ELEMENT "metronome"
    y1 <- read_2 read_Print_Style (read_IMPLIED "parentheses" read_Yes_No)
                 (attributes y)
    y2 <- read_1 read_Metronome_A (childs y )
    return (y1,y2)
-- |
show_Metronome :: Metronome -> [Content ()]
show_Metronome ((a,b),c) = 
    show_ELEMENT "metronome" (show_Print_Style a ++ 
                              show_IMPLIED "parentheses" show_Yes_No b)
                             (show_Metronome_A c)
-- |
data Metronome_A = Metronome_1 (Beat_Unit, [Beat_Unit_Dot], Metronome_B)
                 | Metronome_2 ([Metronome_Note], 
                                Maybe (Metronome_Relation, [Metronome_Note]))
                 deriving (Eq, Show)
-- |
read_Metronome_A :: Eq i => StateT Result [Content i] Metronome_A
read_Metronome_A = 
    (read_Metronome_A_aux1 >>= return . Metronome_1) `mplus`
    (read_Metronome_A_aux2 >>= return . Metronome_2) 
-- |
show_Metronome_A :: Metronome_A -> [Content ()]
show_Metronome_A (Metronome_1 (a,b,c)) = show_Beat_Unit a ++ 
                                         show_LIST show_Beat_Unit_Dot b ++
                                         show_Metronome_B c
show_Metronome_A (Metronome_2 (a,b)) = show_LIST show_Metronome_Note a ++
                                       show_MAYBE show_Metronome_A_aux1 b
-- |
read_Metronome_A_aux1 :: Eq i => 
    StateT Result [Content i] (Beat_Unit, [Beat_Unit_Dot], Metronome_B)
read_Metronome_A_aux1 = do
    y1 <- read_Beat_Unit
    y2 <- read_LIST read_Beat_Unit_Dot
    y3 <- read_Metronome_B
    return (y1,y2,y3)
-- |
read_Metronome_A_aux2 :: Eq i => StateT Result [Content i] 
    ([Metronome_Note], Maybe (Metronome_Relation, [Metronome_Note]))
read_Metronome_A_aux2 = do
    y1 <- read_LIST1 read_Metronome_Note
    y2 <- read_MAYBE read_Metronome_A_aux3 
    return (y1,y2)
-- |
read_Metronome_A_aux3 :: Eq i => 
    StateT Result [Content i] (Metronome_Relation, [Metronome_Note])
read_Metronome_A_aux3 = do
    y1 <- read_Metronome_Relation
    y2 <- read_LIST1 read_Metronome_Note
    return (y1,y2)
-- |
show_Metronome_A_aux1 :: (Metronome_Relation, [Metronome_Note]) -> [Content ()]
show_Metronome_A_aux1 (a,b) = show_Metronome_Relation a ++ 
                              show_LIST show_Metronome_Note b
-- |
data Metronome_B = Metronome_3 Per_Minute
                 | Metronome_4 (Beat_Unit, [Beat_Unit_Dot])
                 deriving (Eq, Show)
-- |
read_Metronome_B :: Eq i => StateT Result [Content i] Metronome_B
read_Metronome_B = 
    (read_Per_Minute >>= return . Metronome_3) `mplus`
    (read_Metronome_B_aux1 >>= return . Metronome_4)     
-- |
show_Metronome_B :: Metronome_B -> [Content ()]
show_Metronome_B (Metronome_3 a) = show_Per_Minute a
show_Metronome_B (Metronome_4 (a,b)) = show_Beat_Unit a ++ 
                                       show_LIST show_Beat_Unit_Dot b
-- |
read_Metronome_B_aux1 :: Eq i => 
    StateT Result [Content i] (Beat_Unit, [Beat_Unit_Dot])
read_Metronome_B_aux1 = do
    y1 <- read_Beat_Unit
    y2 <- read_LIST read_Beat_Unit_Dot
    return (y1,y2)
-- |
type Beat_Unit = PCDATA
-- |
read_Beat_Unit :: StateT Result [Content i] Beat_Unit
read_Beat_Unit = do
    y <- read_ELEMENT "beat-unit" 
    read_1 read_PCDATA (childs y)
-- |
show_Beat_Unit :: Beat_Unit -> [Content ()]
show_Beat_Unit a = show_ELEMENT "beat-unit" [] (show_PCDATA a)
-- |
type Beat_Unit_Dot = ()
-- |
read_Beat_Unit_Dot :: StateT Result [Content i] Beat_Unit_Dot
read_Beat_Unit_Dot = read_ELEMENT "beat-unit-dot" >> return ()
-- |
show_Beat_Unit_Dot :: Beat_Unit_Dot -> [Content ()]
show_Beat_Unit_Dot _ = show_ELEMENT "beat-unit-dot" [] []
-- |
type Per_Minute = (Font, PCDATA)
-- |
read_Per_Minute :: StateT Result [Content i] Per_Minute
read_Per_Minute = do
    y <- read_ELEMENT "per-minute"
    y1 <- read_1 read_Font (attributes y)
    y2 <- read_1 read_PCDATA (childs y)
    return (y1,y2)
-- |
show_Per_Minute :: Per_Minute -> [Content ()]
show_Per_Minute (a,b) = 
    show_ELEMENT "per-minute" (show_Font a) (show_PCDATA b)
-- |
type Metronome_Note = (Metronome_Type, [Metronome_Dot], 
    [Metronome_Beam], Maybe Metronome_Tuplet)
-- |
read_Metronome_Note :: Eq i => StateT Result [Content i] Metronome_Note
read_Metronome_Note = do
    y <- read_ELEMENT "metronome-note"
    read_4 read_Metronome_Type (read_LIST read_Metronome_Dot)
           (read_LIST read_Metronome_Beam) 
           (read_MAYBE read_Metronome_Tuplet) (childs y)
-- |
show_Metronome_Note :: Metronome_Note -> [Content ()]
show_Metronome_Note (a,b,c,d) = 
    show_ELEMENT "metronome-note" [] 
        (show_Metronome_Type a ++ show_LIST show_Metronome_Dot b ++
         show_LIST show_Metronome_Beam c ++ show_MAYBE show_Metronome_Tuplet d)
-- |
type Metronome_Relation = PCDATA
-- |
read_Metronome_Relation :: StateT Result [Content i] Metronome_Relation
read_Metronome_Relation = do
    y <- read_ELEMENT "metronome-relation" 
    read_1 read_PCDATA (childs y)
-- |
show_Metronome_Relation :: Metronome_Relation -> [Content ()]
show_Metronome_Relation a = 
    show_ELEMENT "metronome-relation" [] (show_PCDATA a)
-- |
type Metronome_Type = PCDATA
-- |
read_Metronome_Type :: StateT Result [Content i] Metronome_Type
read_Metronome_Type = do
    y <- read_ELEMENT "metronome-type" 
    read_1 read_PCDATA (childs y)
-- |
show_Metronome_Type :: Metronome_Type -> [Content ()]
show_Metronome_Type a = 
    show_ELEMENT "metronome-type" [] (show_PCDATA a)
-- |
type Metronome_Dot = ()
-- |
read_Metronome_Dot :: StateT Result [Content i] Metronome_Dot
read_Metronome_Dot = read_ELEMENT "metronome-dot" >> return ()
-- |
show_Metronome_Dot :: Metronome_Dot -> [Content ()]
show_Metronome_Dot _ = 
    show_ELEMENT "metronome-dot" [] []
-- |
type Metronome_Beam = (Beam_Level, PCDATA)
-- |
read_Metronome_Beam :: StateT Result [Content i] Metronome_Beam
read_Metronome_Beam = do
    y <- read_ELEMENT "metronome-beam"
    y1 <- read_1 (read_DEFAULT "number" read_Beam_Level Beam_Level_1) 
                 (attributes y)
    y2 <- read_1 read_PCDATA (childs y)
    return (y1,y2)
-- |
show_Metronome_Beam :: Metronome_Beam -> [Content ()]
show_Metronome_Beam (a,b) = 
    show_ELEMENT "metronome-beam" (show_DEFAULT "number" show_Beam_Level a) 
                                  (show_PCDATA b)
-- |
type Metronome_Tuplet = ((Start_Stop, Maybe Yes_No, Maybe Metronome_Tuplet_), 
    (Actual_Notes, Normal_Notes, Maybe (Normal_Type, [Normal_Dot])))
-- |
read_Metronome_Tuplet :: Eq i => StateT Result [Content i] Metronome_Tuplet
read_Metronome_Tuplet = do
    y <- read_ELEMENT "metronome-tuplet"
    y1 <- read_3 (read_REQUIRED "type" read_Start_Stop)
                 (read_IMPLIED "bracket" read_Yes_No)
                 (read_IMPLIED "show-number" read_Metronome_Tuplet_)
                 (attributes y)
    y2 <- read_3 read_Actual_Notes read_Normal_Notes 
                 (read_MAYBE read_Metronome_Tuplet_aux1) (childs y)
    return (y1,y2)
-- |
show_Metronome_Tuplet :: Metronome_Tuplet -> [Content ()]
show_Metronome_Tuplet ((a,b,c),(d,e,f)) = 
    show_ELEMENT "metronome-tuplet" 
        (show_REQUIRED "type" show_Start_Stop a ++
         show_IMPLIED "bracket" show_Yes_No b ++
         show_IMPLIED "show-number" show_Metronome_Tuplet_ c) 
        (show_Actual_Notes d ++ show_Normal_Notes e ++
         show_MAYBE show_Metronome_Tuplet_aux1 f)
-- |
read_Metronome_Tuplet_aux1 :: Eq i => 
    StateT Result [Content i] (Normal_Type, [Normal_Dot])
read_Metronome_Tuplet_aux1 = do
    y1 <- read_Normal_Type
    y2 <- read_LIST read_Normal_Dot
    return (y1,y2)
-- |
show_Metronome_Tuplet_aux1 :: (Normal_Type, [Normal_Dot]) -> [Content ()]
show_Metronome_Tuplet_aux1 (a,b) = 
    show_ELEMENT "metronome-tuplet" [] 
        (show_Normal_Type a ++ show_LIST show_Normal_Dot b)
-- |
data Metronome_Tuplet_ = Metronome_Tuplet_1 
                       | Metronome_Tuplet_2 
                       | Metronome_Tuplet_3
                         deriving (Eq, Show)
-- | 
read_Metronome_Tuplet_ :: Data.Char.String -> Result Metronome_Tuplet_
read_Metronome_Tuplet_ "actual" = return Metronome_Tuplet_1
read_Metronome_Tuplet_ "both" = return Metronome_Tuplet_2
read_Metronome_Tuplet_ "none" = return Metronome_Tuplet_3
read_Metronome_Tuplet_ x = fail x
-- |
show_Metronome_Tuplet_ :: Metronome_Tuplet_ -> Data.Char.String
show_Metronome_Tuplet_ Metronome_Tuplet_1 = "actual"
show_Metronome_Tuplet_ Metronome_Tuplet_2 = "both"
show_Metronome_Tuplet_ Metronome_Tuplet_3 = "none"
\end{code} \begin{musicxml} Octave shifts indicate where notes are shifted up or down from their true pitched values because of printing difficulty. Thus a treble clef line noted with 8va will be indicated with an octave-shift down from the pitch data indicated in the notes. A size of 8 indicates one octave; a size of 15 indicates two octaves. \end{musicxml} \begin{code}
-- |
type Octave_Shift = ((Octave_Shift_, Maybe Number_Level, 
    CDATA, Print_Style), ())
-- |
read_Octave_Shift :: StateT Result [Content i] Octave_Shift
read_Octave_Shift = do
    y <- read_ELEMENT "octave-shift"
    y1 <- read_4 (read_REQUIRED "type" read_Octave_Shift_)
                 (read_IMPLIED "number" read_Number_Level)
                 (read_DEFAULT "size" read_CDATA "8")
                 read_Print_Style (attributes y)
    return (y1,())
-- |
show_Octave_Shift :: Octave_Shift -> [Content ()]
show_Octave_Shift ((a,b,c,d),_) = 
    show_ELEMENT "octave-shift" 
        (show_REQUIRED "type" show_Octave_Shift_ a ++
         show_IMPLIED "number" show_Number_Level b ++
         show_DEFAULT "size" show_CDATA c ++ show_Print_Style d) []
-- |
data Octave_Shift_ = Octave_Shift_1 | Octave_Shift_2 | Octave_Shift_3
                     deriving (Eq, Show)
-- |
read_Octave_Shift_ :: Data.Char.String -> Result Octave_Shift_
read_Octave_Shift_ "up" = return Octave_Shift_1
read_Octave_Shift_ "down" = return Octave_Shift_2
read_Octave_Shift_ "stop" = return Octave_Shift_3
read_Octave_Shift_ x = fail x
-- |
show_Octave_Shift_ :: Octave_Shift_ -> Data.Char.String 
show_Octave_Shift_ Octave_Shift_1 = "up"
show_Octave_Shift_ Octave_Shift_2 = "down"
show_Octave_Shift_ Octave_Shift_3 = "stop"
\end{code} \begin{musicxml} The harp-pedals element is used to create harp pedal diagrams. The pedal-step and pedal-alter elements use the same values as the step and alter elements. For easiest reading, the pedal-tuning elements should follow standard harp pedal order, with pedal-step values of D, C, B, E, F, G, and A. \end{musicxml} \begin{code}
-- |
type Harp_Pedals = (Print_Style, [Pedal_Tuning])
-- |
read_Harp_Pedals :: Eq i => StateT Result [Content i] Harp_Pedals
read_Harp_Pedals = do
    y <- read_ELEMENT "harp-pedals"
    y1 <- read_1 read_Print_Style (attributes y)
    y2 <- read_1 (read_LIST1 read_Pedal_Tuning) (childs y)
    return (y1,y2)
-- |
show_Harp_Pedals :: Harp_Pedals -> [Content ()]
show_Harp_Pedals (a,b) = 
    show_ELEMENT "harp-pedals" (show_Print_Style a) 
                               (show_LIST show_Pedal_Tuning b)
-- |
type Pedal_Tuning = (Pedal_Step, Pedal_Alter)
-- |
read_Pedal_Tuning :: StateT Result [Content i] Pedal_Tuning
read_Pedal_Tuning = do
    y <- read_ELEMENT "pedal-tuning"
    read_2 read_Pedal_Step read_Pedal_Alter (childs y)
-- |
show_Pedal_Tuning :: Pedal_Tuning -> [Content ()]
show_Pedal_Tuning (a,b) = 
    show_ELEMENT "pedal-tuning" [] 
        (show_Pedal_Step a ++ show_Pedal_Alter b)
-- |
type Pedal_Step = PCDATA
-- |
read_Pedal_Step :: StateT Result [Content i] Pedal_Step
read_Pedal_Step = do
    y <- read_ELEMENT "pedal-step"
    read_1 read_PCDATA (childs y)
-- |
show_Pedal_Step :: Pedal_Step -> [Content ()]
show_Pedal_Step a = show_ELEMENT "pedal-step" [] (show_Pedal_Step a)
-- |
type Pedal_Alter = PCDATA
-- |
read_Pedal_Alter :: StateT Result [Content i] Pedal_Alter
read_Pedal_Alter = do
    y <- read_ELEMENT "pedal-alter"
    read_1 read_PCDATA (childs y)
-- |
show_Pedal_Alter :: Pedal_Alter -> [Content ()]
show_Pedal_Alter a = show_ELEMENT "pedal-alter" [] (show_Pedal_Alter a)
-- |
type Damp = (Print_Style, ())
-- |
read_Damp :: StateT Result [Content i] Damp
read_Damp = do
    y <- read_ELEMENT "damp"
    y1 <- read_1 read_Print_Style (attributes y)
    return (y1,())
-- |
show_Damp :: Damp -> [Content ()]
show_Damp (a,_) = show_ELEMENT "damp" (show_Print_Style a) []
-- |
type Damp_All = (Print_Style, ())
-- |
read_Damp_All :: StateT Result [Content i] Damp_All
read_Damp_All = do
    y <- read_ELEMENT "damp-all"
    y1 <- read_1 read_Print_Style (attributes y)
    return (y1,())
-- |
show_Damp_All :: Damp_All -> [Content ()]
show_Damp_All (a,_) = show_ELEMENT "damp-all" (show_Print_Style a) []
-- |
type Eyeglasses = (Print_Style, ())
-- |
read_Eyeglasses :: StateT Result [Content i] Eyeglasses
read_Eyeglasses = do
    y <- read_ELEMENT "eyeglasses"
    y1 <- read_1 read_Print_Style (attributes y)
    return (y1,())
-- |
show_Eyeglasses :: Eyeglasses -> [Content ()]
show_Eyeglasses (a,_) = show_ELEMENT "eyeglasses" (show_Print_Style a) []
\end{code} \begin{musicxml} Scordatura string tunings are represented by a series of accord elements. The tuning-step, tuning-alter, and tuning-octave elements are also used with the staff-tuning element, and are defined in the common.mod file. Strings are numbered from high to low. \end{musicxml} \begin{code}
-- |
type Scordatura = [Accord]
-- |
read_Scordatura :: Eq i => StateT Result [Content i] Scordatura
read_Scordatura = do
    y <- read_ELEMENT "scordatura"
    read_1 (read_LIST read_Accord) (childs y)
-- |
show_Scordatura :: Scordatura -> [Content ()]
show_Scordatura a = 
    show_ELEMENT "scordatura" [] (show_LIST show_Accord a)
-- |
type Accord = (CDATA, (Tuning_Step, Maybe Tuning_Alter, Tuning_Octave))
-- |
read_Accord :: StateT Result [Content i] Accord
read_Accord = do
    y <- read_ELEMENT "accord"
    y1 <- read_1 (read_REQUIRED "string" read_CDATA) (attributes y)
    y2 <- read_3 read_Tuning_Step (read_MAYBE read_Tuning_Alter)
                 read_Tuning_Octave (childs y)
    return (y1,y2)
-- |
show_Accord :: Accord -> [Content ()]
show_Accord (a,(b,c,d)) = 
    show_ELEMENT "accord" 
        (show_REQUIRED "string" show_CDATA a) 
        (show_Tuning_Step b ++ show_MAYBE show_Tuning_Alter c ++
         show_Tuning_Octave d)
\end{code} \begin{musicxml} The image element is used to include graphical images in a score. The required source attribute is the URL for the image file. The required type attribute is the MIME type for the image file format. Typical choices include application/postscript, image/gif, image/jpeg, image/png, and image/tiff. \end{musicxml} \begin{code}
-- |
type Image = ((CDATA, CDATA, Position, Halign, Valign_Image), ())
-- |
read_Image :: StateT Result [Content i] Image
read_Image = do
    y <- read_ELEMENT "image"
    y1 <- read_5 (read_REQUIRED "source" read_CDATA)
                 (read_REQUIRED "type" read_CDATA) read_Position
                 read_Halign read_Valign_Image (attributes y)
    return (y1,())
-- |
show_Image :: Image -> [Content ()]
show_Image ((a,b,c,d,e),_) = 
    show_ELEMENT "image" 
        (show_REQUIRED "source" show_CDATA a ++ 
         show_REQUIRED "type" show_CDATA b ++ 
         show_Position c ++ show_Halign d ++ show_Valign_Image e) []
\end{code} \begin{musicxml} The accordion-registration element is use for accordion registration symbols. These are circular symbols divided horizontally into high, middle, and low sections that correspond to 4', 8', and 16' pipes. Each accordion-high, accordion-middle, and accordion-low element represents the presence of one or more dots in the registration diagram. The accordion-middle element may have text values of 1, 2, or 3, corresponding to have 1 to 3 dots in the middle section. An accordion-registration element needs to have at least one of the child elements present. \end{musicxml} \begin{code}
-- |
type Accordion_Registration = (Print_Style,
    (Maybe Accordion_High, Maybe Accordion_Middle, Maybe Accordion_Low))
-- |
read_Accordion_Registration :: StateT Result [Content i] Accordion_Registration 
read_Accordion_Registration = do
    y <- read_ELEMENT "accordion-registration"
    y1 <- read_1 read_Print_Style (attributes y)
    y2 <- read_3 (read_MAYBE read_Accordion_High) 
                 (read_MAYBE read_Accordion_Middle)
                 (read_MAYBE read_Accordion_Low) (childs y)
    return (y1,y2)
-- |
show_Accordion_Registration :: Accordion_Registration -> [Content ()]
show_Accordion_Registration (a,(b,c,d)) = 
    show_ELEMENT "accordion-registration" 
        (show_Print_Style a)
        (show_MAYBE show_Accordion_High b ++
         show_MAYBE show_Accordion_Middle c ++
         show_MAYBE show_Accordion_Low d)
-- |
type Accordion_High = ()
-- |
read_Accordion_High :: StateT Result [Content i] Accordion_High
read_Accordion_High = read_ELEMENT "accordion-high" >> return ()
-- |
show_Accordion_High :: Accordion_High -> [Content ()]
show_Accordion_High _ = show_ELEMENT "accordion-high" [] []
-- |
type Accordion_Middle = PCDATA
-- |
read_Accordion_Middle :: StateT Result [Content i] Accordion_Middle
read_Accordion_Middle = do 
    y <- read_ELEMENT "accordion-middle"
    read_1 read_PCDATA (childs y)
-- |
show_Accordion_Middle :: Accordion_Middle -> [Content ()]
show_Accordion_Middle a = show_ELEMENT "accordion-middle" [] (show_PCDATA a)
-- |
type Accordion_Low = ()
-- |
read_Accordion_Low :: StateT Result [Content i] Accordion_Low
read_Accordion_Low = read_ELEMENT "accordion-low" >> return ()
-- |
show_Accordion_Low :: Accordion_Low -> [Content ()]
show_Accordion_Low _ = show_ELEMENT "accordion-low" [] []
\end{code} \begin{musicxml} The other-direction element is used to define any direction symbols not yet in the current version of the MusicXML format. This allows extended representation, though without application interoperability. \end{musicxml} \begin{code}
-- |
type Other_Direction = ((Print_Object, Print_Style), PCDATA)
-- |
read_Other_Direction :: StateT Result [Content i] Other_Direction
read_Other_Direction = do 
    y <- read_ELEMENT "other-direction"
    y1 <- read_2 read_Print_Object read_Print_Style (attributes y)
    y2 <- read_1 read_PCDATA (childs y)
    return (y1,y2)
-- |
show_Other_Direction :: Other_Direction -> [Content ()]
show_Other_Direction ((a,b),c) = 
    show_ELEMENT "other-direction" 
        (show_Print_Object a ++ show_Print_Style b)
        (show_PCDATA c)
\end{code} \begin{musicxml} An offset is represented in terms of divisions, and indicates where the direction will appear relative to the current musical location. This affects the visual appearance of the direction. If the sound attribute is "yes", then the offset affects playback too. If the sound attribute is "no", then any sound associated with the direction takes effect at the current location. The sound attribute is "no" by default for compatibility with earlier versions of the MusicXML format. If an element within a direction includes a default-x attribute, the offset value will be ignored when determining the appearance of that element. \end{musicxml} \begin{code}
-- |
type Offset = (Maybe Yes_No, PCDATA)
-- |
read_Offset :: StateT Result [Content i] Offset
read_Offset = do
    y <- read_ELEMENT "offset"
    y1 <- read_1 (read_IMPLIED "sound" read_Yes_No) (attributes y)
    y2 <- read_1 read_PCDATA (childs y)
    return (y1,y2)
-- |
show_Offset :: Offset -> [Content ()]
show_Offset (a,b) = 
    show_ELEMENT "offset" (show_IMPLIED "sound" show_Yes_No a)
                          (show_PCDATA b)
\end{code} \begin{musicxml} The harmony elements are based on Humdrum's **harm encoding, extended to support chord symbols in popular music as well as functional harmony analysis in classical music. If there are alternate harmonies possible, this can be specified using multiple harmony elements differentiated by type. Explicit harmonies have all note present in the music; implied have some notes missing but implied; alternate represents alternate analyses. The harmony object may be used for analysis or for chord symbols. The print-object attribute controls whether or not anything is printed due to the harmony element. The print-frame attribute controls printing of a frame or fretboard diagram. The print-style entity sets the default for the harmony, but individual elements can override this with their own print-style values. A harmony element can contain many stacked chords (e.g. V of II). A sequence of harmony-chord entities is used for this type of secondary function, where V of II would be represented by a harmony-chord with a V function followed by a harmony-chord with a II function. \end{musicxml} \begin{code}
-- |
type Harmony_Chord = (Harmony_Chord_, Kind, Maybe Inversion, 
                      Maybe Bass, [Degree])
-- |
read_Harmony_Chord :: Eq i => StateT Result [Content i] Harmony_Chord
read_Harmony_Chord = do
    y1 <- read_Harmony_Chord_ 
    y2 <- read_Kind 
    y3 <- read_MAYBE read_Inversion
    y4 <- read_MAYBE read_Bass
    y5 <- read_LIST read_Degree
    return (y1,y2,y3,y4,y5)
-- |
show_Harmony_Chord :: Harmony_Chord -> [Content ()]
show_Harmony_Chord (a,b,c,d,e) = 
    (show_Harmony_Chord_ a ++ show_Kind b ++ 
     show_MAYBE show_Inversion c ++ show_MAYBE show_Bass d ++
     show_LIST show_Degree e)
-- |
data Harmony_Chord_ = Harmony_Chord_1 Root
                    | Harmony_Chord_2 Function
                      deriving (Eq, Show)
-- |
read_Harmony_Chord_ :: StateT Result [Content i] Harmony_Chord_
read_Harmony_Chord_ = 
    (read_Root >>= return . Harmony_Chord_1) `mplus`
    (read_Function >>= return . Harmony_Chord_2) 
-- |
show_Harmony_Chord_ :: Harmony_Chord_ -> [Content ()]
show_Harmony_Chord_ (Harmony_Chord_1 a) = show_Root a
show_Harmony_Chord_ (Harmony_Chord_2 a) = show_Function a
-- |
type Harmony = ((Maybe Harmony_, Print_Object, Maybe Yes_No, 
        Print_Style, Placement),
    ([Harmony_Chord], Maybe Frame, 
    Maybe Offset, Editorial, Maybe Staff))
-- |
read_Harmony :: Eq i => StateT Result [Content i] Harmony
read_Harmony = do
    y <- read_ELEMENT "harmony"
    y1 <- read_5 (read_IMPLIED "type" read_Harmony_) read_Print_Object
                 (read_IMPLIED "print-frame" read_Yes_No) 
                 read_Print_Style read_Placement (attributes y)
    y2 <- read_5 (read_LIST read_Harmony_Chord) (read_MAYBE read_Frame)
                 (read_MAYBE read_Offset) read_Editorial 
                 (read_MAYBE read_Staff) (childs y)
    return (y1,y2)
--    fail "harmony"
show_Harmony :: Harmony -> [Content ()]
show_Harmony ((a,b,c,d,e),(f,g,h,i,j)) = 
    show_ELEMENT "harmony" 
        (show_IMPLIED "type" show_Harmony_ a ++ show_Print_Object b ++
         show_IMPLIED "print-frame" show_Yes_No c ++ show_Print_Style d ++
         show_Placement e)
        (show_LIST show_Harmony_Chord f ++ show_MAYBE show_Frame g ++
         show_MAYBE show_Offset h ++ show_Editorial i ++ 
         show_MAYBE show_Staff j)
-- |
data Harmony_ = Harmony_1 | Harmony_2 | Harmony_3
                deriving (Eq, Show)
-- |
read_Harmony_ :: Data.Char.String -> Result Harmony_
read_Harmony_ "explicit"  = return Harmony_1
read_Harmony_ "implied"   = return Harmony_2
read_Harmony_ "alternate" = return Harmony_3
read_Harmony_ x           = fail x
-- |
show_Harmony_ :: Harmony_ -> Data.Char.String
show_Harmony_ Harmony_1 = "explicit"
show_Harmony_ Harmony_2 = "implied"
show_Harmony_ Harmony_3 = "alternate"
\end{code} \begin{musicxml} A root is a pitch name like C, D, E, where a function is an indication like I, II, III. Root is generally used with pop chord symbols, function with classical functional harmony. It is an either/or choice to avoid data inconsistency. Function requires that the key be specified in the encoding. The root element has a root-step and optional root-alter similar to the step and alter elements in a pitch, but renamed to distinguish the different musical meanings. The root-step text element indicates how the root should appear on the page if not using the element contents. In some chord styles, this will include the root-alter information as well. In that case, the print-object attribute of the root-alter element can be set to no. The root-alter location attribute indicates whether the alteration should appear to the left or the right of the root-step; it is right by default. \end{musicxml} \begin{code}
-- |
type Root = (Root_Step, Maybe Root_Alter)
-- |
read_Root :: StateT Result [Content i] Root
read_Root = do 
    y <- read_ELEMENT "root"
    read_2 read_Root_Step (read_MAYBE read_Root_Alter) (childs y)
-- |
show_Root :: Root -> [Content ()]
show_Root (a,b) = 
    show_ELEMENT "root" [] 
        (show_Root_Step a ++ show_MAYBE show_Root_Alter b)
-- |
type Root_Step = ((Maybe CDATA, Print_Style), PCDATA)
-- |
read_Root_Step :: StateT Result [Content i] Root_Step
read_Root_Step = do
    y <- read_ELEMENT "root-step"
    y1 <- read_2 (read_IMPLIED "text" read_CDATA) 
                 read_Print_Style (attributes y)
    y2 <- read_1 read_PCDATA (childs y)
    return (y1,y2)
-- |
show_Root_Step :: Root_Step -> [Content ()]
show_Root_Step ((a,b),c) = 
    show_ELEMENT "root-step" 
        (show_IMPLIED "text" show_CDATA a ++ show_Print_Style b) 
        (show_PCDATA c)
-- |
type Root_Alter = ((Print_Object, Print_Style, Maybe Left_Right), PCDATA)
-- |
read_Root_Alter :: StateT Result [Content i] Root_Alter
read_Root_Alter = do
    y <- read_ELEMENT "root-alter"
    y1 <- read_3 read_Print_Object read_Print_Style 
                 (read_IMPLIED "location" read_Left_Right) 
                 (attributes y)
    y2 <- read_1 read_PCDATA (childs y)
    return (y1,y2)
-- |
show_Root_Alter :: Root_Alter -> [Content ()]
show_Root_Alter ((a,b,c),d) = 
    show_ELEMENT "root-alter" 
        (show_Print_Object a ++ show_Print_Style b ++
         show_IMPLIED "location" show_Left_Right c) 
        (show_PCDATA d)
-- |
type Function = (Print_Style, PCDATA)
-- |
read_Function :: StateT Result [Content i] Function
read_Function = do
    y <- read_ELEMENT "function"
    y1 <- read_1 read_Print_Style (attributes y)
    y2 <- read_1 read_PCDATA (childs y)
    return (y1,y2)
-- |
show_Function :: Function -> [Content ()]
show_Function (a,b) = 
    show_ELEMENT "function" (show_Print_Style a) (show_PCDATA b)
\end{code} \begin{musicxml} Kind indicates the type of chord. Degree elements can then add, subtract, or alter from these starting points. Values include: \begin{itemize} \item Triads: major (major third, perfect fifth) minor (minor third, perfect fifth) augmented (major third, augmented fifth) diminished (minor third, diminished fifth) \item Sevenths: dominant (major triad, minor seventh) major-seventh (major triad, major seventh) minor-seventh (minor triad, minor seventh) diminished-seventh (diminished triad, diminished seventh) augmented-seventh (augmented triad, minor seventh) half-diminished (diminished triad, minor seventh) major-minor (minor triad, major seventh) \item Sixths: major-sixth (major triad, added sixth) minor-sixth (minor triad, added sixth) \item Ninths: dominant-ninth (dominant-seventh, major ninth) major-ninth (major-seventh, major ninth) minor-ninth (minor-seventh, major ninth) \item 11ths (usually as the basis for alteration): dominant-11th (dominant-ninth, perfect 11th) major-11th (major-ninth, perfect 11th) minor-11th (minor-ninth, perfect 11th) \item 13ths (usually as the basis for alteration): dominant-13th (dominant-11th, major 13th) major-13th (major-11th, major 13th) minor-13th (minor-11th, major 13th) \item Suspended: suspended-second (major second, perfect fifth) suspended-fourth (perfect fourth, perfect fifth) \item Functional sixths: Neapolitan Italian French German \item Other: pedal (pedal-point bass) power (perfect fifth) Tristan \end{itemize} The \ "other" \ kind is used when the harmony is entirely composed of add elements. The "none" kind is used to explicitly encode absence of chords or functional harmony. The attributes are used to indicate the formatting of the symbol. Since the kind element is the constant in all the harmony-chord entities that can make up a polychord, many formatting attributes are here. The use-symbols attribute is yes if the kind should be represented when possible with harmony symbols rather than letters and numbers. These symbols include: major: a triangle, like Unicode 25B3 minor: -, like Unicode 002D augmented: +, like Unicode 002B diminished: °, like Unicode 00B0 half-diminished: ø, like Unicode 00F8 The text attribute describes how the kind should be spelled if not using symbols; it is ignored if use-symbols is yes. The stack-degrees attribute is yes if the degree elements should be stacked above each other. The parentheses-degrees attribute is yes if all the degrees should be in parentheses. The bracket-degrees attribute is yes if all the degrees should be in a bracket. If not specified, these values are implementation-specific. The alignment attributes are for the entire harmony-chord entity of which this kind element is a part. \end{musicxml} \begin{code}
type Kind = ((Maybe Yes_No, Maybe CDATA,
        Maybe Yes_No, Maybe Yes_No, Maybe Yes_No,
        Print_Style, Halign, Valign), PCDATA)
-- |
read_Kind :: StateT Result [Content i] Kind
read_Kind = do 
    y <- read_ELEMENT "kind"
    y1 <- read_8 (read_IMPLIED "use-symbols" read_Yes_No) 
                 (read_IMPLIED "text" read_CDATA) 
                 (read_IMPLIED "stack-degrees" read_Yes_No) 
                 (read_IMPLIED "parentheses-degrees" read_Yes_No) 
                 (read_IMPLIED "bracket-degrees" read_Yes_No)
                 read_Print_Style read_Halign read_Valign (attributes y)
    y2 <- read_1 read_PCDATA (childs y)
    return (y1,y2)
-- |
show_Kind :: Kind -> [Content ()]
show_Kind ((a,b,c,d,e,f,g,h),i) = 
    show_ELEMENT "kind" 
        (show_IMPLIED "use-symbols" show_Yes_No a ++
         show_IMPLIED "text" show_CDATA b ++ 
         show_IMPLIED "stack-degrees" show_Yes_No c ++
         show_IMPLIED "parentheses-degrees" show_Yes_No d ++
         show_IMPLIED "bracket-degrees" show_Yes_No e ++
         show_Print_Style f ++ show_Halign g ++ show_Valign h) (show_PCDATA i)
\end{code} \begin{musicxml} Inversion is a number indicating which inversion is used: 0 for root position, 1 for first inversion, etc. \end{musicxml} \begin{code}
type Inversion = (Print_Style, PCDATA)
-- |
read_Inversion :: StateT Result [Content i] Inversion
read_Inversion = do 
    y <- read_ELEMENT "inversion"
    y1 <- read_1 read_Print_Style (attributes y)
    y2 <- read_1 read_PCDATA (childs y)
    return (y1,y2)
-- |
show_Inversion :: Inversion -> [Content ()]
show_Inversion (a,b) = 
    show_ELEMENT "inversion" (show_Print_Style a) (show_PCDATA b)
\end{code} \begin{musicxml} Bass is used to indicate a bass note in popular music chord symbols, e.g. G/C. It is generally not used in functional harmony, as inversion is generally not used in pop chord symbols. As with root, it is divided into step and alter elements, similar to pitches. The attributes for bass-step and bass-alter work the same way as the corresponding root-step and root-alter attributes. \end{musicxml} \begin{code}
-- |
type Bass = (Bass_Step, Maybe Bass_Alter)
-- |
read_Bass :: StateT Result [Content i] Bass
read_Bass = do
    y <- read_ELEMENT "bass"
    read_2 read_Bass_Step (read_MAYBE read_Bass_Alter) (childs y)
-- |
show_Bass :: Bass -> [Content ()]
show_Bass (a,b) = 
    show_ELEMENT "bass" [] 
        (show_Bass_Step a ++ show_MAYBE show_Bass_Alter b)
-- |
type Bass_Step = ((Maybe CDATA, Print_Style), PCDATA)
-- |
read_Bass_Step :: StateT Result [Content i] Bass_Step
read_Bass_Step = do
    y <- read_ELEMENT "bass-step"
    y1 <- read_2 (read_IMPLIED "text" read_CDATA) 
                 read_Print_Style (attributes y)
    y2 <- read_1 read_PCDATA (childs y)
    return (y1,y2)
-- |
show_Bass_Step :: Bass_Step -> [Content ()]
show_Bass_Step ((a,b),c) = 
    show_ELEMENT "bass-step" 
        (show_IMPLIED "text" show_CDATA a ++ show_Print_Style b) 
        (show_PCDATA c)
-- |
type Bass_Alter = ((Print_Object, Print_Style, Maybe Bass_Alter_), PCDATA)
-- |
read_Bass_Alter :: StateT Result [Content i] Bass_Alter
read_Bass_Alter = do
    y <- read_ELEMENT "bass-alter"
    y1 <- read_3 read_Print_Object read_Print_Style 
                 (read_IMPLIED "location" read_Bass_Alter_) (attributes y)
    y2 <- read_1 read_PCDATA (childs y)
    return (y1,y2)
-- |
show_Bass_Alter :: Bass_Alter -> [Content ()]
show_Bass_Alter ((a,b,c),d) = 
    show_ELEMENT "bass-alter" 
        (show_Print_Object a ++ show_Print_Style b ++ 
         show_IMPLIED "location" show_Bass_Alter_ c) 
        (show_PCDATA d)
-- | This is equivalent to left-right entity
data Bass_Alter_ = Bass_Alter_1 | Bass_Alter_2 
        deriving (Eq, Show)
-- |
read_Bass_Alter_ :: Data.Char.String -> Result Bass_Alter_
read_Bass_Alter_ "left"  = return Bass_Alter_1
read_Bass_Alter_ "right" = return Bass_Alter_2
read_Bass_Alter_ x       = fail x
-- |
show_Bass_Alter_ :: Bass_Alter_ -> Data.Char.String
show_Bass_Alter_ Bass_Alter_1 = "left"
show_Bass_Alter_ Bass_Alter_2 = "right"
\end{code} \begin{musicxml} The degree element is used to add, alter, or subtract individual notes in the chord. The degree-value element is a number indicating the degree of the chord (1 for the root, 3 for third, etc). The degree-alter element is like the alter element in notes: 1 for sharp, -1 for flat, etc. The degree-type element can be add, alter, or subtract. If the degree-type is alter or subtract, the degree-alter is relative to the degree already in the chord based on its kind element. If the degree-type is add, the degree-alter is relative to a dominant chord (major and perfect intervals except for a minor seventh). The print-object attribute can be used to keep the degree from printing separately when it has already taken into account in the text attribute of the kind element. The plus-minus attribute is used to indicate if plus and minus symbols should be used instead of sharp and flat symbols to display the degree alteration; it is no by default. The degree-value and degree-type text attributes specify how the value and type of the degree should be displayed. A harmony of kind "other" can be spelled explicitly by using a series of degree elements together with a root. \end{musicxml} \begin{code}
-- |
type Degree = (Print_Object, (Degree_Value, Degree_Alter, Degree_Type))
-- |
read_Degree :: StateT Result [Content i] Degree
read_Degree = do
    y <- read_ELEMENT "degree"
    y1 <- read_1 read_Print_Object (attributes y)
    y2 <- read_3 read_Degree_Value read_Degree_Alter 
                 read_Degree_Type (childs y)
    return (y1,y2)
-- |
show_Degree :: Degree -> [Content ()]
show_Degree (a,(b,c,d)) = 
    show_ELEMENT "degree" 
        (show_Print_Object a) 
        (show_Degree_Value b ++ show_Degree_Alter c ++ 
         show_Degree_Type d)
-- |
type Degree_Value = ((Maybe CDATA, Print_Style), PCDATA)
-- |
read_Degree_Value :: StateT Result [Content i] Degree_Value
read_Degree_Value = do
    y <- read_ELEMENT "degree-value"
    y1 <- read_2 (read_IMPLIED "text" read_CDATA) 
                 read_Print_Style (attributes y)
    y2 <- read_1 read_PCDATA (childs y)
    return (y1,y2)
-- |
show_Degree_Value :: Degree_Value -> [Content ()]
show_Degree_Value ((a,b),c) = 
    show_ELEMENT "degree-value" 
        (show_IMPLIED "type" show_CDATA a ++ show_Print_Style b) 
        (show_PCDATA c)
-- |
type Degree_Alter = ((Print_Style, Maybe Yes_No), PCDATA)
-- |
read_Degree_Alter :: StateT Result [Content i] Degree_Alter
read_Degree_Alter = do
    y <- read_ELEMENT "degree-alter"
    y1 <- read_2 read_Print_Style 
                 (read_IMPLIED "plus-minus" read_Yes_No) (attributes y)
    y2 <- read_1 read_PCDATA (childs y)
    return (y1,y2)
-- |
show_Degree_Alter :: Degree_Alter -> [Content ()]
show_Degree_Alter ((a,b),c) = 
    show_ELEMENT "degree-alter" 
        (show_Print_Style a ++ show_IMPLIED "plus-minus" show_Yes_No b) 
        (show_PCDATA c)
-- |
type Degree_Type = ((Maybe CDATA, Print_Style), PCDATA)
-- |
read_Degree_Type :: StateT Result [Content i] Degree_Type
read_Degree_Type = do
    y <- read_ELEMENT "degree-type"
    y1 <- read_2 (read_IMPLIED "text" read_CDATA) 
                 read_Print_Style (attributes y)
    y2 <- read_1 read_PCDATA (childs y)
    return (y1,y2)
-- |
show_Degree_Type :: Degree_Type -> [Content ()]
show_Degree_Type ((a,b),c) = 
    show_ELEMENT "degree-type" 
        (show_IMPLIED "type" show_CDATA a ++ show_Print_Style b) 
        (show_PCDATA c)
\end{code} \begin{musicxml} The frame element represents a frame or fretboard diagram used together with a chord symbol. The representation is based on the NIFF guitar grid with additional information. The frame-strings and frame-frets elements give the overall size of the frame in vertical lines (strings) and horizontal spaces (frets). The first-fret indicates which fret is shown in the top space of the frame; it is fret 1 if the element is not present. The optional text attribute indicates how this is represented in the fret diagram, while the location attribute indicates whether the text appears to the left or right of the frame. The frame-note element represents each note included in the frame. The definitions for string, fret, and fingering are found in the common.mod file. An open string will have a fret value of 0, while a muted string will not be associated with a frame-note element. \end{musicxml} \begin{code}
-- |
type Frame = 
    ((Position, Color, Halign, Valign, Maybe Tenths, Maybe Tenths), 
    (Frame_Strings, Frame_Frets, Maybe First_Fret, [Frame_Note]))
-- |
read_Frame :: Eq i => StateT Result [Content i] Frame
read_Frame = do
    y <- read_ELEMENT "frame"
    y1 <- read_6 read_Position read_Color read_Halign read_Valign 
                 (read_IMPLIED "height" read_Tenths) 
                 (read_IMPLIED "width" read_Tenths) (attributes y)
    y2 <- read_4 read_Frame_Strings read_Frame_Frets 
                 (read_MAYBE read_First_Fret) 
                 (read_LIST read_Frame_Note) (childs y)
    return (y1,y2)
-- |
show_Frame :: Frame -> [Content ()]
show_Frame ((a,b,c,d,e,f),(g,h,i,j)) = 
    show_ELEMENT "frame" 
        (show_Position a ++ show_Color b ++ show_Halign c ++ 
         show_Valign d ++ show_IMPLIED "height" show_Tenths e ++ 
         show_IMPLIED "width" show_Tenths f) 
        (show_Frame_Strings g ++ show_Frame_Frets h ++ 
         show_MAYBE show_First_Fret i ++ show_LIST show_Frame_Note j)
-- |
type Frame_Strings = PCDATA
-- |
read_Frame_Strings :: StateT Result [Content i] Frame_Strings
read_Frame_Strings = do
    y <- read_ELEMENT "frame-strings"
    read_1 read_PCDATA (childs y)
-- |
show_Frame_Strings :: Frame_Strings -> [Content ()]
show_Frame_Strings a = show_ELEMENT "frame-strings" [] (show_PCDATA a)
-- |
type Frame_Frets = PCDATA
-- |
read_Frame_Frets :: StateT Result [Content i] Frame_Frets
read_Frame_Frets = do
    y <- read_ELEMENT "frame-frets"
    read_1 read_PCDATA (childs y)
-- |
show_Frame_Frets :: Frame_Frets -> [Content ()]
show_Frame_Frets a = show_ELEMENT "frame-frets" [] (show_PCDATA a)
-- |
type First_Fret = ((Maybe CDATA, Maybe Left_Right), PCDATA)
-- |
read_First_Fret :: StateT Result [Content i] First_Fret
read_First_Fret = do
    y <- read_ELEMENT "first-fret"
    y1 <- read_2 (read_IMPLIED "text" read_CDATA) 
                 (read_IMPLIED "location" read_Left_Right) (attributes y)
    y2 <- read_1 read_PCDATA (childs y)
    return (y1,y2)
-- |
show_First_Fret :: First_Fret -> [Content ()]
show_First_Fret ((a,b),c) = 
    show_ELEMENT "first-fret" 
        (show_IMPLIED "text" show_CDATA a ++ 
         show_IMPLIED "location" show_Left_Right b) 
        (show_PCDATA c)
-- |
type Frame_Note = (String, Fret, Maybe Fingering, Maybe Barre)
-- |
read_Frame_Note :: StateT Result [Content i] Frame_Note
read_Frame_Note = do
    y <- read_ELEMENT "frame-note"
    read_4 read_String read_Fret (read_MAYBE read_Fingering) 
           (read_MAYBE read_Barre) (childs y)
-- |
show_Frame_Note :: Frame_Note -> [Content ()]
show_Frame_Note (a,b,c,d) = 
    show_ELEMENT "frame-note" [] 
        (show_String a ++ show_Fret b ++ 
         show_MAYBE show_Fingering c ++ show_MAYBE show_Barre d)
\end{code} \begin{musicxml} The barre element indicates placing a finger over multiple strings on a single fret. The type is "start" for the lowest pitched string (e.g., the string with the highest MusicXML number) and is "stop" for the highest pitched string. \end{musicxml} \begin{code}
-- |
type Barre = ((Start_Stop, Color), ())
-- |
read_Barre :: StateT Result [Content i] Barre
read_Barre = do
    y <- read_ELEMENT "barre"
    y1 <- read_2 (read_REQUIRED "type" read_Start_Stop) 
                 read_Color (attributes y)
    return (y1,())
-- |
show_Barre :: Barre -> [Content ()]
show_Barre ((a,b),_) = 
    show_ELEMENT "barre" 
        (show_REQUIRED "type" show_Start_Stop a ++ show_Color b) []
\end{code} \begin{musicxml} The grouping element is used for musical analysis. When the element type is "start" or "single", it usually contains one or more feature elements. The number attribute is used for distinguishing between overlapping and hierarchical groupings. The member-of attribute allows for easy distinguishing of what grouping elements are in what hierarchy. Feature elements contained within a "stop" type of grouping may be ignored. This element is flexible to allow for non-standard analyses. Future versions of the MusicXML format may add elements that can represent more standardized categories of analysis data, allowing for easier data sharing. \end{musicxml} \begin{code}
-- |
type Grouping = ((Start_Stop_Single, CDATA, Maybe CDATA), [Feature])
-- |
read_Grouping :: Eq i => StateT Result [Content i] Grouping
read_Grouping = do
    y <- read_ELEMENT "grouping"
    y1 <- read_3 (read_REQUIRED "type" read_Start_Stop_Single)
                 (read_DEFAULT "number" read_CDATA "1")
                 (read_IMPLIED "member-of" read_CDATA)
                 (attributes y)
    y2 <- read_1 (read_LIST read_Feature) (childs y)
    return (y1,y2)
-- |
show_Grouping :: Grouping -> [Content ()]
show_Grouping ((a,b,c),d) = 
    show_ELEMENT "grouping" (show_REQUIRED "type" show_Start_Stop_Single a ++
                             show_DEFAULT "number" show_CDATA b ++
                             show_IMPLIED "member-of" show_CDATA c) 
                            (show_LIST show_Feature d)
-- |
type Feature = (Maybe CDATA, PCDATA)
-- |
read_Feature :: StateT Result [Content i] Feature
read_Feature = do
    y <- read_ELEMENT "feature"
    y1 <- read_1 (read_IMPLIED "type" read_CDATA) (attributes y)
    y2 <- read_1 read_PCDATA (childs y)
    return (y1,y2)
-- |
show_Feature :: Feature -> [Content ()]
show_Feature (a,b) = 
    show_ELEMENT "feature" (show_IMPLIED "type" show_CDATA a)
                           (show_PCDATA b)
\end{code} \begin{musicxml} The print element contains general printing parameters, including the layout elements defined in the layout.mod file. The part-name-display and part-abbreviation-display elements used in the score.mod file may also be used here to change how a part name or abbreviation is displayed over the course of a piece. They take effect when the current measure or a succeeding measure starts a new system. The new-system and new-page attributes indicate whether to force a system or page break, or to force the current music onto the same system or page as the preceding music. Normally this is the first music data within a measure. If used in multi-part music, they should be placed in the same positions within each part, or the results are undefined. The page-number attribute sets the number of a new page; it is ignored if new-page is not "yes". Version 2.0 adds a blank-page attribute. This is a positive integer value that specifies the number of blank pages to insert before the current measure. It is ignored if new-page is not "yes". These blank pages have no music, but may have text or images specified by the credit element. This is used to allow a combination of pages that are all text, or all text and images, together with pages of music. Staff spacing between multiple staves is measured in tenths of staff lines (e.g. 100 = 10 staff lines). This is deprecated as of Version 1.1; the staff-layout element should be used instead. If both are present, the staff-layout values take priority. Layout elements in a print statement only apply to the current page, system, staff, or measure. Music that follows continues to take the default values from the layout included in the defaults element. \end{musicxml} \begin{code}
-- |
type Print = ((Maybe Tenths, Maybe Yes_No, Maybe Yes_No, 
        Maybe CDATA, Maybe CDATA), 
    (Maybe Page_Layout, Maybe System_Layout, [Staff_Layout],
    Maybe Measure_Layout, Maybe Measure_Numbering, Maybe Part_Name_Display,
    Maybe Part_Abbreviation_Display))
-- |
read_Print :: Eq i => StateT Result [Content i] Print
read_Print = do
    y <- read_ELEMENT "print"
    y1 <- read_5 (read_IMPLIED "staff-spacing" read_Tenths)
                 (read_IMPLIED "new-system" read_Yes_No)
                 (read_IMPLIED "new-page" read_Yes_No)
                 (read_IMPLIED "blank-page" read_CDATA)
                 (read_IMPLIED "page-number" read_CDATA) (attributes y)
    y2 <- read_7 (read_MAYBE read_Page_Layout) (read_MAYBE read_System_Layout)
                 (read_LIST read_Staff_Layout) (read_MAYBE read_Measure_Layout)
                 (read_MAYBE read_Measure_Numbering)
                 (read_MAYBE read_Part_Name_Display) 
                 (read_MAYBE read_Part_Abbreviation_Display) (childs y)
    return (y1,y2)
-- |
show_Print :: Print -> [Content ()]
show_Print ((a,b,c,d,e),(f,g,h,i,j,k,l)) = 
    show_ELEMENT "print" 
        (show_IMPLIED "staff-spacing" show_Tenths a ++
         show_IMPLIED "new-system" show_Yes_No b ++
         show_IMPLIED "new-page" show_Yes_No c ++
         show_IMPLIED "blank-page" show_CDATA d ++
         show_IMPLIED "page-number" show_CDATA e)
        (show_MAYBE show_Page_Layout f ++ show_MAYBE show_System_Layout g ++
         show_LIST show_Staff_Layout h ++ show_MAYBE show_Measure_Layout i ++
         show_MAYBE show_Measure_Numbering j ++ 
         show_MAYBE show_Part_Name_Display k ++
         show_MAYBE show_Part_Abbreviation_Display l)
\end{code} \begin{musicxml} The measure-numbering element describes how measure numbers are displayed on this part. Values may be none, measure, or system. The number attribute from the measure element is used for printing. Measures with an implicit attribute set to "yes" never display a measure number, regardless of the measure-numbering setting. \end{musicxml} \begin{code}
-- |
type Measure_Numbering = (Print_Style, PCDATA)
-- |
read_Measure_Numbering :: Eq i => StateT Result [Content i] Measure_Numbering
read_Measure_Numbering = do
    y <- read_ELEMENT "measure-numbering"
    y1 <- read_1 read_Print_Style (attributes y)
    y2 <- read_1 read_PCDATA (childs y)
    return (y1,y2)
-- |
show_Measure_Numbering :: Measure_Numbering -> [Content ()]
show_Measure_Numbering (a,b) = 
    show_ELEMENT "measure-numbering" 
        (show_Print_Style a) (show_PCDATA b)
\end{code} \begin{musicxml} The sound element contains general playback parameters. They can stand alone within a part/measure, or be a component element within a direction. Tempo is expressed in quarter notes per minute. If 0, the sound-generating program should prompt the user at the time of compiling a sound (MIDI) file. Dynamics (or MIDI velocity) are expressed as a percentage of the default forte value (90 for MIDI 1.0). Dacapo indicates to go back to the beginning of the movement. When used it always has the value "yes". Segno and dalsegno are used for backwards jumps to a segno sign; coda and tocoda are used for forward jumps to a coda sign. If there are multiple jumps, the value of these parameters can be used to name and distinguish them. If segno or coda is used, the divisions attribute can also be used to indicate the number of divisions per quarter note. Otherwise sound and MIDI generating programs may have to recompute this. By default, a dalsegno or dacapo attribute indicates that the jump should occur the first time through, while a tocoda attribute indicates the jump should occur the second time through. The time that jumps occur can be changed by using the time-only attribute. Forward-repeat is used when a forward repeat sign is implied, and usually follows a bar line. When used it always has the value of "yes". The fine attribute follows the final note or rest in a movement with a da capo or dal segno direction. If numeric, the value represents the actual duration of the final note or rest, which can be ambiguous in written notation and different among parts and voices. The value may also be "yes" to indicate no change to the final duration. If the sound element applies only one time through a repeat, the time-only attribute indicates which time to apply the sound element. Pizzicato in a sound element effects all following notes. Yes indicates pizzicato, no indicates arco. The pan and elevation attributes are deprecated in Version 2.0. The pan and elevation elements in the midi-instrument element should be used instead. The meaning of the pan and elevation attributes is the same as for the pan and elevation elements. If both are present, the mid-instrument elements take priority. The damper-pedal, soft-pedal, and sostenuto-pedal attributes effect playback of the three common piano pedals and their MIDI controller equivalents. The yes value indicates the pedal is depressed; no indicates the pedal is released. A numeric value from 0 to 100 may also be used for half pedaling. This value is the percentage that the pedal is depressed. A value of 0 is equivalent to no, and a value of 100 is equivalent to yes. MIDI instruments are changed using the midi-instrument element defined in the common.mod file. The offset element is used to indicate that the sound takes place offset from the current score position. If the sound element is a child of a direction element, the sound offset element overrides the direction offset element if both elements are present. Note that the offset reflects the intended musical position for the change in sound. It should not be used to compensate for latency issues in particular hardware configurations. \end{musicxml} \begin{code}
-- ** Sound
-- |
type Sound = ((Maybe CDATA, Maybe CDATA, Maybe Yes_No,
        Maybe CDATA, Maybe CDATA, Maybe CDATA,
        Maybe CDATA, Maybe CDATA, Maybe Yes_No,
        Maybe CDATA, Maybe CDATA, Maybe Yes_No,
        Maybe CDATA, Maybe CDATA, Maybe Yes_No_Number,
        Maybe Yes_No_Number, Maybe Yes_No_Number), 
    ([Midi_Instrument], Maybe Offset))
-- |
read_Sound :: Eq i => StateT Result [Content i] Sound
read_Sound = do
    y <- read_ELEMENT "sound"
    y1 <- read_17 (read_IMPLIED "tempo" read_CDATA)
                  (read_IMPLIED "dynamics" read_CDATA)
                  (read_IMPLIED "dacapo" read_Yes_No)
                  (read_IMPLIED "segno" read_CDATA)
                  (read_IMPLIED "dalsegno" read_CDATA)
                  (read_IMPLIED "coda" read_CDATA)
                  (read_IMPLIED "tocoda" read_CDATA)
                  (read_IMPLIED "divisions" read_CDATA)
                  (read_IMPLIED "forward-repeat" read_Yes_No)
                  (read_IMPLIED "fine" read_CDATA)
                  (read_IMPLIED "time-only" read_CDATA)
                  (read_IMPLIED "pizzicato" read_Yes_No)
                  (read_IMPLIED "pan" read_CDATA)
                  (read_IMPLIED "elevation" read_CDATA)
                  (read_IMPLIED "damper-pedal" read_Yes_No_Number)
                  (read_IMPLIED "soft-pedal" read_Yes_No_Number)
                  (read_IMPLIED "sostenuto-pedal" read_Yes_No_Number)
                  (attributes y)
    y2 <- read_2 (read_LIST read_Midi_Instrument)
                 (read_MAYBE read_Offset) (childs y)
    return (y1,y2)
-- |
show_Sound :: Sound -> [Content ()]
show_Sound ((a,b,c,d,e,f,g,h,i,j,k,l,m,n,o,p,q),(r,s)) = 
    show_ELEMENT "sound" (show_IMPLIED "tempo" show_CDATA a ++
                          show_IMPLIED "dynamics" show_CDATA b ++
                          show_IMPLIED "dacapo" show_Yes_No c ++
                          show_IMPLIED "segno" show_CDATA d ++ 
                          show_IMPLIED "dalsegno" show_CDATA e ++
                          show_IMPLIED "coda" show_CDATA f ++
                          show_IMPLIED "tocoda" show_CDATA g ++
                          show_IMPLIED "divisions" show_CDATA h ++
                          show_IMPLIED "forward-repeat" show_Yes_No i ++
                          show_IMPLIED "fine" show_CDATA j ++
                          show_IMPLIED "time-only" show_CDATA k ++
                          show_IMPLIED "pizzicato" show_Yes_No l ++
                          show_IMPLIED "pan" show_CDATA m ++
                          show_IMPLIED "elevation" show_CDATA n ++
                          show_IMPLIED "damper-pedal" show_Yes_No_Number o ++
                          show_IMPLIED "soft-pedal" show_Yes_No_Number p ++
                          show_IMPLIED "sostenuto-pedal" show_Yes_No_Number q)
                         (show_LIST show_Midi_Instrument r ++
                          show_MAYBE show_Offset s)
\end{code}