\begin{code}
-- |  
-- Maintainer : silva.samuel@alumni.uminho.pt
-- Stability  : experimental
-- Portability: HaXML
-- 
module Text.XML.MusicXML.Layout where
import Text.XML.MusicXML.Common hiding (Tenths, read_Tenths, show_Tenths)
import Text.XML.HaXml.Types (Content)
import Prelude (Maybe(..), Show, Eq, String, Monad(..),(++))
\end{code} \begin{musicxml} Version 1.1 of the MusicXML format added layout information for pages, systems, staffs, and measures. These layout elements joined the print and sound elements in providing formatting data as elements rather than attributes. Everything is measured in tenths of staff space. Tenths are then scaled to millimeters within the scaling element, used in the defaults element at the start of a score. Individual staves can apply a scaling factor to adjust staff size. When a MusicXML element or attribute refers to tenths, it means the global tenths defined by the scaling element, not the local tenths as adjusted by the staff-size element. Margins, page sizes, and distances are all measured in tenths to keep MusicXML data in a consistent coordinate system as much as possible. The translation to absolute units is done in the scaling element, which specifies how many millimeters are equal to how many tenths. For a staff height of 7 mm, millimeters would be set to 7 while tenths is set to 40. The ability to set a formula rather than a single scaling factor helps avoid roundoff errors. \end{musicxml} \begin{code}
-- |
type Scaling = (Millimeters, Tenths)
-- |
read_Scaling :: Eq i => STM Result [Content i] Scaling
read_Scaling = do
    y <- read_ELEMENT "scaling"
    read_2 read_Millimeters read_Tenths (childs y)
-- |
show_Scaling :: Scaling -> [Content ()]
show_Scaling (a,b) = 
    show_ELEMENT "scaling" [] (show_Millimeters a ++ show_Tenths b)
-- |
type Millimeters = PCDATA
-- |
read_Millimeters :: Eq i => STM Result [Content i] Millimeters
read_Millimeters = do
    y <- read_ELEMENT "millimeters"
    read_1 read_PCDATA (childs y)
-- |
show_Millimeters :: Millimeters -> [Content ()]
show_Millimeters a = show_ELEMENT "millimeters" [] (show_PCDATA a)
-- |
type Tenths = Layout_Tenths
-- |
read_Tenths :: Eq i => STM Result [Content i] Tenths
read_Tenths = do
    y <- read_ELEMENT "tenths"
    read_1 read_Layout_Tenths (childs y)
-- |
show_Tenths :: Tenths -> [Content ()]
show_Tenths a = show_ELEMENT "tenths" [] (show_Layout_Tenths a)
\end{code} \begin{musicxml} Margin elements are included within many of the larger layout elements. \end{musicxml} \begin{code}
-- |
type Left_Margin = Layout_Tenths
-- |
read_Left_Margin :: STM Result [Content i] Left_Margin
read_Left_Margin = do
    y <- read_ELEMENT "left-margin"
    read_1 read_Layout_Tenths (childs y)
-- |
show_Left_Margin :: Left_Margin -> [Content ()]
show_Left_Margin a = show_ELEMENT "left-margin" [] (show_Layout_Tenths a)
-- |
type Right_Margin = Layout_Tenths
-- |
read_Right_Margin :: STM Result [Content i] Right_Margin
read_Right_Margin = do
    y <- read_ELEMENT "right-margin"
    read_1 read_Layout_Tenths (childs y)
-- |
show_Right_Margin :: Right_Margin -> [Content ()]
show_Right_Margin a = show_ELEMENT "right-margin" [] (show_Layout_Tenths a)
-- |
type Top_Margin = Layout_Tenths
-- |
read_Top_Margin :: STM Result [Content i] Top_Margin
read_Top_Margin = do
    y <- read_ELEMENT "top-margin"
    read_1 read_Layout_Tenths (childs y)
-- |
show_Top_Margin :: Top_Margin -> [Content ()]
show_Top_Margin a = show_ELEMENT "top-margin" [] (show_Layout_Tenths a)
-- |
type Bottom_Margin = Layout_Tenths
-- |
read_Bottom_Margin :: STM Result [Content i] Bottom_Margin
read_Bottom_Margin = do
    y <- read_ELEMENT "bottom-margin"
    read_1 read_Layout_Tenths (childs y)
-- |
show_Bottom_Margin :: Bottom_Margin -> [Content ()]
show_Bottom_Margin a = show_ELEMENT "bottom-margin" [] (show_Layout_Tenths a)
\end{code} \begin{musicxml} Page layout can be defined both in score-wide defaults and in the print element. Page margins are specified either for both even and odd pages, or via separate odd and even page number values. The type is not needed when used as part of a print element. If omitted when used in the defaults element, "both" is the default. \end{musicxml} \begin{code}
-- |
type Page_Layout = (Maybe (Page_Height, Page_Width), 
    Maybe (Page_Margins, Maybe Page_Margins))
