\begin{code}
-- |  
-- Maintainer : silva.samuel@alumni.uminho.pt
-- Stability  : experimental
-- Portability: HaXML
-- 
module Text.XML.MusicXML.Common (
    module Text.XML.MusicXML.Util, 
    module Text.XML.MusicXML.Common) 
    where
import Text.XML.MusicXML.Util 
import Control.Monad (MonadPlus(..))
import Prelude (Maybe(..), Bool(..), Show, Eq,
    Monad(..), Int, (++), (.))
import qualified Data.Char (String)
import Text.XML.HaXml.Types (Attribute, Content(..))
\end{code} \begin{musicxml} This file contains entities and elements that are common across multiple DTD modules. In particular, several elements here are common across both notes and measures. If greater ASCII compatibility is desired, entity references may be used instead of the direct Unicode characters. Currently we include ISO Latin-1 for Western European characters and ISO Latin-2 for Central European characters. These files are local copies of the W3C entities located at: http://www.w3.org/2003/entities/ Data type entities. The ones that resolve to strings show intent for how data is formatted and used. Calendar dates are represented yyyy-mm-dd format, following ISO 8601. \end{musicxml} \begin{code}
-- * Entities
-- |
type YYYY_MM_DD = PCDATA
-- |
read_YYYY_MM_DD :: STM Result [Content i] YYYY_MM_DD
read_YYYY_MM_DD = read_PCDATA
-- |
show_YYYY_MM_DD :: YYYY_MM_DD -> [Content ()]
show_YYYY_MM_DD = show_PCDATA
\end{code} \begin{musicxml} The tenths entity is a number representing tenths of interline space (positive or negative) for use in attributes. The layout-tenths entity is the same for use in elements. Both integer and decimal values are allowed, such as 5 for a half space and 2.5 for a quarter space. Interline space is measured from the middle of a staff line. \end{musicxml} \begin{code}
-- |
type Tenths = CDATA
-- |
read_Tenths :: Data.Char.String -> Result Tenths
read_Tenths = read_CDATA
-- |
show_Tenths :: Tenths -> Data.Char.String
show_Tenths = show_CDATA
-- |
type Layout_Tenths = PCDATA
-- |
read_Layout_Tenths :: STM Result [Content i] Layout_Tenths
read_Layout_Tenths = read_PCDATA
-- |
show_Layout_Tenths :: Layout_Tenths -> [Content ()]
show_Layout_Tenths = show_PCDATA
\end{code} \begin{musicxml} The start-stop and start-stop-continue entities are used for musical elements that can either start or stop, such as slurs, tuplets, and wedges. The start-stop-continue entity is used when there is a need to refer to an intermediate point in the symbol, as for complex slurs. The start-stop-single entity is used when the same element is used for multi-note and single-note notations, as for tremolos. \end{musicxml} \begin{code}
-- |
data Start_Stop = Start_Stop_1 | Start_Stop_2
                  deriving (Eq, Show)
-- |
read_Start_Stop :: Data.Char.String -> Result Start_Stop
read_Start_Stop "start" = return Start_Stop_1
read_Start_Stop "stop"  = return Start_Stop_2
read_Start_Stop _       = 
    fail "wrong value at start-stop entity"
-- |
show_Start_Stop :: Start_Stop -> Data.Char.String
show_Start_Stop Start_Stop_1 = "start"
show_Start_Stop Start_Stop_2 = "stop"
-- |
data Start_Stop_Continue = Start_Stop_Continue_1 
                         | Start_Stop_Continue_2 
                         | Start_Stop_Continue_3
                         deriving (Eq, Show)
-- |
read_Start_Stop_Continue :: Data.Char.String -> Result Start_Stop_Continue
read_Start_Stop_Continue "start"    = return Start_Stop_Continue_1
read_Start_Stop_Continue "stop"     = return Start_Stop_Continue_2
read_Start_Stop_Continue "continue" = return Start_Stop_Continue_3
read_Start_Stop_Continue _          = 
    fail "wrong value at start-stop-continue entity"
-- |
show_Start_Stop_Continue :: Start_Stop_Continue -> Data.Char.String
show_Start_Stop_Continue Start_Stop_Continue_1 = "start"
show_Start_Stop_Continue Start_Stop_Continue_2 = "stop"
show_Start_Stop_Continue Start_Stop_Continue_3 = "continue"
data Start_Stop_Single = Start_Stop_Single_1 
                       | Start_Stop_Single_2
                       | Start_Stop_Single_3
                         deriving (Eq, Show)
-- |
read_Start_Stop_Single :: Data.Char.String -> Result Start_Stop_Single
read_Start_Stop_Single "start"  = return Start_Stop_Single_1
read_Start_Stop_Single "stop"   = return Start_Stop_Single_2
read_Start_Stop_Single "single" = return Start_Stop_Single_3
read_Start_Stop_Single _        = 
    fail "wrong value at start-stop-single entity"
-- |
show_Start_Stop_Single :: Start_Stop_Single -> Data.Char.String
show_Start_Stop_Single Start_Stop_Single_1 = "start"
show_Start_Stop_Single Start_Stop_Single_2 = "stop"
show_Start_Stop_Single Start_Stop_Single_3 = "single"
\end{code} \begin{musicxml} The yes-no entity is used for boolean-like attributes. \end{musicxml} \begin{code}
-- | The yes-no entity is used for boolean-like attributes.
type Yes_No = Bool
-- | 
read_Yes_No :: Data.Char.String -> Result Yes_No
read_Yes_No "yes" = return True
read_Yes_No "no"  = return False
read_Yes_No str   = fail str
-- | 
show_Yes_No :: Yes_No -> Data.Char.String
show_Yes_No True  = "yes"
show_Yes_No False = "no"
\end{code} \begin{musicxml} The yes-no-number entity is used for attributes that can be either boolean or numeric values. Values can be "yes", "no", or numbers. \end{musicxml} \begin{code}
-- | 
type Yes_No_Number = CDATA
-- |
read_Yes_No_Number :: Data.Char.String -> Result Yes_No_Number
read_Yes_No_Number = read_CDATA
-- |
show_Yes_No_Number :: Yes_No_Number -> Data.Char.String 
show_Yes_No_Number = show_CDATA

\end{code} \begin{musicxml} The symbol-size entity is used to indicate full vs. cue-sized vs. oversized symbols. The large value for oversized symbols was added in version 1.1. \end{musicxml} \begin{code}
-- |
data Symbol_Size = Symbol_Size_1 
                 | Symbol_Size_2 
                 | Symbol_Size_3
                   deriving (Eq, Show)
-- |
read_Symbol_Size :: Data.Char.String -> Result Symbol_Size
read_Symbol_Size "full"  = return Symbol_Size_1
read_Symbol_Size "cue"   = return Symbol_Size_2
read_Symbol_Size "large" = return Symbol_Size_3
read_Symbol_Size _       = 
    fail "wrong value at symbol-size entity"
-- |
show_Symbol_Size :: Symbol_Size -> Data.Char.String
show_Symbol_Size Symbol_Size_1 = "full"
show_Symbol_Size Symbol_Size_2 = "cue"
show_Symbol_Size Symbol_Size_3 = "large"
\end{code} \begin{musicxml} The up-down entity is used for arrow direction, indicating which way the tip is pointing. \end{musicxml} \begin{code}
-- |
data Up_Down = Up_Down_1 | Up_Down_2
               deriving (Eq, Show)
-- |
read_Up_Down :: Data.Char.String -> Result Up_Down
read_Up_Down "up"   = return Up_Down_1
read_Up_Down "down" = return Up_Down_2
read_Up_Down _ = 
    fail "wrong value at up-down entity"
-- |
show_Up_Down :: Up_Down -> Data.Char.String
show_Up_Down Up_Down_1 = "up"
show_Up_Down Up_Down_2 = "down"
\end{code} \begin{musicxml} The top-bottom entity is used to indicate the top or bottom part of a vertical shape like non-arpeggiate. \end{musicxml} \begin{code}
-- |
data Top_Bottom = Top_Bottom_1 
                | Top_Bottom_2
                  deriving (Eq, Show)
-- |
read_Top_Bottom :: Data.Char.String -> Result Top_Bottom
read_Top_Bottom "top"    = return Top_Bottom_1
read_Top_Bottom "bottom" = return Top_Bottom_2
read_Top_Bottom _        = 
    fail "wrong value at top-bottom entity"
-- |
show_Top_Bottom :: Top_Bottom -> Data.Char.String
show_Top_Bottom Top_Bottom_1 = "top"
show_Top_Bottom Top_Bottom_2 = "bottom"
\end{code} \begin{musicxml} The left-right entity is used to indicate whether one element appears to the left or the right of another element. \end{musicxml} \begin{code}
-- |
data Left_Right = Left_Right_1 | Left_Right_2
                  deriving (Eq, Show)
-- |
read_Left_Right :: Data.Char.String -> Result Left_Right
read_Left_Right "left"  = return Left_Right_1
read_Left_Right "right" = return Left_Right_2
read_Left_Right _       =
    fail "wrong value at left-right entity"
-- |
show_Left_Right :: Left_Right -> Data.Char.String
show_Left_Right Left_Right_1 = "left"
show_Left_Right Left_Right_2 = "right"
\end{code} \begin{musicxml} The number-of-lines entity is used to specify the number of lines in text decoration attributes. \end{musicxml} \begin{code}
-- |
data Number_Of_Lines = Number_Of_Lines_0
                     | Number_Of_Lines_1
                     | Number_Of_Lines_2
                     | Number_Of_Lines_3
                     deriving (Eq, Show)
-- |
read_Number_Of_Lines :: Data.Char.String -> Result Number_Of_Lines
read_Number_Of_Lines "0" = return Number_Of_Lines_0
read_Number_Of_Lines "1" = return Number_Of_Lines_1
read_Number_Of_Lines "2" = return Number_Of_Lines_2
read_Number_Of_Lines "3" = return Number_Of_Lines_3
read_Number_Of_Lines _   =
    fail "wrong value at number-of-lines entity"
-- |
show_Number_Of_Lines :: Number_Of_Lines -> Data.Char.String
show_Number_Of_Lines Number_Of_Lines_0 = "0"
show_Number_Of_Lines Number_Of_Lines_1 = "1"
show_Number_Of_Lines Number_Of_Lines_2 = "2"
show_Number_Of_Lines Number_Of_Lines_3 = "3"
\end{code} \begin{musicxml} Slurs, tuplets, and many other features can be concurrent and overlapping within a single musical part. The number-level attribute distinguishes up to six concurrent objects of the same type. A reading program should be prepared to handle cases where the number-levels stop in an arbitrary order. Different numbers are needed when the features overlap in MusicXML file order. When a number-level value is implied, the value is 1 by default. \end{musicxml} \begin{code}
-- |
data Number_Level = Number_Level_1 
                  | Number_Level_2
                  | Number_Level_3
                  | Number_Level_4
                  | Number_Level_5
                  | Number_Level_6
                  deriving (Eq, Show)
