\begin{code} -- | -- Maintainer : silva.samuel@alumni.uminho.pt -- Stability : experimental -- Portability: HaXML -- module Text.XML.MusicXML.Barline where import Text.XML.MusicXML.Common import Text.XML.HaXml.Types (Content) import Prelude (Maybe, Show, Eq, Monad(..), String, (++)) \end{code} \begin{musicxml} If a barline is other than a normal single barline, it should be represented by a barline element that describes it. This includes information about repeats and multiple endings, as well as line style. Barline data is on the same level as the other musical data in a score - a child of a measure in a partwise score, or a part in a timewise score. This allows for barlines within measures, as in dotted barlines that subdivide measures in complex meters. The two fermata elements allow for fermatas on both sides of the barline (the lower one inverted). Barlines have a location attribute to make it easier to process barlines independently of the other musical data in a score. It is often easier to set up measures separately from entering notes. The location attribute must match where the barline element occurs within the rest of the musical data in the score. If location is left, it should be the first element in the measure, aside from the print, bookmark, and link elements. If location is right, it should be the last element, again with the possible exception of the print, bookmark, and link elements. If no location is specified, the right barline is the default. The segno, coda, and divisions attributes work the same way as in the sound element defined in the direction.mod file. They are used for playback when barline elements contain segno or coda child elements. \end{musicxml} \begin{code} -- * Barline -- | type Barline = ((Barline_, Maybe CDATA, Maybe CDATA, Maybe CDATA), (Maybe Bar_Style, Editorial, Maybe Wavy_Line, Maybe Segno, Maybe Coda, Maybe (Fermata, Maybe Fermata), Maybe Ending, Maybe Repeat)) -- | read_Barline :: Eq i => STM Result [Content i] Barline read_Barline = do y <- read_ELEMENT "barline" y1 <- read_4 (read_DEFAULT "location" read_Barline_ Barline_1) (read_IMPLIED "segno" read_CDATA) (read_IMPLIED "coda" read_CDATA) (read_IMPLIED "divisions" read_CDATA) (attributes y) y2 <- read_8 (read_MAYBE read_Bar_Style) read_Editorial (read_MAYBE read_Wavy_Line) (read_MAYBE read_Segno) (read_MAYBE read_Coda) (read_MAYBE read_Barline_aux1) (read_MAYBE read_Ending) (read_MAYBE read_Repeat) (childs y) return (y1,y2) -- | show_Barline :: Barline -> [Content ()] show_Barline ((a,b,c,d),(e,f,g,h,i,j,k,l)) = show_ELEMENT "barline" (show_DEFAULT "location" show_Barline_ a ++ show_IMPLIED "segno" show_CDATA b ++ show_IMPLIED "coda" show_CDATA c ++ show_IMPLIED "divisions" show_CDATA d) (show_MAYBE show_Bar_Style e ++ show_Editorial f ++ show_MAYBE show_Wavy_Line g ++ show_MAYBE show_Segno h ++ show_MAYBE show_Coda i ++ show_MAYBE show_Barline_aux1 j ++ show_MAYBE show_Ending k ++ show_MAYBE show_Repeat l) -- | read_Barline_aux1 :: STM Result [Content i] (Fermata, Maybe Fermata) read_Barline_aux1 = do y1 <- read_Fermata y2 <- read_MAYBE read_Fermata return (y1,y2) -- | show_Barline_aux1 :: (Fermata, Maybe Fermata) -> [Content ()] show_Barline_aux1 (a,b) = show_Fermata a ++ show_MAYBE show_Fermata b -- | data Barline_ = Barline_1 | Barline_2 | Barline_3 deriving (Eq, Show) -- | read_Barline_ :: Prelude.String -> Result Barline_ read_Barline_ "right" = return Barline_1 read_Barline_ "left" = return Barline_2 read_Barline_ "middle" = return Barline_3 read_Barline_ x = fail x -- | show_Barline_ :: Barline_ -> Prelude.String show_Barline_ Barline_1 = "right" show_Barline_ Barline_2 = "left" show_Barline_ Barline_3 = "middle" \end{code} \begin{musicxml} Bar-style contains style information. Choices are regular, dotted, dashed, heavy, light-light, light-heavy, heavy-light, heavy-heavy, tick (a short stroke through the top line), short (a partial barline between the 2nd and 4th lines), and none. \end{musicxml} \begin{code} -- ** Bar_Style -- | type Bar_Style = (Color, PCDATA) -- | read_Bar_Style :: STM Result [Content i] Bar_Style read_Bar_Style = do y <- read_ELEMENT "bar-style" y1 <- read_1 read_Color (attributes y) y2 <- read_1 read_PCDATA (childs y) return (y1,y2) -- | show_Bar_Style :: Bar_Style -> [Content ()] show_Bar_Style (a,b) = show_ELEMENT "bar-style" (show_Color a) (show_PCDATA b) \end{code} \begin{musicxml} The voice entity and the wavy-line, segno, and fermata elements are defined in the common.mod file. They can apply to both notes and barlines. Endings refers to multiple (e.g. first and second) endings. Typically, the start type is associated with the left barline of the first measure in an ending. The stop and discontinue types are associated with the right barline of the last measure in an ending. Stop is used when the ending mark concludes with a downward jog, as is typical for first endings. Discontinue is used when there is no downward jog, as is typical for second endings that do not conclude a piece. The length of the jog can be specified using the end-length attribute. The text-x and text-y attributes are offsets that specify where the baseline of the start of the ending text appears, relative to the start of the ending line. The number attribute reflects the numeric values of what is under the ending line. Single endings such as "1" or comma-separated multiple endings such as "1, 2" may be used. The ending element text is used when the text displayed in the ending is different than what appears in the number attribute. The print-object element is used to indicate when an ending is present but not printed, as is often the case for many parts in a full score. \end{musicxml} \begin{code} -- ** Ending -- | type Ending = ((CDATA, Ending_, Print_Object, Print_Style, Maybe Tenths, Maybe Tenths, Maybe Tenths), PCDATA) -- | read_Ending :: Eq i => STM Result [Content i] Ending read_Ending = do y <- read_ELEMENT "ending" y1 <- read_7 (read_REQUIRED "number" read_CDATA) (read_REQUIRED "type" read_Ending_) read_Print_Object read_Print_Style (read_IMPLIED "end-length" read_Tenths) (read_IMPLIED "text-x" read_Tenths) (read_IMPLIED "text-y" read_Tenths) (attributes y) y2 <- read_1 read_PCDATA (childs y) return (y1,y2) -- | show_Ending :: Ending -> [Content ()] show_Ending ((a,b,c,d,e,f,g),h) = show_ELEMENT "ending" (show_REQUIRED "number" show_CDATA a ++ show_REQUIRED "type" show_Ending_ b ++ show_Print_Object c ++ show_Print_Style d ++ show_IMPLIED "end-length" show_Tenths e ++ show_IMPLIED "text-x" show_Tenths f ++ show_IMPLIED "text-y" show_Tenths g) (show_PCDATA h) -- | data Ending_ = Ending_1 | Ending_2 | Ending_3 deriving (Eq, Show) -- | read_Ending_ :: Prelude.String -> Result Ending_ read_Ending_ "start" = return Ending_1 read_Ending_ "stop" = return Ending_2 read_Ending_ "discontinue" = return Ending_3 read_Ending_ x = fail x -- | show_Ending_ :: Ending_ -> Prelude.String show_Ending_ Ending_1 = "start" show_Ending_ Ending_2 = "stop" show_Ending_ Ending_3 = "discontinue" \end{code} \begin{musicxml} Repeat marks. The start of the repeat has a forward direction while the end of the repeat has a backward direction. Backward repeats that are not part of an ending can use the times attribute to indicate the number of times the repeated section is played. \end{musicxml} \begin{code} -- ** Repeat -- | type Repeat = ((Repeat_, Maybe CDATA), ()) -- | read_Repeat :: STM Result [Content i] Repeat read_Repeat = do y <- read_ELEMENT "repeat" y1 <- read_2 (read_REQUIRED "direction" read_Repeat_) (read_IMPLIED "times" read_CDATA) (attributes y) return (y1,()) -- | show_Repeat :: Repeat -> [Content ()] show_Repeat ((a,b),_) = show_ELEMENT "repeat" (show_REQUIRED "direction" show_Repeat_ a ++ show_IMPLIED "times" show_CDATA b) [] -- | data Repeat_ = Repeat_1 | Repeat_2 deriving (Eq, Show) -- | read_Repeat_ :: Prelude.String -> Result Repeat_ read_Repeat_ "backward" = return Repeat_1 read_Repeat_ "forward" = return Repeat_2 read_Repeat_ x = fail x -- | show_Repeat_ :: Repeat_ -> Prelude.String show_Repeat_ Repeat_1 = "backward" show_Repeat_ Repeat_2 = "forward" \end{code}