-- |
read_Page_Layout :: Eq i => STM Result [Content i] Page_Layout
read_Page_Layout = do
    y <- read_ELEMENT "page-layout"
    read_2 (read_MAYBE read_Page_Layout_aux1) 
           (read_MAYBE read_Page_Layout_aux2) (childs y)
-- | 
show_Page_Layout :: Page_Layout -> [Content ()]
show_Page_Layout (a,b) = 
    show_ELEMENT "page-layout" [] (show_MAYBE show_Page_Layout_aux1 a ++ 
                                   show_MAYBE show_Page_Layout_aux2 b)
-- |
read_Page_Layout_aux1 :: Eq i => STM Result [Content i] (Page_Height, Page_Width)
read_Page_Layout_aux1 = do
    y1 <- read_Page_Height
    y2 <- read_Page_Width
    return (y1,y2)
-- |
show_Page_Layout_aux1 :: (Page_Height, Page_Width) -> [Content ()]
show_Page_Layout_aux1 (a,b) = show_Page_Height a ++ show_Page_Width b
-- |
read_Page_Layout_aux2 :: Eq i => 
    STM Result [Content i] (Page_Margins, Maybe Page_Margins)
read_Page_Layout_aux2 = do
    y1 <- read_Page_Margins
    y2 <- read_MAYBE read_Page_Margins
    return (y1,y2)
-- |
show_Page_Layout_aux2 :: (Page_Margins, Maybe Page_Margins) -> [Content ()]
show_Page_Layout_aux2 (a,b) = 
    show_Page_Margins a ++ show_MAYBE show_Page_Margins b
-- |
type Page_Height = Layout_Tenths 
-- |
read_Page_Height :: Eq i => STM Result [Content i] Page_Height
read_Page_Height = do
    y <- read_ELEMENT "page-height"
    read_1 read_Layout_Tenths (childs y)
-- |
show_Page_Height :: Page_Height -> [Content ()]
show_Page_Height a = show_ELEMENT "page-height" [] (show_Layout_Tenths a)
-- |
type Page_Width = Layout_Tenths
-- |
read_Page_Width :: Eq i => STM Result [Content i] Page_Width
read_Page_Width = do
    y <- read_ELEMENT "page-width"
    read_1 read_Layout_Tenths (childs y)
-- |
show_Page_Width :: Page_Width -> [Content ()]
show_Page_Width a = show_ELEMENT "page-width" [] (show_Layout_Tenths a)
-- |
type Page_Margins = (Maybe Page_Margins_,
    (Left_Margin, Right_Margin, Top_Margin, Bottom_Margin))
-- |
read_Page_Margins :: Eq i => STM Result [Content i] Page_Margins
read_Page_Margins = do
    y <- read_ELEMENT "page-margins"
    y1 <- read_1 (read_IMPLIED "type" read_Page_Margins_) (attributes y)
    y2 <- read_4 read_Left_Margin read_Right_Margin 
                 read_Top_Margin read_Bottom_Margin (childs y)
    return (y1,y2)
-- |
show_Page_Margins :: Page_Margins -> [Content ()]
show_Page_Margins (a,(b,c,d,e)) = 
    show_ELEMENT "page-margins" (show_IMPLIED "type" show_Page_Margins_ a) 
                                (show_Left_Margin b ++ show_Right_Margin c ++
                                 show_Top_Margin d ++ show_Bottom_Margin e)
-- |
data Page_Margins_ = Page_Margins_1 | Page_Margins_2 | Page_Margins_3
                     deriving (Eq, Show)
-- |
read_Page_Margins_ :: Prelude.String -> Result Page_Margins_
read_Page_Margins_ "odd"  = return Page_Margins_1 
read_Page_Margins_ "even" = return Page_Margins_2 
read_Page_Margins_ "both" = return Page_Margins_3 
read_Page_Margins_ x = fail x
-- |
show_Page_Margins_ :: Page_Margins_ -> Prelude.String
show_Page_Margins_ Page_Margins_1 = "odd"
show_Page_Margins_ Page_Margins_2 = "even"
show_Page_Margins_ Page_Margins_3 = "both"
\end{code} \begin{musicxml} System layout includes left and right margins and the vertical distance from the previous system. Margins are relative to the page margins. Positive values indent and negative values reduce the margin size. The system distance is measured from the bottom line of the previous system to the top line of the current system. It is ignored for the first system on a page. The top system distance is measured from the page's top margin to the top line of the first system. It is ignored for all but the first system on a page. Sometimes the sum of measure widths in a system may not equal the system width specified by the layout elements due to roundoff or other errors. The behavior when reading MusicXML files in these cases is application-dependent. For instance, applications may find that the system layout data is more reliable than the sum of the measure widths, and adjust the measure widths accordingly. \end{musicxml} \begin{code}
-- |
type System_Layout = (Maybe System_Margins, 
    Maybe System_Distance, Maybe Top_System_Distance)
