\begin{code} -- | -- Maintainer : silva.samuel@alumni.uminho.pt -- Stability : experimental -- Portability: HaXML -- module Text.XML.MusicXML.Attributes where import Text.XML.MusicXML.Common hiding (Directive, read_Directive, show_Directive) import Text.XML.HaXml.Types (Content) import Control.Monad (MonadPlus(..)) import Prelude (Maybe(..), Show, Eq, Monad(..), (.), String, (++)) \end{code} \begin{musicxml} The attributes DTD module contains the attributes element and its children, such as key and time signatures. The attributes element contains musical information that typically changes on measure boundaries. This includes key and time signatures, clefs, transpositions, and staving. \end{musicxml} \begin{code} -- * Attributes -- | type Attributes = (Editorial, Maybe Divisions, [Key], [Time], Maybe Staves, Maybe Part_Symbol, Maybe Instruments, [Clef], [Staff_Details], Maybe Transpose, [Directive], [Measure_Style]) -- | read_Attributes :: Eq i => StateT Result [Content i] Attributes read_Attributes = do y <- read_ELEMENT "attributes" read_12 read_Editorial (read_MAYBE read_Divisions) (read_LIST read_Key) (read_LIST read_Time) (read_MAYBE read_Staves) (read_MAYBE read_Part_Symbol) (read_MAYBE read_Instruments) (read_LIST read_Clef) (read_LIST read_Staff_Details) (read_MAYBE read_Transpose) (read_LIST read_Directive) (read_LIST read_Measure_Style) (childs y) -- | show_Attributes :: Attributes -> [Content ()] show_Attributes (a,b,c,d,e,f,g,h,i,j,k,l) = show_ELEMENT "attributes" [] (show_Editorial a ++ show_MAYBE show_Divisions b ++ show_LIST show_Key c ++ show_LIST show_Time d ++ show_MAYBE show_Staves e ++ show_MAYBE show_Part_Symbol f ++ show_MAYBE show_Instruments g ++ show_LIST show_Clef h ++ show_LIST show_Staff_Details i ++ show_MAYBE show_Transpose j ++ show_LIST show_Directive k ++ show_LIST show_Measure_Style l) \end{code} \begin{musicxml} Traditional key signatures are represented by the number of flats and sharps, plus an optional mode for major/ minor/mode distinctions. Negative numbers are used for flats and positive numbers for sharps, reflecting the key's placement within the circle of fifths (hence the element name). A cancel element indicates that the old key signature should be cancelled before the new one appears. This will always happen when changing to C major or A minor and need not be specified then. The cancel value matches the fifths value of the cancelled key signature (e.g., a cancel of -2 will provide an explicit cancellation for changing from B flat major to F major). The optional location attribute indicates whether the cancellation appears to the left or the right of the new key signature. It is left by default. Non-traditional key signatures can be represented using the Humdrum/Scot concept of a list of altered tones. The key-step and key-alter elements are represented the same way as the step and alter elements are in the pitch element in the note.mod file. The different element names indicate the different meaning of altering notes in a scale versus altering a sounding pitch. Valid mode values include major, minor, dorian, phrygian, lydian, mixolydian, aeolian, ionian, and locrian. The optional number attribute refers to staff numbers, from top to bottom on the system. If absent, the key signature applies to all staves in the part. The optional list of key-octave elements is used to specify in which octave each element of the key signature appears. The content specifies the octave value using the same values as the display-octave element. The number attribute is a positive integer that refers to the key signature element in left-to-right order. If the cancel attribute is set to yes, then this number refers to an element specified by the cancel element. It is no by default. \end{musicxml} \begin{code} -- ** Key -- | type Key = ((Maybe CDATA, Print_Style, Print_Object), (Key_, [Key_Octave])) -- | read_Key :: Eq i => StateT Result [Content i] Key read_Key = do y <- read_ELEMENT "key" y1 <- read_3 (read_IMPLIED "number" read_CDATA) read_Print_Style read_Print_Object (attributes y) y2 <- read_2 read_Key_ (read_LIST read_Key_Octave) (childs y) return (y1,y2) -- | show_Key :: Key -> [Content ()] show_Key ((a,b,c),(d,e)) = show_ELEMENT "key" (show_IMPLIED "number" show_CDATA a ++ show_Print_Style b ++ show_Print_Object c) (show_Key_ d ++ show_LIST show_Key_Octave e) -- | data Key_ = Key_1 (Maybe Cancel, Fifths, Maybe Mode) | Key_2 [(Key_Step, Key_Alter)] deriving (Eq, Show) -- | read_Key_ :: Eq i => StateT Result [Content i] Key_ read_Key_ = (read_Key_aux1 >>= return . Key_1) `mplus` (read_LIST read_Key_aux2 >>= return . Key_2) -- | show_Key_ :: Key_ -> [Content ()] show_Key_ (Key_1 (a,b,c)) = show_MAYBE show_Cancel a ++ show_Fifths b ++ show_MAYBE show_Mode c show_Key_ (Key_2 a) = show_LIST show_Key_aux1 a -- | read_Key_aux1 :: Eq i => StateT Result [Content i] (Maybe Cancel, Fifths, Maybe Mode) read_Key_aux1 = do y1 <- read_MAYBE read_Cancel y2 <- read_Fifths y3 <- read_MAYBE read_Mode return (y1,y2,y3) read_Key_aux2 :: Eq i => StateT Result [Content i] (Key_Step, Key_Alter) read_Key_aux2 = do y1 <- read_Key_Step y2 <- read_Key_Alter return (y1,y2) -- | show_Key_aux1 :: (Key_Step, Key_Alter) -> [Content ()] show_Key_aux1 (a,b) = show_Key_Step a ++ show_Key_Alter b -- | type Cancel = (Maybe Left_Right, PCDATA) -- | read_Cancel :: StateT Result [Content i] Cancel read_Cancel = do y <- read_ELEMENT "cancel" y1 <- read_1 (read_IMPLIED "location" read_Left_Right) (attributes y) y2 <- read_1 read_PCDATA (childs y) return (y1,y2) -- | show_Cancel :: Cancel -> [Content ()] show_Cancel (a,b) = show_ELEMENT "cancel" (show_IMPLIED "location" show_Left_Right a) (show_PCDATA b) -- | type Fifths = PCDATA -- | read_Fifths :: StateT Result [Content i] Fifths read_Fifths = do y <- read_ELEMENT "fifths" read_1 read_PCDATA (childs y) -- | show_Fifths :: Fifths -> [Content ()] show_Fifths a = show_ELEMENT "fifths" [] (show_PCDATA a) -- | type Mode = PCDATA -- | read_Mode :: StateT Result [Content i] Mode read_Mode = do y <- read_ELEMENT "mode" read_1 read_PCDATA (childs y) -- | show_Mode :: Mode -> [Content ()] show_Mode a = show_ELEMENT "mode" [] (show_PCDATA a) -- | type Key_Step = PCDATA -- | read_Key_Step :: StateT Result [Content i] Key_Step read_Key_Step = do y <- read_ELEMENT "key-step" read_1 read_PCDATA (childs y) -- | show_Key_Step :: Key_Step -> [Content ()] show_Key_Step a = show_ELEMENT "key-step" [] (show_PCDATA a) -- | type Key_Alter = PCDATA -- | read_Key_Alter :: StateT Result [Content i] Key_Alter read_Key_Alter = do y <- read_ELEMENT "key-alter" read_1 read_PCDATA (childs y) -- | show_Key_Alter :: Key_Alter -> [Content ()] show_Key_Alter a = show_ELEMENT "key-alter" [] (show_PCDATA a) -- | type Key_Octave = ((CDATA, Maybe Yes_No), PCDATA) -- | read_Key_Octave :: StateT Result [Content i] Key_Octave read_Key_Octave = do y <- read_ELEMENT "key-octave" y1 <- read_2 (read_REQUIRED "number" read_CDATA) (read_IMPLIED "cancel" read_Yes_No) (attributes y) y2 <- read_1 read_PCDATA (childs y) return (y1,y2) -- | show_Key_Octave :: Key_Octave -> [Content ()] show_Key_Octave ((a,b),c) = show_ELEMENT "key-octave" (show_REQUIRED "number" show_CDATA a ++ show_IMPLIED "cancel" show_Yes_No b) (show_PCDATA c) \end{code} \begin{musicxml} Musical notation duration is commonly represented as fractions. The divisions element indicates how many divisions per quarter note are used to indicate a note's duration. For example, if duration = 1 and divisions = 2, this is an eighth note duration. Duration and divisions are used directly for generating sound output, so they must be chosen to take tuplets into account. Using a divisions element lets us use just one number to represent a duration for each note in the score, while retaining the full power of a fractional representation. For maximum compatibility with Standard MIDI Files, the divisions value should not exceed 16383. \end{musicxml} \begin{code} -- ** Divisions -- | type Divisions = PCDATA -- | read_Divisions :: StateT Result [Content i] Divisions read_Divisions = do y <- read_ELEMENT "divisions" read_1 read_PCDATA (childs y) -- | show_Divisions :: Divisions -> [Content ()] show_Divisions a = show_ELEMENT "divisions" [] (show_PCDATA a) \end{code} \begin{musicxml} Time signatures are represented by two elements. The beats element indicates the number of beats, as found in the numerator of a time signature. The beat-type element indicates the beat unit, as found in the denominator of a time signature. The symbol attribute is used to indicate another notation beyond a fraction: the common and cut time symbols, as well as a single number with an implied denominator. Normal (a fraction) is the implied symbol type if none is specified. Multiple pairs of beat and beat-type elements are used for composite time signatures with multiple denominators, such as 2/4 + 3/8. A composite such as 3+2/8 requires only one beat/beat-type pair. A senza-misura element explicitly indicates that no time signature is present. The print-object attribute allows a time signature to be specified but not printed, as is the case for excerpts from the middle of a score. The value is "yes" if not present. The optional number attribute refers to staff numbers within the part, from top to bottom on the system. If absent, the time signature applies to all staves in the part. \end{musicxml} \begin{code} -- ** Time -- | type Time = ((Maybe CDATA, Maybe Time_A, Print_Style, Print_Object), Time_B) -- | read_Time :: Eq i => StateT Result [Content i] Time read_Time = do y <- read_ELEMENT "time" y1 <- read_4 (read_IMPLIED "number" read_CDATA) (read_IMPLIED "symbol" read_Time_A) read_Print_Style read_Print_Object (attributes y) y2 <- read_1 read_Time_B (childs y) return (y1,y2) -- | show_Time :: Time -> [Content ()] show_Time ((a,b,c,d),e) = show_ELEMENT "time" (show_IMPLIED "number" show_CDATA a ++ show_IMPLIED "symbol" show_Time_A b ++ show_Print_Style c ++ show_Print_Object d) (show_Time_B e) -- | data Time_A = Time_1 | Time_2 | Time_3 | Time_4 deriving (Eq, Show) -- | read_Time_A :: Prelude.String -> Result Time_A read_Time_A "common" = return Time_1 read_Time_A "cut" = return Time_2 read_Time_A "single-number" = return Time_3 read_Time_A "normal" = return Time_4 read_Time_A x = fail x -- | show_Time_A :: Time_A -> Prelude.String show_Time_A Time_1 = "common" show_Time_A Time_2 = "cut" show_Time_A Time_3 = "single-number" show_Time_A Time_4 = "normal" -- | data Time_B = Time_5 [(Beats, Beat_Type)] | Time_6 Senza_Misura deriving (Eq, Show) -- | read_Time_B :: Eq i => StateT Result [Content i] Time_B read_Time_B = (read_LIST1 read_Time_B_aux1 >>= return . Time_5) `mplus` (read_Senza_Misura >>= return . Time_6) -- | show_Time_B :: Time_B -> [Content ()] show_Time_B (Time_5 a) = show_LIST show_Time_B_aux1 a show_Time_B (Time_6 a) = show_Senza_Misura a -- | read_Time_B_aux1 :: StateT Result [Content i] (Beats, Beat_Type) read_Time_B_aux1 = do y1 <- read_Beats y2 <- read_Beat_Type return (y1,y2) -- | show_Time_B_aux1 :: (Beats, Beat_Type) -> [Content ()] show_Time_B_aux1 (a,b) = show_Beats a ++ show_Beat_Type b -- | type Beats = PCDATA -- | read_Beats :: StateT Result [Content i] Beats read_Beats = do y <- read_ELEMENT "beats" read_1 read_PCDATA (childs y) -- | show_Beats :: Beats -> [Content ()] show_Beats a = show_ELEMENT "beats" [] (show_PCDATA a) -- | type Beat_Type = PCDATA -- | read_Beat_Type :: StateT Result [Content i] Beat_Type read_Beat_Type = do y <- read_ELEMENT "beat-type" read_1 read_PCDATA (childs y) -- | show_Beat_Type :: Beat_Type -> [Content ()] show_Beat_Type a = show_ELEMENT "beat-type" [] (show_PCDATA a) -- | type Senza_Misura = () -- | read_Senza_Misura :: StateT Result [Content i] Senza_Misura read_Senza_Misura = do read_ELEMENT "senza-misura" >> return () -- | show_Senza_Misura :: Senza_Misura -> [Content ()] show_Senza_Misura _ = show_ELEMENT "senza-misura" [] [] \end{code} \begin{musicxml} Staves are used if there is more than one staff represented in the given part (e.g., 2 staves for typical piano parts). If absent, a value of 1 is assumed. Staves are ordered from top to bottom in a part in numerical order, with staff 1 above staff 2. \end{musicxml} \begin{code} -- ** Staves -- | type Staves = PCDATA -- | read_Staves :: StateT Result [Content i] Staves read_Staves = do y <- read_ELEMENT "staves" read_1 read_PCDATA (childs y) -- | show_Staves :: Staves -> [Content ()] show_Staves a = show_ELEMENT "staves" [] (show_PCDATA a) \end{code} \begin{musicxml} The part-symbol element indicates how a symbol for a multi-staff part is indicated in the score. Values include none, brace, line, and bracket; brace is the default. The top-staff and bottom-staff elements are used when the brace does not extend across the entire part. For example, in a 3-staff organ part, the top-staff will typically be 1 for the right hand, while the bottom-staff will typically be 2 for the left hand. Staff 3 for the pedals is usually outside the brace. \end{musicxml} \begin{code} -- ** Part_Symbol -- | type Part_Symbol = ((Maybe CDATA, Maybe CDATA, Position, Color), PCDATA) -- | read_Part_Symbol :: StateT Result [Content i] Part_Symbol read_Part_Symbol = do y <- read_ELEMENT "part-symbol" y1 <- read_4 (read_IMPLIED "top-staff" read_CDATA) (read_IMPLIED "bottom-staff" read_CDATA) read_Position read_Color (attributes y) y2 <- read_1 read_PCDATA (childs y) return (y1,y2) -- | show_Part_Symbol :: Part_Symbol -> [Content ()] show_Part_Symbol ((a,b,c,d),e) = show_ELEMENT "part-symbol" (show_IMPLIED "top-staff" show_CDATA a ++ show_IMPLIED "bottom-staff" show_CDATA b ++ show_Position c ++ show_Color d) (show_PCDATA e) \end{code} \begin{musicxml} Instruments are only used if more than one instrument is represented in the part (e.g., oboe I and II where they play together most of the time). If absent, a value of 1 is assumed. \end{musicxml} \begin{code} -- ** Instruments -- | type Instruments = PCDATA -- | read_Instruments :: StateT Result [Content i] Instruments read_Instruments = do y <- read_ELEMENT "instruments" read_1 read_PCDATA (childs y) -- | show_Instruments :: Instruments -> [Content ()] show_Instruments a = show_ELEMENT "instruments" [] (show_PCDATA a) \end{code} \begin{musicxml} Clefs are represented by the sign, line, and clef-octave-change elements. Sign values include G, F, C, percussion, TAB, and none. Line numbers are counted from the bottom of the staff. Standard values are 2 for the G sign (treble clef), 4 for the F sign (bass clef), 3 for the C sign (alto clef) and 5 for TAB (on a 6-line staff). The clef-octave-change element is used for transposing clefs (e.g., a treble clef for tenors would have a clef-octave-change value of -1). 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. Sometimes clefs are added to the staff in non-standard line positions, either to indicate cue passages, or when there are multiple clefs present simultaneously on one staff. In this situation, the additional attribute is set to "yes" and the line value is ignored. The size attribute is used for clefs where the additional attribute is "yes". It is typically used to indicate cue clefs. \end{musicxml} \begin{code} -- ** Clef -- | type Clef = ((Maybe CDATA, Maybe Yes_No, Maybe Symbol_Size, Print_Style, Print_Object), (Sign, Maybe Line, Maybe Clef_Octave_Change)) -- | read_Clef :: Eq i => StateT Result [Content i] Clef read_Clef = do y <- read_ELEMENT "clef" y1 <- read_5 (read_IMPLIED "number" read_CDATA) (read_IMPLIED "additional" read_Yes_No) (read_IMPLIED "size" read_Symbol_Size) read_Print_Style read_Print_Object (attributes y) y2 <- read_3 read_Sign (read_MAYBE read_Line) (read_MAYBE read_Clef_Octave_Change) (childs y) return (y1,y2) -- | show_Clef :: Clef -> [Content ()] show_Clef ((a,b,c,d,e),(f,g,h)) = show_ELEMENT "clef" (show_IMPLIED "number" show_CDATA a ++ show_IMPLIED "additional" show_Yes_No b ++ show_IMPLIED "size" show_Symbol_Size c ++ show_Print_Style d ++ show_Print_Object e) (show_Sign f ++ show_MAYBE show_Line g ++ show_MAYBE show_Clef_Octave_Change h) -- | type Sign = PCDATA -- | read_Sign :: StateT Result [Content i] Sign read_Sign = do y <- read_ELEMENT "sign" read_1 read_PCDATA (childs y) -- | show_Sign :: Sign -> [Content ()] show_Sign a = show_ELEMENT "sign" [] (show_PCDATA a) -- | type Line = PCDATA -- | read_Line :: StateT Result [Content i] Line read_Line = do y <- read_ELEMENT "line" read_1 read_PCDATA (childs y) -- | show_Line :: Line -> [Content ()] show_Line a = show_ELEMENT "line" [] (show_PCDATA a) -- | type Clef_Octave_Change = PCDATA -- | read_Clef_Octave_Change :: StateT Result [Content i] Clef_Octave_Change read_Clef_Octave_Change = do y <- read_ELEMENT "clef-octave-change" read_1 read_PCDATA (childs y) -- | show_Clef_Octave_Change :: Clef_Octave_Change -> [Content ()] show_Clef_Octave_Change a = show_ELEMENT "clef-octave-change" [] (show_PCDATA a) \end{code} \begin{musicxml} The staff-details element is used to indicate different types of staves. The staff-type element can be ossia, cue, editorial, regular, or alternate. An alternate staff indicates one that shares the same musical data as the prior staff, but displayed differently (e.g., treble and bass clef, standard notation and tab). The staff-lines element specifies the number of lines for non 5-line staffs. The staff-tuning and capo elements are used to specify tuning when using tablature notation. The optional number attribute specifies the staff number from top to bottom on the system, as with clef. The optional show-frets attribute indicates whether to show tablature frets as numbers (0, 1, 2) or letters (a, b, c). The default choice is numbers. The print-object attribute is used to indicate when a staff is not printed in a part, usually in large scores where empty parts are omitted. It is yes by default. If print-spacing is yes while print-object is no, the score is printed in cutaway format where vertical space is left for the empty part. \end{musicxml} \begin{code} -- ** Staff_Details -- | type Staff_Details = ((Maybe CDATA, Maybe Staff_Details_, Print_Object, Print_Spacing), (Maybe Staff_Type, Maybe Staff_Lines, [Staff_Tuning], Maybe Capo, Maybe Staff_Size)) -- | read_Staff_Details :: Eq i => StateT Result [Content i] Staff_Details read_Staff_Details = do y <- read_ELEMENT "staff-details" y1 <- read_4 (read_IMPLIED "number" read_CDATA) (read_IMPLIED "show-frets" read_Staff_Details_) read_Print_Object read_Print_Spacing (attributes y) y2 <- read_5 (read_MAYBE read_Staff_Type) (read_MAYBE read_Staff_Lines) (read_LIST read_Staff_Tuning) (read_MAYBE read_Capo) (read_MAYBE read_Staff_Size) (childs y) return (y1,y2) -- | show_Staff_Details :: Staff_Details -> [Content ()] show_Staff_Details ((a,b,c,d),(e,f,g,h,i)) = show_ELEMENT "staff-details" (show_IMPLIED "number" show_CDATA a ++ show_IMPLIED "show-frets" show_Staff_Details_ b ++ show_Print_Object c ++ show_Print_Spacing d) (show_MAYBE show_Staff_Type e ++ show_MAYBE show_Staff_Lines f ++ show_LIST show_Staff_Tuning g ++ show_MAYBE show_Capo h ++ show_MAYBE show_Staff_Size i) -- | data Staff_Details_ = Staff_Details_1 | Staff_Details_2 deriving (Eq, Show) -- | read_Staff_Details_ :: Prelude.String -> Result Staff_Details_ read_Staff_Details_ "numbers" = return Staff_Details_1 read_Staff_Details_ "letters" = return Staff_Details_2 read_Staff_Details_ x = fail x -- | show_Staff_Details_ :: Staff_Details_ -> Prelude.String show_Staff_Details_ Staff_Details_1 = "numbers" show_Staff_Details_ Staff_Details_2 = "letters" -- | type Staff_Type = PCDATA -- | read_Staff_Type :: StateT Result [Content i] Staff_Type read_Staff_Type = do y <- read_ELEMENT "staff-type" read_1 read_PCDATA (childs y) -- | show_Staff_Type :: Staff_Type -> [Content ()] show_Staff_Type a = show_ELEMENT "staff-type" [] (show_PCDATA a) -- | type Staff_Lines = PCDATA -- | read_Staff_Lines :: StateT Result [Content i] Staff_Lines read_Staff_Lines = do y <- read_ELEMENT "staff-lines" read_1 read_PCDATA (childs y) -- | show_Staff_Lines :: Staff_Lines -> [Content ()] show_Staff_Lines a = show_ELEMENT "staff-lines" [] (show_PCDATA a) \end{code} \begin{musicxml} The tuning-step, tuning-alter, and tuning-octave elements are defined in the common.mod file. Staff lines are numbered from bottom to top. \end{musicxml} \begin{code} -- | type Staff_Tuning = (CDATA, (Tuning_Step, Maybe Tuning_Alter, Tuning_Octave)) -- | read_Staff_Tuning :: Eq i => StateT Result [Content i] Staff_Tuning read_Staff_Tuning = do y <- read_ELEMENT "staff-tuning" y1 <- read_1 (read_REQUIRED "line" read_CDATA) (attributes y) y2 <- read_3 read_Tuning_Step (read_MAYBE read_Tuning_Alter) read_Tuning_Octave (childs y) return (y1,y2) -- | show_Staff_Tuning :: Staff_Tuning -> [Content ()] show_Staff_Tuning (a,(b,c,d)) = show_ELEMENT "staff-tuning" (show_REQUIRED "line" show_CDATA a) (show_Tuning_Step b ++ show_MAYBE show_Tuning_Alter c ++ show_Tuning_Octave d) \end{code} \begin{musicxml} The capo element indicates at which fret a capo should be placed on a fretted instrument. This changes the open tuning of the strings specified by staff-tuning by the specified number of half-steps. \end{musicxml} \begin{code} -- | type Capo = PCDATA -- | read_Capo :: StateT Result [Content i] Capo read_Capo = do y <- read_ELEMENT "capo" read_1 read_PCDATA (childs y) -- | show_Capo :: Capo -> [Content ()] show_Capo a = show_ELEMENT "capo" [] (show_PCDATA a) \end{code} \begin{musicxml} The staff-size element indicates how large a staff space is on this staff, expressed as a percentage of the work's default scaling. Values less than 100 make the staff space smaller while values over 100 make the staff space larger. A staff-type of cue, ossia, or editorial implies a staff-size of less than 100, but the exact value is implementation-dependent unless specified here. Staff size affects staff height only, not the relationship of the staff to the left and right margins. \end{musicxml} \begin{code} -- | type Staff_Size = PCDATA -- | read_Staff_Size :: StateT Result [Content i] Staff_Size read_Staff_Size = do y <- read_ELEMENT "staff-size" read_1 read_PCDATA (childs y) -- | show_Staff_Size :: Staff_Size -> [Content ()] show_Staff_Size a = show_ELEMENT "staff-size" [] (show_PCDATA a) \end{code} \begin{musicxml} If the part is being encoded for a transposing instrument in written vs. concert pitch, the transposition must be encoded in the transpose element. The transpose element represents what must be added to the written pitch to get the correct sounding pitch. The transposition is represented by chromatic steps (required) and three optional elements: diatonic pitch steps, octave changes, and doubling an octave down. The chromatic and octave-change elements are numeric values added to the encoded pitch data to create the sounding pitch. The diatonic element is also numeric and allows for correct spelling of enharmonic transpositions. \end{musicxml} \begin{code} -- ** Transpose -- | type Transpose = (Maybe Diatonic, Chromatic, Maybe Octave_Change, Maybe Double) -- | read_Transpose :: Eq i => StateT Result [Content i] Transpose read_Transpose = do y <- read_ELEMENT "transpose" read_4 (read_MAYBE read_Diatonic) read_Chromatic (read_MAYBE read_Octave_Change) (read_MAYBE read_Double) (childs y) -- | show_Transpose :: Transpose -> [Content ()] show_Transpose (a,b,c,d) = show_ELEMENT "transpose" [] (show_MAYBE show_Diatonic a ++ show_Chromatic b ++ show_MAYBE show_Octave_Change c ++ show_MAYBE show_Double d) -- | type Diatonic = PCDATA -- | read_Diatonic :: StateT Result [Content i] Diatonic read_Diatonic = do y <- read_ELEMENT "diatonic" read_1 read_PCDATA (childs y) -- | show_Diatonic :: Diatonic -> [Content ()] show_Diatonic a = show_ELEMENT "diatonic" [] (show_PCDATA a) -- | type Chromatic = PCDATA -- | read_Chromatic :: StateT Result [Content i] Chromatic read_Chromatic = do y <- read_ELEMENT "chromatic" read_1 read_PCDATA (childs y) -- | show_Chromatic :: Chromatic -> [Content ()] show_Chromatic a = show_ELEMENT "chromatic" [] (show_PCDATA a) -- | type Octave_Change = PCDATA -- | read_Octave_Change :: StateT Result [Content i] Octave_Change read_Octave_Change = do y <- read_ELEMENT "octave-change" read_1 read_PCDATA (childs y) -- | show_Octave_Change :: Octave_Change -> [Content ()] show_Octave_Change a = show_ELEMENT "octave-change" [] (show_PCDATA a) -- | type Double = () -- | read_Double :: StateT Result [Content i] Double read_Double = read_ELEMENT "double" >> return () -- | show_Double :: Double -> [Content ()] show_Double _ = show_ELEMENT "double" [] [] \end{code} \begin{musicxml} Directives are like directions, but can be grouped together with attributes for convenience. This is typically used for tempo markings at the beginning of a piece of music. This element has been deprecated in Version 2.0 in favor of the directive attribute for direction elements. Language names come from ISO 639, with optional country subcodes from ISO 3166. \end{musicxml} \begin{code} -- ** Directive -- | type Directive = ((Print_Style, Maybe CDATA), CDATA) -- | read_Directive :: StateT Result [Content i] Directive read_Directive = do y <- read_ELEMENT "directive" y1 <- read_2 read_Print_Style (read_IMPLIED "xml:lang" read_CDATA) (attributes y) y2 <- read_1 read_PCDATA (childs y) return (y1,y2) -- | show_Directive :: Directive -> [Content ()] show_Directive ((a,b),c) = show_ELEMENT "directive" (show_Print_Style a ++ show_IMPLIED "xml:lang" show_CDATA b) (show_PCDATA c) \end{code} \begin{musicxml} A measure-style indicates a special way to print partial to multiple measures within a part. This includes multiple rests over several measures, repeats of beats, single, or multiple measures, and use of slash notation. The multiple-rest and measure-repeat symbols indicate the number of measures covered in the element content. The beat-repeat and slash elements can cover partial measures. All but the multiple-rest element use a type attribute to indicate starting and stopping the use of the style. The optional number attribute specifies the staff number from top to bottom on the system, as with clef. \end{musicxml} \begin{code} -- ** Measure_Style -- | type Measure_Style = ((Maybe CDATA, Font, Color), Measure_Style_) -- | read_Measure_Style :: Eq i => StateT Result [Content i] Measure_Style read_Measure_Style = do y <- read_ELEMENT "measure-style" y1 <- read_3 (read_IMPLIED "number" read_CDATA) read_Font read_Color (attributes y) y2 <- read_1 read_Measure_Style_ (childs y) return (y1,y2) -- | show_Measure_Style :: Measure_Style -> [Content ()] show_Measure_Style ((a,b,c),d) = show_ELEMENT "measure-style" (show_IMPLIED "number" show_CDATA a ++ show_Font b ++ show_Color c) (show_Measure_Style_ d) -- | data Measure_Style_ = Measure_Style_1 Multiple_Rest | Measure_Style_2 Measure_Repeat | Measure_Style_3 Beat_Repeat | Measure_Style_4 Slash deriving (Eq, Show) -- | read_Measure_Style_ :: Eq i => StateT Result [Content i] Measure_Style_ read_Measure_Style_ = (read_Multiple_Rest >>= return . Measure_Style_1) `mplus` (read_Measure_Repeat >>= return . Measure_Style_2) `mplus` (read_Beat_Repeat >>= return . Measure_Style_3) `mplus` (read_Slash >>= return . Measure_Style_4) -- | show_Measure_Style_ :: Measure_Style_ -> [Content ()] show_Measure_Style_ (Measure_Style_1 a) = show_Multiple_Rest a show_Measure_Style_ (Measure_Style_2 a) = show_Measure_Repeat a show_Measure_Style_ (Measure_Style_3 a) = show_Beat_Repeat a show_Measure_Style_ (Measure_Style_4 a) = show_Slash a \end{code} \begin{musicxml} The slash-type and slash-dot elements are optional children of the beat-repeat and slash elements. They have the same values as the type and dot elements, and define what the beat is for the display of repetition marks. If not present, the beat is based on the current time signature. \end{musicxml} \begin{code} -- | type Slash_Type = PCDATA -- | read_Slash_Type :: StateT Result [Content i] Slash_Type read_Slash_Type = do y <- read_ELEMENT "slash-type" read_1 read_PCDATA (childs y) -- | show_Slash_Type :: Slash_Type -> [Content ()] show_Slash_Type a = show_ELEMENT "slash-type" [] (show_PCDATA a) -- | type Slash_Dot = () -- | read_Slash_Dot :: StateT Result [Content i] Slash_Dot read_Slash_Dot = read_ELEMENT "slash-dot" >> return () -- | show_Slash_Dot :: Slash_Dot -> [Content ()] show_Slash_Dot _ = show_ELEMENT "slash-dot" [] [] \end{code} \begin{musicxml} The text of the multiple-rest element indicates the number of measures in the multiple rest. Multiple rests may use the 1-bar / 2-bar / 4-bar rest symbols, or a single shape. The use-symbols attribute indicates which to use; it is no if not specified. \end{musicxml} \begin{code} -- | type Multiple_Rest = (Maybe Yes_No, PCDATA) -- | read_Multiple_Rest :: StateT Result [Content i] Multiple_Rest read_Multiple_Rest = do y <- read_ELEMENT "multiple-rest" y1 <- read_1 (read_IMPLIED "use-symbols" read_Yes_No) (attributes y) y2 <- read_1 read_PCDATA (childs y) return (y1,y2) -- | show_Multiple_Rest :: Multiple_Rest -> [Content ()] show_Multiple_Rest (a,b) = show_ELEMENT "multiple-rest" (show_IMPLIED "use-symbols" show_Yes_No a) (show_PCDATA b) \end{code} \begin{musicxml} The measure-repeat and beat-repeat element specify a notation style for repetitions. The actual music being repeated needs to be repeated within the MusicXML file. These elements specify the notation that indicates the repeat. The measure-repeat element is used for both single and multiple measure repeats. The text of the element indicates the number of measures to be repeated in a single pattern. The slashes attribute specifies the number of slashes to use in the repeat sign. It is 1 if not specified. Both the start and the stop of the measure-repeat must be specified. \end{musicxml} \begin{code} -- | type Measure_Repeat = ((Start_Stop, Maybe CDATA), PCDATA) -- | read_Measure_Repeat :: StateT Result [Content i] Measure_Repeat read_Measure_Repeat = do y <- read_ELEMENT "measure-repeat" y1 <- read_2 (read_REQUIRED "type" read_Start_Stop) (read_IMPLIED "slashes" read_CDATA) (attributes y) y2 <- read_1 read_PCDATA (childs y) return (y1,y2) -- | show_Measure_Repeat :: Measure_Repeat -> [Content ()] show_Measure_Repeat ((a,b),c) = show_ELEMENT "measure-repeat" (show_REQUIRED "type" show_Start_Stop a ++ show_IMPLIED "slashes" show_CDATA b) (show_PCDATA c) \end{code} \begin{musicxml} The beat-repeat element is used to indicate that a single beat (but possibly many notes) is repeated. Both the start and stop of the beat being repeated should be specified. The slashes attribute specifies the number of slashes to use in the symbol. The use-dots attribute indicates whether or not to use dots as well (for instance, with mixed rhythm patterns). By default, the value for slashes is 1 and the value for use-dots is no. \end{musicxml} \begin{code} -- | type Beat_Repeat = ((Start_Stop, Maybe CDATA, Maybe Yes_No), Maybe (Slash_Type, [Slash_Dot])) -- | read_Beat_Repeat :: Eq i => StateT Result [Content i] Beat_Repeat read_Beat_Repeat = do y <- read_ELEMENT "beat-repeat" y1 <- read_3 (read_REQUIRED "type" read_Start_Stop) (read_IMPLIED "slashes" read_CDATA) (read_IMPLIED "use-dots" read_Yes_No) (attributes y) y2 <- read_1 (read_MAYBE read_Beat_Repeat_aux1) (childs y) return (y1,y2) -- | show_Beat_Repeat :: Beat_Repeat -> [Content ()] show_Beat_Repeat ((a,b,c),d) = show_ELEMENT "beat-repeat" (show_REQUIRED "type" show_Start_Stop a ++ show_IMPLIED "slashes" show_CDATA b ++ show_IMPLIED "use-dots" show_Yes_No c) (show_MAYBE show_Beat_Repeat_aux1 d) -- | read_Beat_Repeat_aux1 :: Eq i => StateT Result [Content i] (Slash_Type, [Slash_Dot]) read_Beat_Repeat_aux1 = do y1 <- read_Slash_Type y2 <- read_LIST read_Slash_Dot return (y1,y2) -- | show_Beat_Repeat_aux1 :: (Slash_Type, [Slash_Dot]) -> [Content ()] show_Beat_Repeat_aux1 (a,b) = show_Slash_Type a ++ show_LIST show_Slash_Dot b \end{code} \begin{musicxml} The slash element is used to indicate that slash notation is to be used. If the slash is on every beat, use-stems is no (the default). To indicate rhythms but not pitches, use-stems is set to yes. The type attribute indicates whether this is the start or stop of a slash notation style. The use-dots attribute works as for the beat-repeat element, and only has effect if use-stems is no. \end{musicxml} \begin{code} -- | type Slash = ((Start_Stop, Maybe Yes_No, Maybe Yes_No), Maybe (Slash_Type, [Slash_Dot])) -- | read_Slash :: Eq i => StateT Result [Content i] Slash read_Slash = do y <- read_ELEMENT "slash" y1 <- read_3 (read_REQUIRED "type" read_Start_Stop) (read_IMPLIED "use-dots" read_Yes_No) (read_IMPLIED "use-stems" read_Yes_No) (attributes y) y2 <- read_1 (read_MAYBE read_Slash_aux1) (childs y) return (y1,y2) -- | show_Slash :: Slash -> [Content ()] show_Slash ((a,b,c),d) = show_ELEMENT "slash" (show_REQUIRED "type" show_Start_Stop a ++ show_IMPLIED "use-dots" show_Yes_No b ++ show_IMPLIED "use-stems" show_Yes_No c) (show_MAYBE show_Slash_aux1 d) -- | read_Slash_aux1 :: Eq i => StateT Result [Content i] (Slash_Type, [Slash_Dot]) read_Slash_aux1 = do y1 <- read_Slash_Type y2 <- read_LIST read_Slash_Dot return (y1,y2) -- | show_Slash_aux1 :: (Slash_Type, [Slash_Dot]) -> [Content ()] show_Slash_aux1 (a,b) = show_Slash_Type a ++ show_LIST show_Slash_Dot b \end{code}