\begin{code} -- | -- Maintainer : silva.samuel@alumni.uminho.pt -- Stability : experimental -- Portability: HaXML -- module Text.XML.MusicXML.Opus where import Text.XML.MusicXML.Common import Text.XML.MusicXML.Link import Text.XML.HaXml.Types (Content, DocTypeDecl(..), ExternalID(..), PubidLiteral(..), SystemLiteral(..)) import Control.Monad (MonadPlus(..)) import Prelude (FilePath, Maybe(..), Show, Eq, Monad(..), (++), (.), map, concat) \end{code} \begin{musicxml} An opus collects MusicXML scores together into a larger entity. The individual scores could be movements in a symphony, scenes or acts in an opera, or songs in an album. The opus definition allows arbitrary nesting either via an opus (included in the document) or an opus-link (linked like scores). Future versions of the MusicXML format may expand this DTD to include reference data and other metadata related to musical scores. Suggested use: \begin{verbatim} \end{verbatim} \end{musicxml} \begin{code} -- | doctype :: DocTypeDecl doctype = DTD "opus" (Just (PUBLIC (PubidLiteral "-//Recordare//DTD MusicXML 2.0 Opus//EN") (SystemLiteral "http://www.musicxml.org/dtds/opus.dtd"))) [] -- | getFiles :: Opus -> [FilePath] getFiles (_,(_,l)) = concat (map (\ x -> getFiles_aux1 x) l) where getFiles_aux1 (Opus_1 o) = getFiles o getFiles_aux1 (Opus_2 (x,_)) = [getFiles_aux2 x] getFiles_aux1 (Opus_3 ((x,_),_)) = [getFiles_aux2 x] getFiles_aux2 (_,x,_,_,_,_,_) = x \end{code} \begin{musicxml} Opus is the document element. The document-attributes entity includes the version attribute and is defined in the common.mod file. \end{musicxml} \begin{code} -- * Opus -- | type Opus = (Document_Attributes, (Maybe Title, [Opus_])) -- | read_Opus :: Eq i => STM Result [Content i] Opus read_Opus = do y <- read_ELEMENT "opus" y1 <- read_1 read_Document_Attributes (attributes y) y2 <- read_2 (read_MAYBE read_Title) (read_LIST read_Opus_) (childs y) return (y1,y2) -- | show_Opus :: Opus -> [Content ()] show_Opus (a,(b,c)) = show_ELEMENT "opus" (show_Document_Attributes a) (show_MAYBE show_Title b ++ show_LIST show_Opus_ c) -- | data Opus_ = Opus_1 Opus | Opus_2 Opus_Link | Opus_3 Score deriving (Eq, Show) -- | read_Opus_ :: Eq i => STM Result [Content i] Opus_ read_Opus_ = (read_Opus >>= return . Opus_1) `mplus` (read_Opus_Link >>= return . Opus_2) `mplus` (read_Score >>= return . Opus_3) -- | show_Opus_ :: Opus_ -> [Content ()] show_Opus_ (Opus_1 x) = show_Opus x show_Opus_ (Opus_2 x) = show_Opus_Link x show_Opus_ (Opus_3 x) = show_Score x \end{code} \begin{musicxml} The score elements provide the links to the individual movements. The new-page attribute, added in Version 2.0, is used to indicate if the first page of the score is different than the last page of the previous score. If new-page is "yes", then a different page is used; if "no", then the same page is used. The default value is implementation-dependent. \end{musicxml} \begin{code} -- | type Score = ((Link_Attributes, Maybe Yes_No), ()) -- | read_Score :: STM Result [Content i] Score read_Score = do y <- read_ELEMENT "score" y1 <- read_2 read_Link_Attributes (read_IMPLIED "new-page" read_Yes_No) (attributes y) return (y1,()) -- | show_Score :: Score -> [Content ()] show_Score ((a,b),_) = show_ELEMENT "score" (show_Link_Attributes a ++ show_IMPLIED "new-page" show_Yes_No b) [] \end{code} \begin{musicxml} An opus-link provides a link to another opus document, allowing for multiple levels of opus collections via linking as well as nesting. \end{musicxml} \begin{code} -- | type Opus_Link = (Link_Attributes, ()) -- | read_Opus_Link :: STM Result [Content i] Opus_Link read_Opus_Link = do y <- read_ELEMENT "opus-link" y1 <- read_1 read_Link_Attributes (attributes y) return (y1,()) -- | show_Opus_Link :: Opus_Link -> [Content ()] show_Opus_Link (a,_) = show_ELEMENT "opus-link" (show_Link_Attributes a) [] \end{code} \begin{musicxml} Future versions may include metadata elements. In this version, we just include the title of the opus. \end{musicxml} \begin{code} -- | type Title = PCDATA -- | read_Title :: STM Result [Content i] Title read_Title = do y <- read_ELEMENT "title" read_1 read_PCDATA (childs y) -- | show_Title :: Title -> [Content ()] show_Title a = show_ELEMENT "title" [] (show_PCDATA a) \end{code}