-- |
read_System_Layout :: STM Result [Content i] System_Layout
read_System_Layout = do 
    y <- read_ELEMENT "system-layout" 
    read_3 (read_MAYBE read_System_Margins)
           (read_MAYBE read_System_Distance)
           (read_MAYBE read_Top_System_Distance)
           (childs y)
-- |
show_System_Layout :: System_Layout -> [Content ()]
show_System_Layout (a,b,c) = 
    show_ELEMENT "system-layout" [] 
        (show_MAYBE show_System_Margins a ++ 
         show_MAYBE show_System_Distance b ++
         show_MAYBE show_Top_System_Distance c)
-- |
type System_Margins = (Left_Margin, Right_Margin)
-- |
read_System_Margins :: STM Result [Content i] System_Margins
read_System_Margins = do
    y <- read_ELEMENT "system-margins"
    read_2 read_Left_Margin read_Right_Margin (childs y)
-- |
show_System_Margins :: System_Margins -> [Content ()]
show_System_Margins (a,b) = 
    show_ELEMENT "system-margins" [] 
        (show_Left_Margin a ++ show_Right_Margin b)
-- |
type System_Distance = Layout_Tenths
-- |
read_System_Distance :: STM Result [Content i] System_Distance
read_System_Distance = do
    y <- read_ELEMENT "system-distance"
    read_1 read_Layout_Tenths (childs y)
-- |
show_System_Distance :: System_Distance -> [Content ()]
show_System_Distance a = 
    show_ELEMENT "system-distance" [] (show_Layout_Tenths a)
-- |
type Top_System_Distance = Layout_Tenths
-- |
read_Top_System_Distance :: STM Result [Content i] Top_System_Distance
read_Top_System_Distance = do
    y <- read_ELEMENT "top-system-distance"
    read_1 read_Layout_Tenths (childs y)
-- |
show_Top_System_Distance :: Top_System_Distance -> [Content ()]
show_Top_System_Distance a = 
    show_ELEMENT "top-system-distance" [] (show_Layout_Tenths a)

\end{code} \begin{musicxml} Staff layout includes the vertical distance from the bottom line of the previous staff in this system to the top line of the staff specified by the number attribute. The optional number attribute refers to staff numbers within the part, from top to bottom on the system. A value of 1 is assumed if not present. When used in the defaults element, the values apply to all parts. This value is ignored for the first staff in a system. \end{musicxml} \begin{code}
-- |
type Staff_Layout = (Maybe CDATA, Maybe Staff_Distance)
-- |
read_Staff_Layout :: STM Result [Content i] Staff_Layout
read_Staff_Layout = do
    y <- read_ELEMENT "staff-layout"
    y1 <- read_1 (read_IMPLIED "number" read_CDATA) (attributes y)
    y2 <- read_1 (read_MAYBE read_Staff_Distance) (childs y)
    return (y1,y2)
-- |
show_Staff_Layout :: Staff_Layout -> [Content ()]
show_Staff_Layout (a,b) = 
    show_ELEMENT "staff-layout" 
        (show_IMPLIED "number" show_CDATA a) 
        (show_MAYBE show_Staff_Distance b)
-- |
type Staff_Distance = Layout_Tenths
-- |
read_Staff_Distance :: STM Result [Content i] Staff_Distance
read_Staff_Distance = do
    y <- read_ELEMENT "staff-distance"
    read_1 read_Layout_Tenths (childs y)
-- |
show_Staff_Distance :: Staff_Distance -> [Content ()]
show_Staff_Distance a = 
    show_ELEMENT "staff-distance" [] (show_Layout_Tenths a)
\end{code} \begin{musicxml} Measure layout includes the horizontal distance from the previous measure. This value is only used for systems where there is horizontal whitespace in the middle of a system, as in systems with codas. To specify the measure width, use the width attribute of the measure element. \end{musicxml} \begin{code}
-- |
type Measure_Layout = Maybe Measure_Distance
-- |
read_Measure_Layout :: Eq i => STM Result [Content i] Measure_Layout
read_Measure_Layout = do
    y <- read_ELEMENT "measure-layout"
    read_1 (read_MAYBE read_Measure_Distance) (childs y)
-- |
show_Measure_Layout :: Measure_Layout -> [Content ()]
show_Measure_Layout a = 
    show_ELEMENT "measure-layout" [] (show_MAYBE show_Measure_Distance a)