-- |
read_Number_Level :: Data.Char.String -> Result Number_Level
read_Number_Level "1" = return Number_Level_1
read_Number_Level "2" = return Number_Level_2
read_Number_Level "3" = return Number_Level_3
read_Number_Level "4" = return Number_Level_4
read_Number_Level "5" = return Number_Level_5
read_Number_Level "6" = return Number_Level_6
read_Number_Level _   =
    fail "wrong value at number-level entity"
-- |
show_Number_Level :: Number_Level -> Data.Char.String
show_Number_Level Number_Level_1 = "1"
show_Number_Level Number_Level_2 = "2"
show_Number_Level Number_Level_3 = "3"
show_Number_Level Number_Level_4 = "4"
show_Number_Level Number_Level_5 = "5"
show_Number_Level Number_Level_6 = "6"
\end{code} \begin{musicxml} The MusicXML format supports six levels of beaming, up to 256th notes. Unlike the number-level attribute, the beam-level attribute identifies concurrent beams in a beam group. It does not distinguish overlapping beams such as grace notes within regular notes, or beams used in different voices. \end{musicxml} \begin{code}
-- |
data Beam_Level = Beam_Level_1 
                | Beam_Level_2
                | Beam_Level_3
                | Beam_Level_4
                | Beam_Level_5
                | Beam_Level_6
                deriving (Eq, Show)
-- |
read_Beam_Level :: Data.Char.String -> Result Beam_Level
read_Beam_Level "1" = return Beam_Level_1
read_Beam_Level "2" = return Beam_Level_2
read_Beam_Level "3" = return Beam_Level_3
read_Beam_Level "4" = return Beam_Level_4
read_Beam_Level "5" = return Beam_Level_5
read_Beam_Level "6" = return Beam_Level_6
read_Beam_Level _   =
    fail "wrong value at beam-level entity"
-- |
show_Beam_Level :: Beam_Level -> Data.Char.String
show_Beam_Level Beam_Level_1 = "1"
show_Beam_Level Beam_Level_2 = "2"
show_Beam_Level Beam_Level_3 = "3"
show_Beam_Level Beam_Level_4 = "4"
show_Beam_Level Beam_Level_5 = "5"
show_Beam_Level Beam_Level_6 = "6"
\end{code} \begin{musicxml} Common structures for formatting attribute definitions. The position attributes are based on MuseData print suggestions. For most elements, any program will compute a default x and y position. The position attributes let this be changed two ways. The default-x and default-y attributes change the computation of the default position. For most elements, the origin is changed relative to the left-hand side of the note or the musical position within the bar (x) and the top line of the staff (y). For the following elements, the default-x value changes the origin relative to the start of the current measure: - note - figured-bass - harmony - link - directive - measure-numbering - all descendants of the part-list element - all children of the direction-type element When the part-name and part-abbreviation elements are used in the print element, the default-x value changes the origin relative to the start of the first measure on the system. These values are used when the current measure or a succeeding measure starts a new system. For the note, figured-bass, and harmony elements, the default-x value is considered to have adjusted the musical position within the bar for its descendant elements. Since the credit-words and credit-image elements are not related to a measure, in these cases the default-x and default-y attributes adjust the origin relative to the bottom left-hand corner of the specified page. The relative-x and relative-y attributes change the position relative to the default position, either as computed by the individual program, or as overridden by the default-x and default-y attributes. Positive x is right, negative x is left; positive y is up, negative y is down. All units are in tenths of interline space. For stems, positive relative-y lengthens a stem while negative relative-y shortens it. The default-x and default-y position attributes provide higher-resolution positioning data than related features such as the placement attribute and the offset element. Applications reading a MusicXML file that can understand both features should generally rely on the default-x and default-y attributes for their greater accuracy. For the relative-x and relative-y attributes, the offset element, placement attribute, and directive attribute provide context for the relative position information, so the two features should be interpreted together. As elsewhere in the MusicXML format, tenths are the global tenths defined by the scaling element, not the local tenths of a staff resized by the staff-size element. \end{musicxml} \begin{code}
-- * Attributes
-- |
type Position = (Maybe Tenths, Maybe Tenths, Maybe Tenths, Maybe Tenths)
-- |
read_Position :: STM Result [Attribute] Position
read_Position = do
    y1 <- read_IMPLIED "default-x" read_Tenths 
    y2 <- read_IMPLIED "default-y" read_Tenths 
    y3 <- read_IMPLIED "relative-x" read_Tenths 
    y4 <- read_IMPLIED "relative-y" read_Tenths 
    return (y1,y2,y3,y4)
-- |
show_Position :: Position -> [Attribute]
show_Position (a,b,c,d) = 
    show_IMPLIED "default-x" show_Tenths a ++
    show_IMPLIED "default-y" show_Tenths b ++
    show_IMPLIED "relative-x" show_Tenths c ++
    show_IMPLIED "relative-y" show_Tenths d 
\end{code} \begin{musicxml} The placement attribute indicates whether something is above or below another element, such as a note or a notation. \end{musicxml} \begin{code}
-- |
type Placement = Maybe Placement_
-- |
read_Placement :: STM Result [Attribute] Placement
read_Placement = read_IMPLIED "placement" read_Placement_ 
-- |
show_Placement :: Placement -> [Attribute]
show_Placement = show_IMPLIED "placement" show_Placement_
-- |
data Placement_ = Placement_1 
                | Placement_2
                  deriving (Eq, Show)
-- |
read_Placement_ :: Data.Char.String -> Result Placement_
read_Placement_ "above" = return Placement_1
read_Placement_ "below" = return Placement_2
read_Placement_ _       =
    fail "wrong value at placement attribute"
-- |
show_Placement_ :: Placement_ -> Data.Char.String
show_Placement_ Placement_1 = "above"
show_Placement_ Placement_2 = "below"
\end{code} \begin{musicxml} The orientation attribute indicates whether slurs and ties are overhand (tips down) or underhand (tips up). This is distinct from the placement entity used by any notation type. \end{musicxml} \begin{code}
-- |
type Orientation = Maybe Orientation_
-- |
read_Orientation :: STM Result [Attribute] Orientation
read_Orientation = read_IMPLIED "orientation" read_Orientation_
-- |
show_Orientation :: Orientation -> [Attribute]
show_Orientation = show_IMPLIED "orientation" show_Orientation_
-- |
data Orientation_ = Orientation_1 | Orientation_2
                    deriving (Eq, Show)
-- |
read_Orientation_ :: Data.Char.String -> Result Orientation_
read_Orientation_ "over"  = return Orientation_1
read_Orientation_ "under" = return Orientation_2
read_Orientation_ _       =
    fail "wrong value at orientation attribute"
-- |
show_Orientation_ :: Orientation_ -> Data.Char.String
show_Orientation_ Orientation_1 = "over"
show_Orientation_ Orientation_2 = "under"
\end{code} \begin{musicxml} The directive entity changes the default-x position of a direction. It indicates that the left-hand side of the direction is aligned with the left-hand side of the time signature. If no time signature is present, it is aligned with the left-hand side of the first music notational element in the measure. If a default-x, justify, or halign attribute is present, it overrides the directive entity. \end{musicxml} \begin{code}
-- |
type Directive = Maybe Yes_No
-- |
read_Directive :: STM Result [Attribute] Directive
read_Directive =  read_IMPLIED "directive" read_Yes_No
-- |
show_Directive :: Directive -> [Attribute]
show_Directive = show_IMPLIED "directive" show_Yes_No
\end{code} \begin{musicxml} The bezier entity is used to indicate the curvature of slurs and ties, representing the control points for a cubic bezier curve. For ties, the bezier entity is used with the tied element. Normal slurs, S-shaped slurs, and ties need only two bezier points: one associated with the start of the slur or tie, the other with the stop. Complex slurs and slurs divided over system breaks can specify additional bezier data at slur elements with a continue type. The bezier-offset, bezier-x, and bezier-y attributes describe the outgoing bezier point for slurs and ties with a start type, and the incoming bezier point for slurs and ties with types of stop or continue. The attributes bezier-offset2, bezier-x2, and bezier-y2 are only valid with slurs of type continue, and describe the outgoing bezier point. The bezier-offset and bezier-offset2 attributes are measured in terms of musical divisions, like the offset element. These are the recommended attributes for specifying horizontal position. The other attributes are specified in tenths, relative to any position settings associated with the slur or tied element. \end{musicxml} \begin{code}
-- |
type Bezier = (Maybe CDATA, Maybe CDATA,
        Maybe Tenths, Maybe Tenths, Maybe Tenths, Maybe Tenths)
-- |
read_Bezier :: STM Result [Attribute] Bezier
read_Bezier = do
    y1 <- read_IMPLIED "bezier-offset" read_CDATA 
    y2 <- read_IMPLIED "bezier-offset2" read_CDATA
    y3 <- read_IMPLIED "bezier-x" read_Tenths 
    y4 <- read_IMPLIED "bezier-y" read_Tenths 
    y5 <- read_IMPLIED "bezier-x2" read_Tenths 
    y6 <- read_IMPLIED "bezier-y2" read_Tenths 
    return (y1,y2,y3,y4,y5,y6)
    
-- |
show_Bezier :: Bezier -> [Attribute]
show_Bezier (a,b,c,d,e,f) = 
    show_IMPLIED "bezier-offset" show_CDATA a ++
    show_IMPLIED "bezier-offset2" show_CDATA b ++
    show_IMPLIED "bezier-x" show_CDATA c ++
    show_IMPLIED "bezier-y" show_CDATA d ++
    show_IMPLIED "bezier-x2" show_CDATA e ++
    show_IMPLIED "bezier-y2" show_CDATA f 
\end{code} \begin{musicxml} The font entity gathers together attributes for determining the font within a directive or direction. They are based on the text styles for Cascading Style Sheets. The font-family is a comma-separated list of font names. These can be specific font styles such as Maestro or Opus, or one of several generic font styles: music, serif, sans-serif, handwritten, cursive, fantasy, and monospace. The music and handwritten values refer to music fonts; the rest refer to text fonts. The fantasy style refers to decorative text such as found in older German-style printing. The font-style can be normal or italic. The font-size can be one of the CSS sizes (xx-small, x-small, small, medium, large, x-large, xx-large) or a numeric point size. The font-weight can be normal or bold. The default is application-dependent, but is a text font vs. a music font. \end{musicxml} \begin{code}
-- |
type Font = (Maybe CDATA, Maybe CDATA, Maybe CDATA, Maybe CDATA)
-- |
read_Font :: STM Result [Attribute] Font
read_Font  = do
    y1 <- read_IMPLIED "font-family" read_CDATA 
    y2 <- read_IMPLIED "font-style" read_CDATA 
    y3 <- read_IMPLIED "font-size" read_CDATA 
    y4 <- read_IMPLIED "font-weight" read_CDATA 
    return (y1,y2,y3,y4)
