\begin{code} -- | -- Maintainer : silva.samuel@alumni.uminho.pt -- Stability : experimental -- Portability: HaXML -- module Text.XML.MusicXML.Container where import Text.XML.MusicXML.Common import Text.XML.HaXml.Types (Content, DocTypeDecl(..), ExternalID(..), PubidLiteral(..), SystemLiteral(..)) import Prelude (FilePath, Maybe(..), Eq, Monad(..), (++), map) \end{code} \begin{musicxml} Starting with Version 2.0, the MusicXML format includes a standard zip compressed version. These zip files can contain multiple MusicXML files as well as other media files for images and sound. The container DTD describes the contents of the META-INF/container.xml file. The container describes the starting point for the MusicXML version of the file, as well as alternate renditions such as PDF and audio versions of the musical score. The MusicXML 2.0 zip file format is compatible with the zip format used by the java.util.zip package and Java JAR files. It is based on the Info-ZIP format described at: ftp://ftp.uu.net/pub/archiving/zip/doc/appnote-970311-iz.zip The JAR file format is specified at: http://java.sun.com/javase/6/docs/technotes/guides/jar/jar.html Note that, compatible with JAR files, file names should be encoded in UTF-8 format. Files with the zip container are compressed the DEFLATE algorithm. The DEFLATE Compressed Data Format (RFC 1951) is specified at: http://www.ietf.org/rfc/rfc1951.txt The recommended file suffix for compressed MusicXML 2.0 files is .mxl. The recommended media type for a compressed MusicXML file is: application/vnd.recordare.musicxml The recommended media type for an uncompressed MusicXML file is: application/vnd.recordare.musicxml+xml Suggested use: \begin{verbatim} \end{verbatim} \end{musicxml} \begin{code} -- | doctype :: DocTypeDecl doctype = DTD "container" (Just (PUBLIC (PubidLiteral "-//Recordare//DTD MusicXML 2.0 Container//EN") (SystemLiteral "http://www.musicxml.org/dtds/container.dtd"))) [] -- | getFiles :: Container -> [FilePath] getFiles = map (\((a,_),_) -> a) \end{code} \begin{musicxml} Container is the document element. \end{musicxml} \begin{code} -- * Container -- | type Container = Rootfiles -- | read_Container :: Eq i => StateT Result [Content i] Container read_Container = do y <- read_ELEMENT "container" read_1 read_Rootfiles (childs y) -- | show_Container :: Container -> [Content ()] show_Container a = show_ELEMENT "container" [] (show_Rootfiles a) \end{code} \begin{musicxml} Rootfiles include the starting points for the different representations of a MusicXML score. The MusicXML root must be described in the first rootfile element. Additional rootfile elements can describe alternate versions such as PDF and audio files. \end{musicxml} \begin{code} -- | type Rootfiles = [Rootfile] -- | read_Rootfiles :: Eq i => StateT Result [Content i] Rootfiles read_Rootfiles = do y <- read_ELEMENT "rootfiles" read_1 (read_LIST1 read_Rootfile) (childs y) -- | show_Rootfiles :: Rootfiles -> [Content ()] show_Rootfiles a = show_ELEMENT "rootfiles" [] (show_LIST1 show_Rootfile a) \end{code} \begin{musicxml} The rootfile element describes each top-level file in the MusicXML container. The full-path attribute provides the path relative to the root folder of the zip file. The media-type identifies the type of different top-level root files. It is an error to have a non-MusicXML media-type value in the first rootfile in a rootfiles element. If no media-type value is present, a MusicXML file is assumed. A MusicXML file used as a rootfile may have score-partwise, score-timewise, or opus as its document element. \end{musicxml} \begin{code} -- | type Rootfile = ((CDATA, Maybe CDATA), ()) -- | read_Rootfile :: Eq i => StateT Result [Content i] Rootfile read_Rootfile = do y <- read_ELEMENT "rootfile" y1 <- read_2 (read_REQUIRED "full-path" read_CDATA) (read_IMPLIED "media-type" read_CDATA) (attributes y) return (y1,()) -- | show_Rootfile :: Rootfile -> [Content ()] show_Rootfile ((a,b),_) = show_ELEMENT "rootfile" (show_REQUIRED "full-path" show_CDATA a ++ show_IMPLIED "media-type" show_CDATA b) [] \end{code}