-- |
type Measure_Distance = Layout_Tenths
-- |
read_Measure_Distance :: Eq i => STM Result [Content i] Measure_Distance
read_Measure_Distance = do
    y <- read_ELEMENT "measure-distance"
    read_1 read_Layout_Tenths (childs y)
-- |
show_Measure_Distance :: Measure_Distance -> [Content ()]
show_Measure_Distance a = 
    show_ELEMENT "measure-distance" [] (show_Layout_Tenths a)
\end{code} \begin{musicxml} The appearance element controls general graphical settings for the music's final form appearance on a printed page of display. Currently this includes support for line widths and definitions for note sizes, plus an extension element for other aspects of appearance. The line-width element indicates the width of a line type in tenths. The type attribute defines what type of line is being defined. Values include beam, bracket, dashes, enclosure, ending, extend, heavy barline, leger, light barline, octave shift, pedal, slur middle, slur tip, staff, stem, tie middle, tie tip, tuplet bracket, and wedge. The text content is expressed in tenths. The note-size element indicates the percentage of the regular note size to use for notes with a cue and large size as defined in the type element. The grace type is used for notes of cue size that that include a grace element. The cue type is used for all other notes with cue size, whether defined explicitly or implicitly via a cue element. The large type is used for notes of large size. The text content represent the numeric percentage. A value of 100 would be identical to the size of a regular note as defined by the music font. The other-appearance element is used to define any graphical settings not yet in the current version of the MusicXML format. This allows extended representation, though without application interoperability. \end{musicxml} \begin{code}
-- |
type Appearance = ([Line_Width],[Note_Size],[Other_Appearance])
-- |
read_Appearance :: Eq i => STM Result [Content i] Appearance
read_Appearance = do 
    y <- read_ELEMENT "appearance"
    read_3 (read_LIST read_Line_Width) (read_LIST read_Note_Size)
           (read_LIST read_Other_Appearance) (childs y)
-- |
show_Appearance :: Appearance -> [Content ()]
show_Appearance (a,b,c) = 
    show_ELEMENT "appearance" [] (show_LIST show_Line_Width a ++
                                  show_LIST show_Note_Size b ++
                                  show_LIST show_Other_Appearance c)
-- |
type Line_Width = (CDATA, Layout_Tenths)
-- |
read_Line_Width :: STM Result [Content i] Line_Width
read_Line_Width = do
    y <- read_ELEMENT "line-width"
    y1 <- read_1 (read_REQUIRED "type" read_CDATA) (attributes y)
    y2 <- read_1 read_Layout_Tenths (childs y)
    return (y1,y2)
-- |
show_Line_Width :: Line_Width -> [Content ()]
show_Line_Width (a,b) = 
    show_ELEMENT "line-width" (show_REQUIRED "type" show_CDATA a)
                              (show_Layout_Tenths b)
-- |
type Note_Size = (Note_Size_, PCDATA)
-- |
read_Note_Size :: STM Result [Content i] Note_Size
read_Note_Size = do
    y <- read_ELEMENT "note-size"
    y1 <- read_1 (read_REQUIRED "type" read_Note_Size_) (attributes y)
    y2 <- read_1 read_PCDATA (childs y)
    return (y1,y2)
-- |
show_Note_Size :: Note_Size -> [Content ()]
show_Note_Size (a,b) = 
    show_ELEMENT "note-size" (show_REQUIRED "type" show_Note_Size_ a)
                             (show_PCDATA b)
-- |
data Note_Size_ = Note_Size_1 | Note_Size_2 | Note_Size_3
                  deriving (Eq, Show)
-- |
read_Note_Size_ :: Prelude.String -> Result Note_Size_
read_Note_Size_ "cue" = return Note_Size_1
read_Note_Size_ "grace" = return Note_Size_2
read_Note_Size_ "large" = return Note_Size_3
read_Note_Size_ x = fail x
-- |
show_Note_Size_ :: Note_Size_ -> Prelude.String
show_Note_Size_ Note_Size_1 = "cue"
show_Note_Size_ Note_Size_2 = "grace"
show_Note_Size_ Note_Size_3 = "large"
-- |
type Other_Appearance = (CDATA, PCDATA)
-- |
read_Other_Appearance :: STM Result [Content i] Other_Appearance
read_Other_Appearance = do
    y <- read_ELEMENT "other-appearance"
    y1 <- read_1 (read_REQUIRED "type" read_CDATA) (attributes y)
    y2 <- read_1 read_PCDATA (childs y)
    return (y1,y2)
-- |
show_Other_Appearance :: Other_Appearance -> [Content ()]
show_Other_Appearance (a,b) = 
    show_ELEMENT "other-appearance" (show_REQUIRED "type" show_CDATA a) 
                                    (show_PCDATA b)
\end{code}