-- |
show_Font :: Font -> [Attribute]
show_Font (a,b,c,d) = 
    show_IMPLIED "font-family" show_CDATA a ++
    show_IMPLIED "font-style" show_CDATA b ++
    show_IMPLIED "font-size" show_CDATA c ++
    show_IMPLIED "font-weight" show_CDATA d
\end{code} \begin{musicxml} The color entity indicates the color of an element. Color may be represented as hexadecimal RGB triples, as in HTML, or as hexadecimal ARGB tuples, with the A indicating alpha of transparency. An alpha value of 00 is totally transparent; FF is totally opaque. If RGB is used, the A value is assumed to be FF. For instance, the RGB value \ "\#800080" \ represents purple. An ARGB value of \ \ "\#40800080" \ would be a transparent purple. As in SVG 1.1, colors are defined in terms of the sRGB color space (IEC 61966). \end{musicxml} \begin{code}
-- |
type Color = Maybe CDATA
-- |
read_Color :: STM Result [Attribute] Color
read_Color = read_IMPLIED "color" read_CDATA
-- |
show_Color :: Color -> [Attribute]
show_Color = show_IMPLIED "color" show_CDATA
\end{code} \begin{musicxml} The text-decoration entity is based on the similar feature in XHTML and CSS. It allows for text to be underlined, overlined, or struck-through. It extends the CSS version by allow double or triple lines instead of just being on or off. \end{musicxml} \begin{code}
-- |
type Text_Decoration = (Maybe Number_Of_Lines, 
        Maybe Number_Of_Lines,
        Maybe Number_Of_Lines)
-- |
read_Text_Decoration :: STM Result [Attribute] Text_Decoration
read_Text_Decoration  = do
    y1 <- read_IMPLIED "underline" read_Number_Of_Lines 
    y2 <- read_IMPLIED "overline" read_Number_Of_Lines 
    y3 <- read_IMPLIED "line-through" read_Number_Of_Lines 
    return (y1,y2,y3)
-- |
show_Text_Decoration :: Text_Decoration -> [Attribute]
show_Text_Decoration (a,b,c) = 
    show_IMPLIED "underline" show_Number_Of_Lines a ++
    show_IMPLIED "overline" show_Number_Of_Lines b ++
    show_IMPLIED "line-through" show_Number_Of_Lines c 
\end{code} \begin{musicxml} The justify entity is used to indicate left, center, or right justification. The default value varies for different elements. \end{musicxml} \begin{code}
-- |
type Justify = Maybe Justify_
-- |
read_Justify :: STM Result [Attribute] Justify
read_Justify = read_IMPLIED "justify" read_Justify_
-- |
show_Justify :: Justify -> [Attribute]
show_Justify = show_IMPLIED "justify" show_Justify_
-- |
data Justify_ = Justify_1 | Justify_2 | Justify_3
                deriving (Eq, Show)
-- | 
read_Justify_ :: Data.Char.String -> Result Justify_
read_Justify_ "left"   = return Justify_1
read_Justify_ "center" = return Justify_2
read_Justify_ "right"  = return Justify_3
read_Justify_ _        =
    fail "wrong value at justify attribute"
-- |
show_Justify_ :: Justify_ -> Data.Char.String
show_Justify_ Justify_1 = "left"
show_Justify_ Justify_2 = "center"
show_Justify_ Justify_3 = "right"
\end{code} \begin{musicxml} In cases where text extends over more than one line, horizontal alignment and justify values can be different. The most typical case is for credits, such as: Words and music by Pat Songwriter Typically this type of credit is aligned to the right, so that the position information refers to the right- most part of the text. But in this example, the text is center-justified, not right-justified. The halign attribute is used in these situations. If it is not present, its value is the same as for the justify attribute. \end{musicxml} \begin{code}
-- |
type Halign = Maybe Halign_
-- |
read_Halign :: STM Result [Attribute] Halign
read_Halign = read_IMPLIED "halign" read_Halign_
-- |
show_Halign :: Halign -> [Attribute]
show_Halign = show_IMPLIED "halign" show_Halign_
-- |
data Halign_ = Halign_1 | Halign_2 | Halign_3
               deriving (Eq, Show)
-- | 
read_Halign_ :: Data.Char.String -> Result Halign_
read_Halign_ "left"   = return Halign_1
read_Halign_ "center" = return Halign_2
read_Halign_ "right"  = return Halign_3
read_Halign_ _        =
    fail "wrong value at halign attribute"
-- |
show_Halign_ :: Halign_ -> Data.Char.String
show_Halign_ Halign_1 = "left"
show_Halign_ Halign_2 = "center"
show_Halign_ Halign_3 = "right"
\end{code} \begin{musicxml} The valign entity is used to indicate vertical alignment to the top, middle, bottom, or baseline of the text. Defaults are implementation-dependent. \end{musicxml} \begin{code}
-- |
type Valign = Maybe Valign_
-- |
read_Valign :: STM Result [Attribute] Valign
read_Valign = read_IMPLIED "valign" read_Valign_
-- |
show_Valign :: Valign -> [Attribute]
show_Valign = show_IMPLIED "valign" show_Valign_
-- |
data Valign_ = Valign_1 | Valign_2 | Valign_3 | Valign_4
               deriving (Eq, Show)
-- | 
read_Valign_ :: Data.Char.String -> Result Valign_
read_Valign_ "top"      = return Valign_1
read_Valign_ "middle"   = return Valign_2
read_Valign_ "bottom"   = return Valign_3
read_Valign_ "baseline" = return Valign_4
read_Valign_ _          =
    fail "wrong value at valign attribute"
-- |
show_Valign_ :: Valign_ -> Data.Char.String
show_Valign_ Valign_1 = "top"
show_Valign_ Valign_2 = "middle"
show_Valign_ Valign_3 = "bottom"
show_Valign_ Valign_4 = "baseline"
\end{code} \begin{musicxml} The valign-image entity is used to indicate vertical alignment for images and graphics, so it removes the baseline value. Defaults are implementation-dependent. \end{musicxml} \begin{code}
-- |
type Valign_Image = Maybe Valign_Image_
-- |
read_Valign_Image :: STM Result [Attribute] Valign_Image
read_Valign_Image = read_IMPLIED "valign-image" read_Valign_Image_
-- |
show_Valign_Image :: Valign_Image -> [Attribute]
show_Valign_Image = show_IMPLIED "valign-image" show_Valign_Image_
-- |
data Valign_Image_ = Valign_Image_1 | Valign_Image_2 | Valign_Image_3 
                     deriving (Eq, Show)
-- | 
read_Valign_Image_ :: Data.Char.String -> Result Valign_Image_
read_Valign_Image_ "top"      = return Valign_Image_1
read_Valign_Image_ "middle"   = return Valign_Image_2
read_Valign_Image_ "bottom"   = return Valign_Image_3
read_Valign_Image_ _          =
    fail "wrong value at valign-image attribute"
-- |
show_Valign_Image_ :: Valign_Image_ -> Data.Char.String
show_Valign_Image_ Valign_Image_1 = "top"
show_Valign_Image_ Valign_Image_2 = "middle"
show_Valign_Image_ Valign_Image_3 = "bottom"
\end{code} \begin{musicxml} The letter-spacing entity specifies text tracking. Values are either "normal" or a number representing the number of ems to add between each letter. The number may be negative in order to subtract space. The default is normal, which allows flexibility of letter-spacing for purposes of text justification. \end{musicxml} \begin{code}
-- |
type Letter_Spacing = Maybe CDATA
-- |
read_Letter_Spacing :: STM Result [Attribute] Letter_Spacing
read_Letter_Spacing = read_IMPLIED "letter-spacing" read_CDATA
-- |
show_Letter_Spacing :: Letter_Spacing -> [Attribute]
show_Letter_Spacing = show_IMPLIED "letter-spacing" show_CDATA
\end{code} \begin{musicxml} The line-height entity specified text leading. Values are either "normal" or a number representing the percentage of the current font height to use for leading. The default is "normal". The exact normal value is implementation-dependent, but values between 100 and 120 are recommended. \end{musicxml} \begin{code}
-- |
type Line_Height = Maybe CDATA
-- |
read_Line_Height :: STM Result [Attribute] Line_Height
read_Line_Height = read_IMPLIED "line-height" read_CDATA
-- |
show_Line_Height :: Line_Height -> [Attribute]
show_Line_Height = show_IMPLIED "line-height" show_CDATA
\end{code} \begin{musicxml} The text-direction entity is used to adjust and override the Unicode bidirectional text algorithm, similar to the W3C Internationalization Tag Set recommendation. Values are ltr (left-to-right embed), rtl (right-to-left embed), lro (left-to-right bidi-override), and rlo (right-to-left bidi-override). The default value is ltr. This entity is typically used by applications that store text in left-to-right visual order rather than logical order. Such applications can use the lro value to better communicate with other applications that more fully support bidirectional text. \end{musicxml} \begin{code}
-- |
type Text_Direction = Maybe Text_Direction_
-- |
read_Text_Direction :: STM Result [Attribute] Text_Direction
read_Text_Direction = read_IMPLIED "dir" read_Text_Direction_
-- |
show_Text_Direction :: Text_Direction -> [Attribute]
show_Text_Direction = show_IMPLIED "dir" show_Text_Direction_
-- |
data Text_Direction_ = Text_Direction_1 
                     | Text_Direction_2
                     | Text_Direction_3
                     | Text_Direction_4
                     deriving (Eq, Show)
-- |
read_Text_Direction_ :: Data.Char.String -> Result Text_Direction_
read_Text_Direction_ "ltr" = return Text_Direction_1
read_Text_Direction_ "rtl" = return Text_Direction_2
read_Text_Direction_ "rlo" = return Text_Direction_3
read_Text_Direction_ "lro" = return Text_Direction_4
read_Text_Direction_ _     =
    fail "wrong value at text-direction attribute"
