\begin{code} -- | -- Maintainer : silva.samuel@alumni.uminho.pt -- Stability : experimental -- Portability: HaXML -- module Text.XML.MusicXML.Partwise where import Text.XML.MusicXML.Common import Text.XML.MusicXML.Identity import Text.XML.MusicXML.Score import Text.XML.HaXml.Types (Content, DocTypeDecl(..), ExternalID(..), PubidLiteral(..), SystemLiteral(..)) import Prelude (Maybe(..), Monad(..), Eq, (++)) \end{code} \begin{musicxml} The MusicXML format is designed to represent musical scores, specifically common western musical notation from the 17th century onwards. It is designed as an interchange format for notation, analysis, retrieval, and performance applications. Therefore it is intended to be sufficient, not optimal, for these applications. The MusicXML format is based on the MuseData and Humdrum formats. Humdrum explicitly represents the two-dimensional nature of musical scores by a 2-D layout notation. Since the XML format is hierarchical, we cannot do this explicitly. Instead, there are two top-level formats: partwise.dtd Represents scores by part/instrument timewise.dtd Represents scores by time/measure Thus partwise.dtd contains measures within each part, while timewise.dtd contains parts within each measure. XSLT stylesheets are provided to convert between the two formats. The partwise and timewise score DTDs represent a single movement of music. Multiple movements or other musical collections are presented using opus.dtd. An opus document contains XLinks to individual scores. Suggested use: \begin{verbatim} \end{verbatim} This DTD is made up of a series of component DTD modules, all of which are included here. \end{musicxml} \begin{code} -- | doctype :: DocTypeDecl doctype = DTD "score-partwise" (Just (PUBLIC (PubidLiteral "-//Recordare//DTD MusicXML 2.0 Partwise//EN") (SystemLiteral "http://www.musicxml.org/dtds/partwise.dtd"))) [] \end{code} \begin{musicxml} The score is the root element for the DTD. It includes the score-header entity, followed either by a series of parts with measures inside (score-partwise) or a series of measures with parts inside (score-timewise). Having distinct top-level elements for partwise and timewise scores makes it easy to ensure that an XSLT stylesheet does not try to transform a document already in the desired format. The document-attributes entity includes the version attribute and is defined in the common.mod file. In either format, the part element has an id attribute that is an IDREF back to a score-part in the part-list. Measures have a required number attribute (going from partwise to timewise, measures are grouped via the number). The implicit attribute is set to "yes" for measures where the measure number should never appear, such as pickup measures and the last half of mid-measure repeats. The value is "no" if not specified. The non-controlling attribute is intended for use in multimetric music like the Don Giovanni minuet. If set to "yes", the left barline in this measure does not coincide with the left barline of measures in other parts. The value is "no" if not specified. In partwise files, the number attribute should be the same for measures in different parts that share the same left barline. While the number attribute is often numeric, it does not have to be. Non-numeric values are typically used together with the implicit or non-controlling attributes being set to "yes". For a pickup measure, the number attribute is typically set to "0" and the implicit attribute is typically set to "yes". Further details about measure numbering can be defined using the measure-numbering element defined in the direction.mod file Measure width is specified in tenths. These are the global tenths specified in the scaling element, not local tenths as modified by the staff-size element. \end{musicxml} \begin{code} -- * Score_Partwise -- | type Score_Partwise = (Document_Attributes, (Score_Header, [Part])) -- | read_Score_Partwise :: Eq i => StateT Result [Content i] Score_Partwise read_Score_Partwise = do y <- read_ELEMENT "score-partwise" y1 <- read_1 read_Document_Attributes (attributes y) y2 <- read_2 read_Score_Header (read_LIST1 read_Part) (childs y) return (y1,y2) -- | show_Score_Partwise :: Score_Partwise -> [Content ()] show_Score_Partwise (a,(b,c)) = show_ELEMENT "score-partwise" (show_Document_Attributes a) (show_Score_Header b ++ show_LIST1 show_Part c) -- | update_Score_Partwise :: ([Software], Encoding_Date) -> Score_Partwise -> Score_Partwise update_Score_Partwise x (a,(b,c)) = (a,(update_Score_Header x b, c)) -- | type Part = (ID, [Measure]) -- | read_Part :: Eq i => StateT Result [Content i] Part read_Part = do y <- read_ELEMENT "part" y1 <- read_1 (read_REQUIRED "id" read_ID) (attributes y) y2 <- read_1 (read_LIST1 read_Measure) (childs y) return (y1,y2) show_Part :: Part -> [Content ()] show_Part (a,b) = show_ELEMENT "part" (show_REQUIRED "id" show_ID a) (show_LIST1 show_Measure b) -- | type Measure = ((CDATA, Maybe Yes_No, Maybe Yes_No, Maybe Tenths), Music_Data) -- | read_Measure :: Eq i => StateT Result [Content i] Measure read_Measure = do y <- read_ELEMENT "measure" y1 <- read_4 (read_REQUIRED "number" read_CDATA) (read_IMPLIED "implicit" read_Yes_No) (read_IMPLIED "non-controlling" read_Yes_No) (read_IMPLIED "width" read_Tenths) (attributes y) y2 <- read_1 read_Music_Data (childs y) return (y1,y2) -- | show_Measure :: Measure -> [Content ()] show_Measure ((a,b,c,d),e) = show_ELEMENT "measure" (show_REQUIRED "number" show_CDATA a ++ show_IMPLIED "implicit" show_Yes_No b ++ show_IMPLIED "non-controlling" show_Yes_No c ++ show_IMPLIED "width" show_Tenths d) (show_Music_Data e) \end{code}