-- |
show_Text_Direction_ :: Text_Direction_ -> Data.Char.String
show_Text_Direction_ Text_Direction_1 = "ltr"
show_Text_Direction_ Text_Direction_2 = "rtl"
show_Text_Direction_ Text_Direction_3 = "rlo"
show_Text_Direction_ Text_Direction_4 = "lro"
\end{code} \begin{musicxml} The text-rotation entity is used to rotate text around the alignment point specified by the halign and valign entities. The value is a number ranging from -180 to 180. Positive values are clockwise rotations, while negative values are counter-clockwise rotations. \end{musicxml} \begin{code}
-- |
type Text_Rotation = Maybe CDATA
-- |
read_Text_Rotation :: STM Result [Attribute] Text_Rotation
read_Text_Rotation = read_IMPLIED "text-rotation" read_CDATA
-- |
show_Text_Rotation :: Text_Rotation -> [Attribute]
show_Text_Rotation = show_IMPLIED "text-rotation" show_CDATA
\end{code} \begin{musicxml} The print-style entity groups together the most popular combination of printing attributes: position, font, and color. \end{musicxml} \begin{code}
-- |
type Print_Style = (Position, Font, Color)
-- |
read_Print_Style :: STM Result [Attribute] Print_Style
read_Print_Style = do
    y1 <- read_Position 
    y2 <- read_Font 
    y3 <- read_Color 
    return (y1,y2,y3)
-- |
show_Print_Style :: Print_Style -> [Attribute]
show_Print_Style (a,b,c) = 
    show_Position a ++ show_Font b ++ show_Color c
\end{code} \begin{musicxml} The line-shape entity is used to distinguish between straight and curved lines. The line-type entity distinguishes between solid, dashed, dotted, and wavy lines. \end{musicxml} \begin{code}
type Line_Shape = Maybe Line_Shape_
-- |
read_Line_Shape :: STM Result [Attribute] Line_Shape
read_Line_Shape = read_IMPLIED "line-shape" read_Line_Shape_
-- |
show_Line_Shape :: Line_Shape -> [Attribute]
show_Line_Shape = show_IMPLIED "line-shape" show_Line_Shape_
-- |
data Line_Shape_ = Line_Shape_1 | Line_Shape_2
                   deriving (Eq, Show)
-- |
read_Line_Shape_ :: Data.Char.String -> Result Line_Shape_
read_Line_Shape_ "straight" = return Line_Shape_1
read_Line_Shape_ "curved"   = return Line_Shape_2
read_Line_Shape_ _          = 
    fail "wrong value at line-shape attribute"
-- |
show_Line_Shape_ :: Line_Shape_ -> Data.Char.String
show_Line_Shape_ Line_Shape_1 = "straight"
show_Line_Shape_ Line_Shape_2 = "curved"
-- |
type Line_Type = Maybe Line_Type_
-- |
read_Line_Type :: STM Result [Attribute] Line_Type
read_Line_Type = read_IMPLIED "line-type" read_Line_Type_
-- |
show_Line_Type :: Line_Type -> [Attribute]
show_Line_Type = show_IMPLIED "line-type" show_Line_Type_
-- |
data Line_Type_ = Line_Type_1 | Line_Type_2 | Line_Type_3 | Line_Type_4
                  deriving (Eq, Show)
-- |
read_Line_Type_ :: Data.Char.String -> Result Line_Type_
read_Line_Type_ "solid"  = return Line_Type_1
read_Line_Type_ "dashed" = return Line_Type_2
read_Line_Type_ "dotted" = return Line_Type_3
read_Line_Type_ "wavy"   = return Line_Type_4
read_Line_Type_ _        =
    fail "wrong value at line-type attribute"
show_Line_Type_ :: Line_Type_ -> Data.Char.String
show_Line_Type_ Line_Type_1 = "solid"
show_Line_Type_ Line_Type_2 = "dashed"
show_Line_Type_ Line_Type_3 = "dotted"
show_Line_Type_ Line_Type_4 = "wavy"
\end{code} \begin{musicxml} The printout entity is based on MuseData print suggestions. They allow a way to specify not to print print an object (e.g. note or rest), its augmentation dots, or its lyrics. This is especially useful for notes that overlap in different voices, or for chord sheets that contain lyrics and chords but no melody. For wholly invisible notes, such as those providing sound-only data, the attribute for print-spacing may be set to no so that no space is left for this note. The print-spacing value is only used if no note, dot, or lyric is being printed. By default, all these attributes are set to yes. If print-object is set to no, print-dot and print-lyric are interpreted to also be set to no if they are not present. \end{musicxml} \begin{code}
-- |
type Print_Object = Maybe Yes_No
-- |
read_Print_Object :: STM Result [Attribute] Print_Object
read_Print_Object = read_IMPLIED "print-object" read_Yes_No
-- |
show_Print_Object :: Print_Object -> [Attribute]
show_Print_Object = show_IMPLIED "print-object" show_Yes_No
-- |
type Print_Spacing = Maybe Yes_No
-- |
read_Print_Spacing :: STM Result [Attribute] Print_Spacing
read_Print_Spacing = read_IMPLIED "print-spacing" read_Yes_No
-- |
show_Print_Spacing :: Print_Spacing -> [Attribute]
show_Print_Spacing = show_IMPLIED "print-spacing" show_Yes_No
-- |
type Printout = (Print_Object, Maybe Yes_No, Print_Spacing, Maybe Yes_No)
-- |
read_Printout :: STM Result [Attribute] Printout 
read_Printout = do
    y1 <- read_Print_Object 
    y2 <- read_IMPLIED "print-dot" read_Yes_No 
    y3 <- read_Print_Spacing 
    y4 <-  read_IMPLIED "print-lyric" read_Yes_No 
    return (y1,y2,y3,y4)
-- |
show_Printout :: Printout -> [Attribute]
show_Printout (a,b,c,d) = 
    show_Print_Object a ++
    show_IMPLIED "print-dot" show_Yes_No b ++
    show_Print_Spacing c ++
    show_IMPLIED "print-lyric" show_Yes_No d
\end{code} \begin{musicxml} The text-formatting entity contains the common formatting attributes for text elements. Default values may differ across the elements that use this entity. \end{musicxml} \begin{code}
type Text_Formatting = (Justify, Halign, Valign, 
        Print_Style, Text_Decoration, Text_Rotation, Letter_Spacing,
        Line_Height, Maybe CDATA, Text_Direction, Maybe Text_Formatting_)
-- |
read_Text_Formatting :: STM Result [Attribute] Text_Formatting
read_Text_Formatting = do
    y1 <- read_Justify 
    y2 <- read_Halign 
    y3 <- read_Valign 
    y4 <- read_Print_Style 
    y5 <- read_Text_Decoration 
    y6 <- read_Text_Rotation 
    y7 <- read_Letter_Spacing 
    y8 <- read_Line_Height 
    y9 <-  read_IMPLIED "xml:lang" read_CDATA
    y10 <- read_Text_Direction 
    y11 <- read_IMPLIED "enclosure" read_Text_Formatting_
    return (y1,y2,y3,y4,y5,y6,y7,y8,y9,y10,y11)
-- |
show_Text_Formatting :: Text_Formatting -> [Attribute]
show_Text_Formatting (a,b,c,d,e,f,g,h,i,j,k) = 
    show_Justify a ++
    show_Halign b ++
    show_Valign c ++
    show_Print_Style d ++
    show_Text_Decoration e ++
    show_Text_Rotation f ++
    show_Letter_Spacing g ++
    show_Line_Height h ++
    show_IMPLIED "xml:lang" show_CDATA i ++
    show_Text_Direction j ++
    show_IMPLIED "enclosure" show_Text_Formatting_ k
-- |
data Text_Formatting_ = Text_Formatting_1 
                      | Text_Formatting_2
                      | Text_Formatting_3
                        deriving (Eq, Show)
-- |
read_Text_Formatting_ :: Data.Char.String -> Result Text_Formatting_
read_Text_Formatting_ "rectangle" = return Text_Formatting_1
read_Text_Formatting_ "oval"      = return Text_Formatting_2
read_Text_Formatting_ "none"      = return Text_Formatting_3
read_Text_Formatting_ _           =
    fail "wrong value at enclosure attribute"
-- |
show_Text_Formatting_ :: Text_Formatting_ -> Data.Char.String
show_Text_Formatting_ Text_Formatting_1 = "rectangle"
show_Text_Formatting_ Text_Formatting_2 = "oval"
show_Text_Formatting_ Text_Formatting_3 = "none"
\end{code} \begin{musicxml} The level-display entity allows specification of three common ways to indicate editorial indications: putting parentheses or square brackets around a symbol, or making the symbol a different size. If not specified, they are left to application defaults. It is used by the level and accidental elements. \end{musicxml} \begin{code}
-- |
type Level_Display = (Maybe Yes_No, Maybe Yes_No, Maybe Symbol_Size)
-- |
read_Level_Display :: STM Result [Attribute] Level_Display
read_Level_Display = do -- return (
    y1 <- read_IMPLIED "parentheses" read_Yes_No 
    y2 <- read_IMPLIED "braket" read_Yes_No 
    y3 <- read_IMPLIED "size" read_Symbol_Size 
    return (y1,y2,y3)
    
-- |
show_Level_Display :: Level_Display -> [Attribute]
show_Level_Display (a,b,c) =
    show_IMPLIED "parentheses" show_Yes_No a ++
    show_IMPLIED "braket" show_Yes_No b ++
    show_IMPLIED "size" show_Symbol_Size c 
\end{code} \begin{musicxml} Common structures for playback attribute definitions. The trill-sound entity includes attributes used to guide the sound of trills, mordents, turns, shakes, and wavy lines, based on MuseData sound suggestions. The default choices are: start-note = "upper" trill-step = "whole" two-note-turn = "none" accelerate = "no" beats = "4" (minimum of "2"). Second-beat and last-beat are percentages for landing on the indicated beat, with defaults of 25 and 75 respectively. For mordent and inverted-mordent elements, the defaults are different: The default start-note is "main", not "upper". The default for beats is "3", not "4". The default for second-beat is "12", not "25". The default for last-beat is "24", not "75". \end{musicxml} \begin{code}
-- * Attributes
-- |
type Trill_Sound = (
        Maybe Trill_Sound_A, Maybe Trill_Sound_B, Maybe Trill_Sound_C,
        Maybe Bool, Maybe CDATA, Maybe CDATA, Maybe CDATA)
-- |
read_Trill_Sound :: STM Result [Attribute] Trill_Sound
read_Trill_Sound = do
    y1 <- read_IMPLIED "start-note" read_Trill_Sound_A 
    y2 <- read_IMPLIED "trill-step" read_Trill_Sound_B 
    y3 <- read_IMPLIED "two-note-turn" read_Trill_Sound_C 
    y4 <- read_IMPLIED "accelerate" read_Yes_No 
    y5 <- read_IMPLIED "beats" read_CDATA 
    y6 <- read_IMPLIED "second-beat" read_CDATA 
    y7 <- read_IMPLIED "last-beat" read_CDATA 
    return (y1,y2,y3,y4,y5,y6,y7)
-- |
show_Trill_Sound :: Trill_Sound -> [Attribute]
show_Trill_Sound (a,b,c,d,e,f,g) =
    show_IMPLIED "start-note" show_Trill_Sound_A a ++
    show_IMPLIED "trill-step" show_Trill_Sound_B b ++
    show_IMPLIED "two-note-turn" show_Trill_Sound_C c ++
    show_IMPLIED "accelerate" show_Yes_No d ++
    show_IMPLIED "beats" show_CDATA e ++
    show_IMPLIED "second-beat" show_CDATA f ++
    show_IMPLIED "last-beat" show_CDATA g
-- |
data Trill_Sound_A = Trill_Sound_1 | Trill_Sound_2 | Trill_Sound_3
                     deriving (Eq, Show)
-- |
read_Trill_Sound_A :: Data.Char.String -> Result Trill_Sound_A
read_Trill_Sound_A "upper" = return Trill_Sound_1
read_Trill_Sound_A "main"  = return Trill_Sound_2
read_Trill_Sound_A "below" = return Trill_Sound_3
read_Trill_Sound_A _       =
    fail "wrong value at start-note attribute"
-- |
show_Trill_Sound_A :: Trill_Sound_A -> Data.Char.String
show_Trill_Sound_A Trill_Sound_1 = "upper"
show_Trill_Sound_A Trill_Sound_2 = "main"
show_Trill_Sound_A Trill_Sound_3 = "below"
-- |
data Trill_Sound_B = Trill_Sound_4 | Trill_Sound_5 | Trill_Sound_6
                     deriving (Eq, Show)
-- |
read_Trill_Sound_B :: Data.Char.String -> Result Trill_Sound_B
read_Trill_Sound_B "whole"  = return Trill_Sound_4
read_Trill_Sound_B "half"   = return Trill_Sound_5
read_Trill_Sound_B "unison" = return Trill_Sound_6
read_Trill_Sound_B _        =
    fail "wrong value at trill-step attribute"
-- |
show_Trill_Sound_B :: Trill_Sound_B -> Data.Char.String
show_Trill_Sound_B Trill_Sound_4 = "whole"
show_Trill_Sound_B Trill_Sound_5 = "half"
show_Trill_Sound_B Trill_Sound_6 = "unison"
-- |
data Trill_Sound_C = Trill_Sound_7 | Trill_Sound_8 | Trill_Sound_9
                     deriving (Eq, Show)
-- |
read_Trill_Sound_C :: Data.Char.String -> Result Trill_Sound_C
read_Trill_Sound_C "whole" = return Trill_Sound_7
read_Trill_Sound_C "half"  = return Trill_Sound_8
read_Trill_Sound_C "none"  = return Trill_Sound_9
read_Trill_Sound_C _       =
    fail "wrong value at two-note-turn attribute"
-- |
show_Trill_Sound_C :: Trill_Sound_C -> Data.Char.String
show_Trill_Sound_C Trill_Sound_7 = "whole"
show_Trill_Sound_C Trill_Sound_8 = "half"
show_Trill_Sound_C Trill_Sound_9 = "none"
\end{code} \begin{musicxml} The bend-sound entity is used for bend and slide elements, and is similar to the trill-sound. Here the beats element refers to the number of discrete elements (like MIDI pitch bends) used to represent a continuous bend or slide. The first-beat indicates the percentage of the direction for starting a bend; the last-beat the percentage for ending it. The default choices are: accelerate = "no" beats = "4" (minimum of "2") first-beat = "25" last-beat = "75" \end{musicxml} \begin{code}
-- |
type Bend_Sound = (Maybe Yes_No, Maybe CDATA, Maybe CDATA, Maybe CDATA)
-- |
read_Bend_Sound :: STM Result [Attribute] Bend_Sound
read_Bend_Sound = do
    y1 <- read_IMPLIED "accelerate" read_Yes_No 
    y2 <- read_IMPLIED "beats" read_CDATA 
    y3 <- read_IMPLIED "first-beat" read_CDATA 
    y4 <- read_IMPLIED "last-beat" read_CDATA 
    return (y1,y2,y3,y4)
-- |
show_Bend_Sound :: Bend_Sound -> [Attribute]
show_Bend_Sound (a,b,c,d) = 
    show_IMPLIED "accelerate" show_Yes_No a ++
    show_IMPLIED "beats" show_CDATA b ++
    show_IMPLIED "first-beat" show_CDATA c ++
    show_IMPLIED "second-beat" show_CDATA d
\end{code} \begin{musicxml} Common structures for other attribute definitions. The document-attributes entity is used to specify the attributes for an entire MusicXML document. Currently this is used for the version attribute. The version attribute was added in Version 1.1 for the score-partwise and score-timewise documents, and in Version 2.0 for opus documents. It provides an easier way to get version information than through the MusicXML public ID. The default value is 1.0 to make it possible for programs that handle later versions to distinguish earlier version files reliably. Programs that write MusicXML 1.1 or 2.0 files should set this attribute. \end{musicxml} \begin{code}
-- * Attributes
-- |
type Document_Attributes = CDATA
-- |
read_Document_Attributes :: STM Result [Attribute] Document_Attributes
read_Document_Attributes = read_DEFAULT "version" read_CDATA "1.0"
-- |
show_Document_Attributes :: Document_Attributes -> [Attribute]
show_Document_Attributes = show_DEFAULT "version" show_CDATA
\end{code} \begin{musicxml} Common structures for element definitions. Two entities for editorial information in notes. These entities, and their elements defined below, are used across all the different component DTD modules. \end{musicxml} \begin{code}
-- * Elements
-- |
type Editorial = (Maybe Footnote, Maybe Level)
-- | 
read_Editorial :: STM Result [Content i] (Editorial)
read_Editorial = do
    y1 <- read_MAYBE read_Footnote
    y2 <- read_MAYBE read_Level
    return (y1,y2)    
-- |
show_Editorial :: Editorial -> [Content ()]
show_Editorial (a,b) = 
    show_MAYBE show_Footnote a ++
    show_MAYBE show_Level b
-- |
type Editorial_Voice = (Maybe Footnote, Maybe Level, Maybe Voice)
-- | 
read_Editorial_Voice :: STM Result [Content i] Editorial_Voice
read_Editorial_Voice = do
    y1 <- read_MAYBE read_Footnote 
    y2 <- read_MAYBE read_Level 
    y3 <- read_MAYBE read_Voice 
    return (y1,y2,y3)
-- |
show_Editorial_Voice :: Editorial_Voice -> [Content ()]
show_Editorial_Voice (a,b,c) = 
    show_MAYBE show_Footnote a ++
    show_MAYBE show_Level b ++
    show_MAYBE show_Voice c
\end{code} \begin{musicxml} Footnote and level are used to specify editorial information, while voice is used to distinguish between multiple voices (what MuseData calls tracks) in individual parts. These elements are used throughout the different MusicXML DTD modules. If the reference attribute for the level element is yes, this indicates editorial information that is for display only and should not affect playback. For instance, a modern edition of older music may set reference="yes" on the attributes containing the music's original clef, key, and time signature. It is no by default. \end{musicxml} \begin{code}
-- * Elements
-- |
type Footnote = (Text_Formatting, PCDATA)
-- |
read_Footnote :: STM Result [Content i] Footnote
read_Footnote = do
    y <- read_ELEMENT "footnote" 
    y1 <- read_1 read_Text_Formatting (attributes y)
    y2 <- read_1 read_PCDATA (childs y)
    return (y1,y2)
-- |
show_Footnote :: Footnote -> [Content ()]
show_Footnote (a,b) = 
    show_ELEMENT "footnote" 
        (show_Text_Formatting a)
        (show_PCDATA b)
-- |
type Level = ((Maybe Yes_No, Level_Display), PCDATA)
-- | 
read_Level :: STM Result [Content i] Level
read_Level = do
    y <- read_ELEMENT "level" 
    y1 <- read_2 (read_IMPLIED "reference" read_Yes_No) 
                  read_Level_Display (attributes y)
    y2 <- read_1 read_PCDATA (childs y)
    return (y1,y2)
-- |
show_Level :: Level -> [Content ()]
show_Level ((a,b),c) = 
    show_ELEMENT "level" 
            (show_IMPLIED "reference" show_Yes_No a ++
            show_Level_Display b)
        (show_PCDATA c)
-- |
type Voice = PCDATA
-- | 
read_Voice :: STM Result [Content i] Voice
read_Voice = do
    y <- read_ELEMENT "voice" 
    read_1 read_PCDATA (childs y)
-- |
show_Voice :: Voice -> [Content ()]
show_Voice x = show_ELEMENT "voice" [] (show_PCDATA x)
\end{code} \begin{musicxml} Fermata and wavy-line elements can be applied both to notes and to measures, so they are defined here. Wavy lines are one way to indicate trills; when used with a measure element, they should always have type="continue" set. The fermata text content represents the shape of the fermata sign and may be normal, angled, or square. An empty fermata element represents a normal fermata. The fermata type is upright if not specified. \end{musicxml} \begin{code}
-- |
type Fermata = ((Maybe Fermata_, Print_Style), PCDATA)
data Fermata_ = Fermata_1 | Fermata_2
                deriving (Eq, Show)
-- | 
read_Fermata_ :: Data.Char.String -> Result Fermata_
read_Fermata_ "upright"  = return Fermata_1
read_Fermata_ "inverted" = return Fermata_2
read_Fermata_ _          =
    fail "I expect type attribute"
-- |
show_Fermata_ :: Fermata_ -> Data.Char.String
show_Fermata_ Fermata_1 = "upright"
show_Fermata_ Fermata_2 = "inverted"
-- |
read_Fermata :: STM Result [Content i] Fermata
read_Fermata = do
    y <- read_ELEMENT "fermata"
    y1 <- read_2 (read_IMPLIED "type" read_Fermata_) 
                  read_Print_Style (attributes y)
    y2 <- read_1 read_PCDATA (childs y)
    return (y1,y2)
-- |
show_Fermata :: Fermata -> [Content ()]
show_Fermata ((a,b),c) =
    show_ELEMENT "fermata" 
        (show_IMPLIED "type" show_Fermata_ a ++
         show_Print_Style b)
        (show_PCDATA c)
-- |
type Wavy_Line = ((Start_Stop_Continue, Maybe Number_Level,
        Position, Placement, Color, Trill_Sound),())
-- |
read_Wavy_Line :: STM Result [Content i] Wavy_Line
read_Wavy_Line = do
    y <- read_ELEMENT "wavy-line" 
    y1 <- read_6 (read_REQUIRED "type" read_Start_Stop_Continue) 
                 (read_IMPLIED "number" read_Number_Level) 
                 read_Position read_Placement read_Color 
                 read_Trill_Sound (attributes y)
    return (y1,())
-- |
show_Wavy_Line :: Wavy_Line -> [Content ()]
show_Wavy_Line ((a,b,c,d,e,f),()) = 
        show_ELEMENT "wavy-line" 
            (show_REQUIRED "type" show_Start_Stop_Continue a ++
             show_IMPLIED "number" show_Number_Level b ++
             show_Position c ++
             show_Placement d ++
             show_Color e ++
             show_Trill_Sound f
            )
            []
\end{code} \begin{musicxml} Staff assignment is only needed for music notated on multiple staves. Used by both notes and directions. Staff values are numbers, with 1 referring to the top-most staff in a part. \end{musicxml} \begin{code}
-- |
type Staff = PCDATA
-- | 
read_Staff :: STM Result [Content i] Staff
read_Staff = do
    y <- read_ELEMENT "staff" 
    read_1 read_PCDATA (childs y)
-- |
show_Staff :: Staff -> [Content ()]
show_Staff x = show_ELEMENT "staff" [] (show_PCDATA x)
\end{code} \begin{musicxml} Segno and coda signs can be associated with a measure or a general musical direction. These are visual indicators only; a sound element is needed to guide playback applications reliably. \end{musicxml} \begin{code}
-- |
type Segno = (Print_Style, ())
-- |
read_Segno :: STM Result [Content i] Segno
read_Segno = do
    y <- read_ELEMENT "segno"
    y1 <- read_1 read_Print_Style (attributes y)
    return (y1,())
-- |
show_Segno :: Segno -> [Content ()]
show_Segno (x,_) = show_ELEMENT "segno" (show_Print_Style x) []
-- |
type Coda = (Print_Style, ())
-- |
read_Coda :: STM Result [Content i] Coda
read_Coda = do
    y <- read_ELEMENT "coda"
    y1 <- read_1 read_Print_Style (attributes y)
    return (y1,())
-- |
show_Coda :: Coda -> [Content ()]
show_Coda (x,_) = show_ELEMENT "coda" (show_Print_Style x) []
\end{code} \begin{musicxml} These elements are used both in the time-modification and metronome-tuplet elements. The actual-notes element describes how many notes are played in the time usually occupied by the number of normal-notes. If the normal-notes type is different than the current note type (e.g., a quarter note within an eighth note triplet), then the normal-notes type (e.g. eighth) is specified in the normal-type and normal-dot elements. \end{musicxml} \begin{code}
-- |
type Actual_Notes = PCDATA
-- | 
read_Actual_Notes :: STM Result [Content i] Actual_Notes
read_Actual_Notes = do
    y <- read_ELEMENT "actual-notes" 
    read_1 read_PCDATA (childs y)
-- |
show_Actual_Notes :: Actual_Notes -> [Content ()]
show_Actual_Notes x = show_ELEMENT "actual-notes" [] (show_PCDATA x)
-- |
type Normal_Notes = PCDATA
-- | 
read_Normal_Notes :: STM Result [Content i] Normal_Notes
read_Normal_Notes = do
    y <- read_ELEMENT "normal-notes" 
    read_1 read_PCDATA (childs y)
-- |
show_Normal_Notes :: Normal_Notes -> [Content ()]
show_Normal_Notes x = show_ELEMENT "normal-notes" [] (show_PCDATA x)
-- |
type Normal_Type = PCDATA
-- | 
read_Normal_Type :: STM Result [Content i] Normal_Type
read_Normal_Type = do
    y <- read_ELEMENT "normal-type"
    read_1 read_PCDATA (childs y)
-- |
show_Normal_Type :: Normal_Type -> [Content ()]
show_Normal_Type x = show_ELEMENT "normal-type" [] (show_PCDATA x)
-- |
type Normal_Dot = ()
-- | 
read_Normal_Dot :: STM Result [Content i] Normal_Dot
read_Normal_Dot = read_ELEMENT "normal-dot" >> return ()
-- |
show_Normal_Dot :: Normal_Dot -> [Content ()]
show_Normal_Dot _ = show_ELEMENT "normal-dot" [] []
\end{code} \begin{musicxml} Dynamics can be associated either with a note or a general musical direction. To avoid inconsistencies between and amongst the letter abbreviations for dynamics (what is sf vs. sfz, standing alone or with a trailing dynamic that is not always piano), we use the actual letters as the names of these dynamic elements. The other-dynamics element allows other dynamic marks that are not covered here, but many of those should perhaps be included in a more general musical direction element. Dynamics may also be combined as in . These letter dynamic symbols are separated from crescendo, decrescendo, and wedge indications. Dynamic representation is inconsistent in scores. Many things are assumed by the composer and left out, such as returns to original dynamics. Systematic representations are quite complex: for example, Humdrum has at least 3 representation formats related to dynamics. The MusicXML format captures what is in the score, but does not try to be optimal for analysis or synthesis of dynamics. \end{musicxml} \begin{nocode} read_P_F :: [Content i] -> ([Content i], Result ()) read_P_F l = let (s,x) = read_ELEMENT_F "p" l in (s, x `and` const (return ())) read_P_J :: () read_P_J = () \end{nocode} \begin{code}
-- |
type Dynamics = ((Print_Style, Placement),[Dynamics_])
-- | 
read_Dynamics :: Eq i => STM Result [Content i] Dynamics
read_Dynamics = do
    y <- read_ELEMENT "dynamics"
    y1 <- read_2 read_Print_Style read_Placement (attributes y)
    y2 <- read_1 (read_LIST read_Dynamics_) (childs y)
    return (y1,y2)
-- |
show_Dynamics :: Dynamics -> [Content ()]
show_Dynamics ((a,b),c) = 
    show_ELEMENT "dynamics" 
        (show_Print_Style a ++ show_Placement b) 
        (show_LIST show_Dynamics_ c)
-- |
data Dynamics_ = Dynamics_1 P
               | Dynamics_2 PP
               | Dynamics_3 PPP
               | Dynamics_4 PPPP
               | Dynamics_5 PPPPP
               | Dynamics_6 PPPPPP
               | Dynamics_7 F
               | Dynamics_8 FF
               | Dynamics_9 FFF
               | Dynamics_10 FFFF
               | Dynamics_11 FFFFF
               | Dynamics_12 FFFFFF
               | Dynamics_13 MP
               | Dynamics_14 MF
               | Dynamics_15 SF
               | Dynamics_16 SFP
               | Dynamics_17 SFPP
               | Dynamics_18 FP
               | Dynamics_19 RF
               | Dynamics_20 RFZ
               | Dynamics_21 SFZ
               | Dynamics_22 SFFZ
               | Dynamics_23 FZ
               | Dynamics_24 Other_Dynamics
                 deriving (Eq, Show)
-- |
read_Dynamics_ :: STM Result [Content i] Dynamics_
read_Dynamics_  = 
   (read_P >>= return . Dynamics_1) `mplus`
   (read_PP >>= return . Dynamics_2) `mplus`
   (read_PPP >>= return . Dynamics_3) `mplus`
   (read_PPPP >>= return . Dynamics_4) `mplus`
   (read_PPPPP >>= return . Dynamics_5) `mplus`
   (read_PPPPPP >>= return . Dynamics_6) `mplus`
   (read_F >>= return . Dynamics_7) `mplus`
   (read_FF >>= return . Dynamics_8) `mplus`
   (read_FFF >>= return . Dynamics_9) `mplus`
   (read_FFFF >>= return . Dynamics_10) `mplus`
   (read_FFFFF >>= return . Dynamics_11) `mplus`
   (read_FFFFFF >>= return . Dynamics_12) `mplus`
   (read_MP >>= return . Dynamics_13) `mplus`
   (read_MF >>= return . Dynamics_14) `mplus`
   (read_SF >>= return . Dynamics_15) `mplus`
   (read_SFP >>= return . Dynamics_16) `mplus`
   (read_SFPP >>= return . Dynamics_17) `mplus`
   (read_FP >>= return . Dynamics_18) `mplus`
   (read_RF >>= return . Dynamics_19) `mplus`
   (read_RFZ >>= return . Dynamics_20) `mplus`
   (read_SFZ >>= return . Dynamics_21) `mplus`
   (read_SFFZ >>= return . Dynamics_22) `mplus`
   (read_FZ >>= return . Dynamics_23) `mplus`
   (read_Other_Dynamics >>= return . Dynamics_24) 
-- |
show_Dynamics_ :: Dynamics_ -> [Content ()]
show_Dynamics_ (Dynamics_1 x) = show_P x
show_Dynamics_ (Dynamics_2 x) = show_PP x
show_Dynamics_ (Dynamics_3 x) = show_PPP x
show_Dynamics_ (Dynamics_4 x) = show_PPPP x
show_Dynamics_ (Dynamics_5 x) = show_PPPPP x
show_Dynamics_ (Dynamics_6 x) = show_PPPPPP x
show_Dynamics_ (Dynamics_7 x) = show_F x
show_Dynamics_ (Dynamics_8 x) = show_FF x
show_Dynamics_ (Dynamics_9 x) = show_FFF x
show_Dynamics_ (Dynamics_10 x) = show_FFFF x
show_Dynamics_ (Dynamics_11 x) = show_FFFFF x
show_Dynamics_ (Dynamics_12 x) = show_FFFFFF x
show_Dynamics_ (Dynamics_13 x) = show_MP x
show_Dynamics_ (Dynamics_14 x) = show_MF x
show_Dynamics_ (Dynamics_15 x) = show_SF x
show_Dynamics_ (Dynamics_16 x) = show_SFP x
show_Dynamics_ (Dynamics_17 x) = show_SFPP x
show_Dynamics_ (Dynamics_18 x) = show_FP x
show_Dynamics_ (Dynamics_19 x) = show_RF x
show_Dynamics_ (Dynamics_20 x) = show_RFZ x
show_Dynamics_ (Dynamics_21 x) = show_SFZ x
show_Dynamics_ (Dynamics_22 x) = show_SFFZ x
show_Dynamics_ (Dynamics_23 x) = show_FZ x
show_Dynamics_ (Dynamics_24 x) = show_Other_Dynamics x
-- |
type P = ()
-- |
read_P :: STM Result [Content i] P
read_P = read_ELEMENT "p" >> return ()
-- |
show_P :: P -> [Content ()]
show_P _ = show_ELEMENT "p" [] []
-- |
type PP = ()
-- | 
read_PP :: STM Result [Content i] PP
read_PP = read_ELEMENT "pp" >> return ()
-- |
show_PP :: PP -> [Content ()]
show_PP _ = show_ELEMENT "pp" [] []
-- |
type PPP = ()
-- | 
read_PPP :: STM Result [Content i] PPP
read_PPP = read_ELEMENT "ppp" >> return ()
-- |
show_PPP :: PPP -> [Content ()]
show_PPP _ = show_ELEMENT "ppp" [] []
-- |
type PPPP = ()
-- | 
read_PPPP :: STM Result [Content i] PPPP
read_PPPP = read_ELEMENT "pppp" >> return ()
-- |
show_PPPP :: PPPP -> [Content ()]
show_PPPP _ = show_ELEMENT "pppp" [] []
-- |
type PPPPP = ()
-- | 
read_PPPPP :: STM Result [Content i] PPPPP
read_PPPPP = read_ELEMENT "ppppp" >> return ()
-- |
show_PPPPP :: PPPPP -> [Content ()]
show_PPPPP _ = show_ELEMENT "ppppp" [] []
-- |
type PPPPPP = ()
-- | 
read_PPPPPP :: STM Result [Content i] PPPPPP
read_PPPPPP = read_ELEMENT "pppppp" >> return ()
-- |
show_PPPPPP :: PPPPPP -> [Content ()]
show_PPPPPP _ = show_ELEMENT "pppppp" [] []
-- |
type FFFFFF = ()
-- | 
read_FFFFFF :: STM Result [Content i] FFFFFF
read_FFFFFF = read_ELEMENT "ffffff" >> return ()
-- |
show_FFFFFF :: FFFFFF -> [Content ()]
show_FFFFFF _ = show_ELEMENT "ffffff" [] []
-- |
type FFFFF = ()
-- | 
read_FFFFF :: STM Result [Content i] FFFFF
read_FFFFF = read_ELEMENT "fffff" >> return ()
-- |
show_FFFFF :: FFFFF -> [Content ()]
show_FFFFF _ = show_ELEMENT "fffff" [] []
-- |
type FFFF = ()
-- | 
read_FFFF :: STM Result [Content i] FFFF
read_FFFF = read_ELEMENT "ffff" >> return ()
-- |
show_FFFF :: FFFF -> [Content ()]
show_FFFF _ = show_ELEMENT "ffff" [] []
-- |
type FFF = ()
-- | 
read_FFF :: STM Result [Content i] FFF
read_FFF = read_ELEMENT "fff" >> return ()
-- |
show_FFF :: FFF -> [Content ()]
show_FFF _ = show_ELEMENT "fff" [] []
-- |
type FF = ()
-- | 
read_FF :: STM Result [Content i] FF
read_FF = read_ELEMENT "ff" >> return ()
-- |
show_FF :: FF -> [Content ()]
show_FF _ = show_ELEMENT "ff" [] []
-- |
type F = ()
-- | 
read_F :: STM Result [Content i] F
read_F  = read_ELEMENT "f" >> return ()
-- |
show_F :: F -> [Content ()]
show_F _ = show_ELEMENT "f" [] []
-- |
type MP = ()
-- | 
read_MP :: STM Result [Content i] MP
read_MP = read_ELEMENT "mp" >> return ()
-- |
show_MP :: MP -> [Content ()]
show_MP _ = show_ELEMENT "mp" [] []
-- |
type MF = ()
-- | 
read_MF :: STM Result [Content i] MF
read_MF = read_ELEMENT "mf" >> return ()
-- |
show_MF :: MF -> [Content ()]
show_MF _ = show_ELEMENT "mf" [] []
-- |
type SF = ()
-- | 
read_SF :: STM Result [Content i] SF
read_SF = read_ELEMENT "sf" >> return ()
-- |
show_SF :: SF -> [Content ()]
show_SF _ = show_ELEMENT "sf" [] []
-- |
type SFP = ()
-- | 
read_SFP :: STM Result [Content i] SFP
read_SFP = read_ELEMENT "sfp" >> return ()
-- |
show_SFP :: SFP -> [Content ()]
show_SFP _ = show_ELEMENT "sfp" [] []
-- |
type SFPP = ()
-- | 
read_SFPP :: STM Result [Content i] SFPP
read_SFPP = read_ELEMENT "sfpp" >> return ()
-- |
show_SFPP :: SFPP -> [Content ()]
show_SFPP _ = show_ELEMENT "sfpp" [] []
-- |
type FP = ()
-- | 
read_FP :: STM Result [Content i] FP
read_FP = read_ELEMENT "fp" >> return ()
-- |
show_FP :: FP -> [Content ()]
show_FP _ = show_ELEMENT "fp" [] []
-- |
type RF = ()
-- | 
read_RF :: STM Result [Content i] RF
read_RF = read_ELEMENT "rf" >> return ()
-- |
show_RF :: RF -> [Content ()]
show_RF _ = show_ELEMENT "rf" [] []
-- |
type RFZ = ()
-- | 
read_RFZ :: STM Result [Content i] RFZ
read_RFZ = read_ELEMENT "rfz" >> return ()
-- |
show_RFZ :: RFZ -> [Content ()]
show_RFZ _ = show_ELEMENT "rfz" [] []
-- |
type SFZ = ()
-- | 
read_SFZ :: STM Result [Content i] SFZ
read_SFZ = read_ELEMENT "sfz" >> return ()
-- |
show_SFZ :: SFZ -> [Content ()]
show_SFZ _ = show_ELEMENT "sfz" [] []
-- |
type SFFZ = ()
-- | 
read_SFFZ :: STM Result [Content i] SFFZ
read_SFFZ = read_ELEMENT "sffz" >> return ()
-- |
show_SFFZ :: SFFZ -> [Content ()]
show_SFFZ _ = show_ELEMENT "sffz" [] []
-- |
type FZ = ()
-- | 
read_FZ :: STM Result [Content i] FZ
read_FZ = read_ELEMENT "fz" >> return ()
-- |
show_FZ :: FZ -> [Content ()]
show_FZ _ = show_ELEMENT "fz" [] []
-- |
type Other_Dynamics = PCDATA
-- | 
read_Other_Dynamics :: STM Result [Content i] Other_Dynamics
read_Other_Dynamics = do
    y <- read_ELEMENT "other-dynamics" 
    read_1 read_PCDATA (childs y)
-- |
show_Other_Dynamics :: Other_Dynamics -> [Content ()]
show_Other_Dynamics x = show_ELEMENT "other-dynamics" [] (show_PCDATA x)
\end{code} \begin{musicxml} The fret, string, and fingering elements can be used either in a technical element for a note or in a frame element as part of a chord symbol. Fingering is typically indicated 1,2,3,4,5. Multiple fingerings may be given, typically to substitute fingerings in the middle of a note. The substitution and alternate values are "no" if the attribute is not present. For guitar and other fretted instruments, the fingering element represents the fretting finger; the pluck element represents the plucking finger. \end{musicxml} \begin{code}
-- |
type Fingering = ((Maybe Yes_No, Maybe Yes_No, Print_Style, Placement), PCDATA)
-- |
read_Fingering :: STM Result [Content i] Fingering
read_Fingering = do
    y <- read_ELEMENT "fingering" 
    y1 <- read_4 (read_IMPLIED "substitution" read_Yes_No) 
                 (read_IMPLIED "alternate" read_Yes_No)
                 read_Print_Style read_Placement (attributes y)
    y2 <- read_1 read_PCDATA (childs y)
    return (y1,y2)
-- | 
show_Fingering :: Fingering -> [Content ()]
show_Fingering ((a,b,c,d),e)= 
    show_ELEMENT "fingering" 
        (show_IMPLIED "substitution" show_Yes_No a ++
         show_IMPLIED "alternate" show_Yes_No b ++
         show_Print_Style c ++
         show_Placement d)
        (show_PCDATA e)
\end{code} \begin{musicxml} Fret and string are used with tablature notation and chord symbols. Fret numbers start with 0 for an open string and 1 for the first fret. String numbers start with 1 for the highest string. The string element can also be used in regular notation. \end{musicxml} \begin{code}
-- |
type Fret = ((Font, Color), PCDATA)
-- |
read_Fret :: STM Result [Content i] Fret
read_Fret = do
    y <- read_ELEMENT "fret" 
    y1 <- read_2 read_Font read_Color (attributes y)
    y2 <- read_1 read_PCDATA (childs y)
    return (y1,y2)
-- |
show_Fret :: Fret -> [Content ()]
show_Fret ((a,b),c) = 
    show_ELEMENT "fret" 
        (show_Font a ++ show_Color b)
        (show_PCDATA c)
-- |
type String = ((Print_Style, Placement), PCDATA)
-- |
read_String :: STM Result [Content i] String
read_String = do
    y <- read_ELEMENT "string"
    y1 <- read_2 read_Print_Style read_Placement (attributes y)
    y2 <- read_1 read_PCDATA (childs y)
    return (y1,y2)
-- |
show_String :: String -> [Content ()]
show_String ((a,b),c) = 
    show_ELEMENT "string" 
        (show_Print_Style a ++ show_Placement b)
        (show_PCDATA c)
\end{code} \begin{musicxml} The tuning-step, tuning-alter, and tuning-octave elements are represented like the step, alter, and octave elements, with different names to reflect their different function. They are used in the staff-tuning and accord elements. \end{musicxml} \begin{code}
-- |
type Tuning_Step = PCDATA
-- | 
read_Tuning_Step :: STM Result [Content i] Tuning_Step
read_Tuning_Step = do
    y <- read_ELEMENT "tuning-step" 
    read_1 read_PCDATA (childs y)
-- |
show_Tuning_Step :: Tuning_Step -> [Content ()]
show_Tuning_Step x = show_ELEMENT "tuning-step" [] (show_PCDATA x)
-- |
type Tuning_Alter = PCDATA
-- | 
read_Tuning_Alter :: STM Result [Content i] Tuning_Alter
read_Tuning_Alter = do
    y <- read_ELEMENT "tuning-alter" 
    read_1 read_PCDATA (childs y)
-- |
show_Tuning_Alter :: Tuning_Alter -> [Content ()]
show_Tuning_Alter x = show_ELEMENT "tuning-alter" [] (show_PCDATA x)
-- |
type Tuning_Octave = PCDATA
-- | 
read_Tuning_Octave :: STM Result [Content i] Tuning_Octave
read_Tuning_Octave = do
    y <- read_ELEMENT "tuning-octave"
    read_1 read_PCDATA (childs y)
-- |
show_Tuning_Octave :: Tuning_Octave -> [Content ()]
show_Tuning_Octave x = show_ELEMENT "tuning-octave" [] (show_PCDATA x)
\end{code} \begin{musicxml} The display-text element is used for exact formatting of multi-font text in element in display elements such as part-name-display. Language is Italian ("it") by default. Enclosure is none by default. \end{musicxml} \begin{code}
-- |
type Display_Text = (Text_Formatting, PCDATA)
-- |
read_Display_Text :: STM Result [Content i] Display_Text
read_Display_Text = do
    y <- read_ELEMENT "display-text"
    y1 <- read_1 read_Text_Formatting (attributes y)
    y2 <- read_1 read_PCDATA (childs y)
    return (y1,y2)    
-- |
show_Display_Text :: Display_Text -> [Content ()]
show_Display_Text (a,b) = 
    show_ELEMENT "display-text"
        (show_Text_Formatting a)
        (show_PCDATA b)
\end{code} \begin{musicxml} The accidental-text element is used for exact formatting of accidentals in display elements such as part-name-display. Values are the same as for the accidental element. Enclosure is none by default. \end{musicxml} \begin{code}
-- |
type Accidental_Text = (Text_Formatting, PCDATA)
-- |
read_Accidental_Text :: STM Result [Content i] Accidental_Text
read_Accidental_Text = do
    y <- read_ELEMENT "accidental-text"
    y1 <- read_1 read_Text_Formatting (attributes y)
    y2 <- read_1 read_PCDATA (childs y)
    return (y1,y2)
-- |
show_Accidental_Text :: Accidental_Text -> [Content ()]
show_Accidental_Text (a,b) = 
    show_ELEMENT "accidental-text"
        (show_Text_Formatting a)
        (show_PCDATA b)
\end{code} \begin{musicxml} The part-name-display and part-abbreviation-display elements are used in both the \ score.mod and direction.mod files. They allow more precise control of how part names and abbreviations appear throughout a score. The print-object attributes can be used to determine what, if anything, is printed at the start of each system. Formatting specified in the part-name-display and part-abbreviation-display elements override the formatting specified in the part-name and part-abbreviation elements, respectively. \end{musicxml} \begin{code}
type Part_Name_Display = (Print_Object, [Part_Name_Display_])
-- |
read_Part_Name_Display :: Eq i => STM Result [Content i] Part_Name_Display
read_Part_Name_Display = do
    y <- read_ELEMENT "part-name-display"
    y1 <- read_1 read_Print_Object (attributes y)
    y2 <- read_1 (read_LIST read_Part_Name_Display_) (childs y)
    return (y1,y2)
-- | 
show_Part_Name_Display :: Part_Name_Display -> [Content ()]
show_Part_Name_Display (a,b) = 
    show_ELEMENT "part-name-display"
        (show_Print_Object a)
        (show_LIST show_Part_Name_Display_ b)
-- |
data Part_Name_Display_ = Part_Name_Display_1 Display_Text 
                        | Part_Name_Display_2 Accidental_Text
                        deriving (Eq, Show)
-- |
read_Part_Name_Display_ :: STM Result [Content i] Part_Name_Display_
read_Part_Name_Display_ = 
    (read_Display_Text >>= (return . Part_Name_Display_1)) `mplus`
    (read_Accidental_Text >>= (return . Part_Name_Display_2)) `mplus`
    fail "part-name-display"
-- |
show_Part_Name_Display_ :: Part_Name_Display_ -> [Content ()]
show_Part_Name_Display_ (Part_Name_Display_1 x) = show_Display_Text x
show_Part_Name_Display_ (Part_Name_Display_2 x) = show_Accidental_Text x
-- |
type Part_Abbreviation_Display = (Print_Object, [Part_Abbreviation_Display_])
-- |
read_Part_Abbreviation_Display :: Eq i => 
    STM Result [Content i] Part_Abbreviation_Display
read_Part_Abbreviation_Display = do
    y <- read_ELEMENT "part-abbreviation-display"
    y1 <- read_1 read_Print_Object (attributes y)
    y2 <- read_1 (read_LIST read_Part_Abbreviation_Display_) (childs y)
    return (y1,y2)
-- | 
show_Part_Abbreviation_Display :: Part_Abbreviation_Display -> [Content ()]
show_Part_Abbreviation_Display (a,b) = 
    show_ELEMENT "part-abbreviation-display"
        (show_Print_Object a)
        (show_LIST show_Part_Abbreviation_Display_ b)
-- |
data Part_Abbreviation_Display_ = 
      Part_Abbreviation_Display_1 Display_Text 
    | Part_Abbreviation_Display_2 Accidental_Text
      deriving (Eq, Show)
-- |
read_Part_Abbreviation_Display_ :: 
    STM Result [Content i] Part_Abbreviation_Display_
read_Part_Abbreviation_Display_ = 
    (read_Display_Text >>= (return . Part_Abbreviation_Display_1)) `mplus`
    (read_Accidental_Text >>= (return . Part_Abbreviation_Display_2)) `mplus`
    fail "part-name-display"
-- |
show_Part_Abbreviation_Display_ :: Part_Abbreviation_Display_ -> [Content ()]
show_Part_Abbreviation_Display_ 
    (Part_Abbreviation_Display_1 x) = show_Display_Text x
show_Part_Abbreviation_Display_ 
    (Part_Abbreviation_Display_2 x) = show_Accidental_Text x
-- |
\end{code} \begin{musicxml} The midi-instrument element can be a part of either the score-instrument element at the start of a part, or the sound element within a part. The id attribute refers to the score-instrument affected by the change. \end{musicxml} \begin{code}
-- |
type Midi_Instrument = (ID, (Maybe Midi_Channel, Maybe Midi_Name, 
    Maybe Midi_Bank, Maybe Midi_Program, Maybe Midi_Unpitched,
    Maybe Volume, Maybe Pan, Maybe Elevation))
-- |
read_Midi_Instrument :: STM Result [Content i] Midi_Instrument
read_Midi_Instrument = do
    y <- read_ELEMENT "midi-instrument"
    y1 <- read_1 (read_REQUIRED "id" read_ID) (attributes y)
    y2 <- read_8 (read_MAYBE read_Midi_Channel) (read_MAYBE read_Midi_Name)
                 (read_MAYBE read_Midi_Bank) (read_MAYBE read_Midi_Program)
                 (read_MAYBE read_Midi_Unpitched) (read_MAYBE read_Volume) 
                 (read_MAYBE read_Pan) (read_MAYBE read_Elevation)
                 (childs y)
    return (y1,y2)
-- |
show_Midi_Instrument :: Midi_Instrument -> [Content ()]
show_Midi_Instrument (a,(b,c,d,e,f,g,h,i)) = 
    show_ELEMENT "midi-instrument" 
        (show_REQUIRED "id" show_ID a)
        (show_MAYBE show_Midi_Channel b ++ show_MAYBE show_Midi_Name c ++
         show_MAYBE show_Midi_Bank d ++ show_MAYBE show_Midi_Program e ++
         show_MAYBE show_Midi_Unpitched f ++ show_MAYBE show_Volume g ++
         show_MAYBE show_Pan h ++ show_MAYBE show_Elevation i)
\end{code} \begin{musicxml} MIDI 1.0 channel numbers range from 1 to 16. \end{musicxml} \begin{code}
-- |
type Midi_Channel = PCDATA
-- |
read_Midi_Channel :: STM Result [Content i] Midi_Channel
read_Midi_Channel = do
    y <- read_ELEMENT "midi-channel" 
    read_1 read_PCDATA (childs y)
-- |
show_Midi_Channel :: Midi_Channel -> [Content ()]
show_Midi_Channel x = 
    show_ELEMENT "midi-channel" [] (show_PCDATA x)
\end{code} \begin{musicxml} MIDI names correspond to ProgramName meta-events within a Standard MIDI File. \end{musicxml} \begin{code}
-- |
type Midi_Name = PCDATA
-- |
read_Midi_Name :: STM Result [Content i] Midi_Name
read_Midi_Name = do
    y <- read_ELEMENT "midi-name" 
    read_1 read_PCDATA (childs y)
-- |
show_Midi_Name :: Midi_Name -> [Content ()]
show_Midi_Name x = 
    show_ELEMENT "midi-name" [] (show_PCDATA x)
\end{code} \begin{musicxml} MIDI 1.0 bank numbers range from 1 to 16,384. \end{musicxml} \begin{code}
-- |
type Midi_Bank = PCDATA
-- |
read_Midi_Bank :: STM Result [Content i] Midi_Bank
read_Midi_Bank = do
    y <- read_ELEMENT "midi-bank" 
    read_1 read_PCDATA (childs y)
-- |
show_Midi_Bank :: Midi_Bank -> [Content ()]
show_Midi_Bank x = 
    show_ELEMENT "midi-bank" [] (show_PCDATA x)
\end{code} \begin{musicxml} MIDI 1.0 program numbers range from 1 to 128. \end{musicxml} \begin{code}
-- |
type Midi_Program = PCDATA
-- |
read_Midi_Program :: STM Result [Content i] Midi_Program
read_Midi_Program = do
    y <- read_ELEMENT "midi-program" 
    read_1 read_PCDATA (childs y)
-- |
show_Midi_Program :: Midi_Program -> [Content ()]
show_Midi_Program x = 
    show_ELEMENT "midi-program" [] (show_PCDATA x)
\end{code} \begin{musicxml} For unpitched instruments, specify a MIDI 1.0 note number ranging from 1 to 128. Usually used with MIDI banks for percussion. \end{musicxml} \begin{code}
-- |
type Midi_Unpitched = PCDATA
-- |
read_Midi_Unpitched :: STM Result [Content i] Midi_Unpitched
read_Midi_Unpitched = do
    y <- read_ELEMENT "midi-unpitched" 
    read_1 read_PCDATA (childs y)
-- |
show_Midi_Unpitched :: Midi_Unpitched -> [Content ()]
show_Midi_Unpitched x = 
    show_ELEMENT "midi-unpitched" [] (show_PCDATA x)
\end{code} \begin{musicxml} The volume value is a percentage of the maximum ranging from 0 to 100, with decimal values allowed. This corresponds to a scaling value for the MIDI 1.0 channel volume controller. \end{musicxml} \begin{code}
-- |
type Volume = PCDATA
-- |
read_Volume :: STM Result [Content i] Volume
read_Volume = do
    y <- read_ELEMENT "volume" 
    read_1 read_PCDATA (childs y)
-- |
show_Volume :: Volume -> [Content ()]
show_Volume x = 
    show_ELEMENT "volume" [] (show_PCDATA x)
\end{code} \begin{musicxml} Pan and elevation allow placing of sound in a 3-D space relative to the listener. Both are expressed in degrees ranging from -180 to 180. For pan, 0 is straight ahead, -90 is hard left, 90 is hard right, and -180 and 180 are directly behind the listener. For elevation, 0 is level with the listener, 90 is directly above, and -90 is directly below. \end{musicxml} \begin{code}
-- |
type Pan = PCDATA
-- |
read_Pan :: STM Result [Content i] Pan
read_Pan = do
    y <- read_ELEMENT "pan" 
    read_1 read_PCDATA (childs y)
-- |
show_Pan :: Pan -> [Content ()]
show_Pan x = 
    show_ELEMENT "pan" [] (show_PCDATA x)
-- |
type Elevation = PCDATA
-- |
read_Elevation :: STM Result [Content i] Elevation
read_Elevation = do
    y <- read_ELEMENT "elevation" 
    read_1 read_PCDATA (childs y)
-- |
show_Elevation :: Elevation -> [Content ()]
show_Elevation x = 
    show_ELEMENT "elevation" [] (show_PCDATA x)
\end{code}