\begin{code}
-- |  
-- Maintainer : silva.samuel@alumni.uminho.pt
-- Stability  : experimental
-- Portability: HaXML
-- 
module Text.XML.MusicXML.Identity where
import Text.XML.MusicXML.Common 
import Text.XML.HaXml.Types (Content)
import Control.Monad (MonadPlus(..))
import Prelude (Maybe, Monad(..), Functor(..), Show, Eq, (.), (++))
\end{code} \begin{musicxml} The identify DTD module contains the identification element and its children, containing metadata about a score. Identification contains basic metadata about the score. It includes the information in MuseData headers that may apply at a score-wide, movement-wide, or part-wide level. The creator, rights, source, and relation elements are based on Dublin Core. \end{musicxml} \begin{code}
-- * Identification
-- |
type Identification = ([Creator], [Rights], Maybe Encoding,
    Maybe Source, [Relation], Maybe Miscellaneous)
-- |
read_Identification :: Eq i => StateT Result [Content i] Identification
read_Identification = do
    y <- read_ELEMENT "identification" 
    read_6 (read_LIST read_Creator) (read_LIST read_Rights)
           (read_MAYBE read_Encoding) (read_MAYBE read_Source)
           (read_LIST read_Relation) (read_MAYBE read_Miscellaneous)
           (childs y)
-- |
show_Identification :: Identification -> [Content ()]
show_Identification (a,b,c,d,e,f) = 
    show_ELEMENT "identification" [] 
        (show_LIST show_Creator a ++ show_LIST show_Rights b ++
         show_MAYBE show_Encoding c ++ show_MAYBE show_Source d ++
         show_LIST show_Relation e ++ show_MAYBE show_Miscellaneous f)
-- |
update_Identification :: ([Software], Encoding_Date) -> Identification -> Identification
update_Identification x (a,b,c,d,e,f) = (a, b, fmap (update_Encoding x) c, d, e, f)
\end{code} \begin{musicxml} The creator element is borrowed from Dublin Core. It is used for the creators of the score. The type attribute is used to distinguish different creative contributions. Thus, there can be multiple creators within an identification. Standard type values are composer, lyricist, and arranger. Other type values may be used for different types of creative roles. The type attribute should usually be used even if there is just a single creator element. The MusicXML format does not use the creator / contributor distinction from Dublin Core. \end{musicxml} \begin{code}
-- ** Creator
-- |
type Creator = (Maybe CDATA, PCDATA)
-- |
read_Creator :: Eq i => StateT Result [Content i] Creator
read_Creator = do
    y <- read_ELEMENT "creator"
    y1 <- read_1 (read_IMPLIED "type" read_CDATA) (attributes y)
    y2 <- read_1 read_PCDATA (childs y)
    return (y1,y2)
-- |
show_Creator :: Creator -> [Content ()]
show_Creator (a,b) = 
    show_ELEMENT "creator" (show_IMPLIED "type" show_CDATA a) 
                           (show_PCDATA b)
\end{code} \begin{musicxml} Rights is borrowed from Dublin Core. It contains copyright and other intellectual property notices. Words, music, and derivatives can have different types, so multiple rights tags with different type attributes are supported. Standard type values are music, words, and arrangement, but other types may be used. The type attribute is only needed when there are multiple rights elements. \end{musicxml} \begin{code}
-- ** Rights
-- |
type Rights = (Maybe CDATA, CDATA)
-- |
read_Rights :: Eq i => StateT Result [Content i] Rights
read_Rights = do
    y <- read_ELEMENT "rights"
    y1 <- read_1 (read_IMPLIED "type" read_CDATA) (attributes y)
    y2 <- read_1 read_PCDATA (childs y)
    return (y1,y2)
-- |
show_Rights :: Rights -> [Content ()]
show_Rights (a,b) = 
    show_ELEMENT "rights" (show_IMPLIED "type" show_CDATA a) 
                          (show_PCDATA b)
\end{code} \begin{musicxml} Encoding contains information about who did the digital encoding, when, with what software, and in what aspects. Standard type values for the encoder element are music, words, and arrangement, but other types may be used. The type attribute is only needed when there are multiple encoder elements. The supports element indicates if the encoding supports a particular MusicXML element. This is recommended for elements like beam, stem, and accidental, where the absence of an element is ambiguous if you do not know if the encoding supports that element. For Version 2.0, the supports element is expanded to allow programs to indicate support for particular attributes or particular values. This lets applications communicate, for example, that all system and/or page breaks are contained in the MusicXML file. \end{musicxml} \begin{code}
-- ** Encoding
-- |
type Encoding = [Encoding_]
-- |
read_Encoding :: Eq i => StateT Result [Content i] Encoding
read_Encoding = do
    y <- read_ELEMENT "encoding"
    read_1 (read_LIST read_Encoding_) (childs y)
-- |
show_Encoding :: Encoding -> [Content ()]
show_Encoding a = show_ELEMENT "encoding" [] (show_LIST show_Encoding_ a)
-- |
update_Encoding :: ([Software], Encoding_Date) -> Encoding -> Encoding
update_Encoding (s,d) _ = (Encoding_1 d) : (fmap Encoding_3 s)
-- |
data Encoding_ = Encoding_1 Encoding_Date
               | Encoding_2 Encoder
               | Encoding_3 Software
               | Encoding_4 Encoding_Description
               | Encoding_5 Supports
                 deriving (Eq, Show)
-- |
read_Encoding_ :: Eq i => StateT Result [Content i] Encoding_
read_Encoding_ = 
    (read_Encoding_Date >>= return . Encoding_1) `mplus`
    (read_Encoder >>= return . Encoding_2) `mplus`
    (read_Software >>= return . Encoding_3) `mplus`
    (read_Encoding_Description >>= return . Encoding_4) `mplus`
    (read_Supports >>= return . Encoding_5)
-- |
show_Encoding_ :: Encoding_ -> [Content ()]
show_Encoding_ (Encoding_1 a) = show_Encoding_Date a
show_Encoding_ (Encoding_2 a) = show_Encoder a
show_Encoding_ (Encoding_3 a) = show_Software a
show_Encoding_ (Encoding_4 a) = show_Encoding_Description a
show_Encoding_ (Encoding_5 a) = show_Supports a
-- |
type Encoding_Date = YYYY_MM_DD
-- |
read_Encoding_Date :: Eq i => StateT Result [Content i] Encoding_Date
read_Encoding_Date = do
    y <- read_ELEMENT "encoding-date"
    read_1 (read_YYYY_MM_DD) (childs y)
-- |
show_Encoding_Date :: Encoding_Date -> [Content ()]
show_Encoding_Date a = 
    show_ELEMENT "encoding-date" [] (show_YYYY_MM_DD a)
-- |
type Encoder = (Maybe CDATA, PCDATA)
-- |
read_Encoder :: Eq i => StateT Result [Content i] Encoder
read_Encoder = do 
    y <- read_ELEMENT "encoder"
    y1 <- read_1 (read_IMPLIED "type" read_CDATA) (attributes y)
    y2 <- read_1 read_PCDATA (childs y)
    return (y1,y2)
-- |
show_Encoder :: Encoder -> [Content ()]
show_Encoder (a,b) = 
    show_ELEMENT "encoder" (show_IMPLIED "type" show_CDATA a) 
                           (show_PCDATA b)
-- |
type Software = PCDATA
-- |
read_Software :: Eq i => StateT Result [Content i] Software
read_Software = do
    y <- read_ELEMENT "software"
    read_1 read_PCDATA (childs y)
-- |
show_Software :: Software -> [Content ()]
show_Software a = show_ELEMENT "software" [] (show_PCDATA a)
-- |
type Encoding_Description = PCDATA
-- |
read_Encoding_Description :: StateT Result [Content i] Encoding_Description
read_Encoding_Description = do
    y <- read_ELEMENT "encoding-description"
    read_1 read_PCDATA (childs y)
-- |
show_Encoding_Description :: Encoding_Description -> [Content ()]
show_Encoding_Description a = 
    show_ELEMENT "encoding-description" [] (show_PCDATA a)
-- |
type Supports = ((Yes_No, CDATA, Maybe CDATA, Maybe CDATA), ())
-- |
read_Supports :: Eq i => StateT Result [Content i] Supports
read_Supports = do
    y <- read_ELEMENT "supports"
    y1 <- read_4 (read_REQUIRED "type" read_Yes_No)
                 (read_REQUIRED "element" read_CDATA)
                 (read_IMPLIED "attribute" read_CDATA)
                 (read_IMPLIED "value" read_CDATA) (attributes y)
    return (y1,())
-- |
show_Supports :: Supports -> [Content ()]
show_Supports ((a,b,c,d),_) = 
    show_ELEMENT "supports" (show_REQUIRED "type" show_Yes_No a ++
                             show_REQUIRED "element" show_CDATA b ++
                             show_IMPLIED "attribute" show_CDATA c ++
                             show_IMPLIED "value" show_CDATA d) []
\end{code} \begin{musicxml} The source for the music that is encoded. This is similar to the Dublin Core source element. \end{musicxml} \begin{code}
-- ** Source
-- |
type Source = PCDATA
-- |
read_Source :: StateT Result [Content i] Source
read_Source = do
    y <- read_ELEMENT "source"
    read_1 read_PCDATA (childs y)
-- |
show_Source :: Source -> [Content ()]
show_Source a = show_ELEMENT "source" [] (show_PCDATA a)
\end{code} \begin{musicxml} A related resource for the music that is encoded. This is similar to the Dublin Core relation element. Standard type values are music, words, and arrangement, but other types may be used. \end{musicxml} \begin{code}
-- ** Relation
-- |
type Relation = (Maybe CDATA, CDATA)
-- |
read_Relation :: StateT Result [Content i] Relation
read_Relation = do
    y <- read_ELEMENT "relation"
    y1 <- read_1 (read_IMPLIED "type" read_CDATA) (attributes y)
    y2 <- read_1 read_PCDATA (childs y)
    return (y1,y2)
-- |
show_Relation :: Relation -> [Content ()]
show_Relation (a,b) = 
    show_ELEMENT "relation" (show_IMPLIED "type" show_CDATA a) 
                            (show_PCDATA b)
\end{code} \begin{musicxml} If a program has other metadata not yet supported in the MusicXML format, it can go in the miscellaneous area. \end{musicxml} \begin{code}
-- ** Miscellaneous
-- |
type Miscellaneous = [Miscellaneous_Field]
-- |
read_Miscellaneous :: Eq i => StateT Result [Content i] Miscellaneous
read_Miscellaneous = do
    y <- read_ELEMENT "miscellaneous"
    read_1 (read_LIST read_Miscellaneous_Field) (childs y)
-- |
show_Miscellaneous :: Miscellaneous -> [Content ()]
show_Miscellaneous a = 
    show_ELEMENT "miscellaneous" [] 
        (show_LIST show_Miscellaneous_Field a)
-- |
type Miscellaneous_Field = (CDATA, PCDATA)
-- |
read_Miscellaneous_Field :: StateT Result [Content i] Miscellaneous_Field
read_Miscellaneous_Field = do
    y <- read_ELEMENT "miscellaneous-field"
    y1 <- read_1 (read_REQUIRED "name" read_CDATA) (attributes y)
    y2 <- read_1 read_PCDATA (childs y)
    return (y1,y2)
-- |
show_Miscellaneous_Field :: Miscellaneous_Field -> [Content ()]
show_Miscellaneous_Field (a,b) = 
    show_ELEMENT "miscellaneous-field" 
        (show_REQUIRED "name" show_CDATA a) 
        (show_PCDATA b)
\end{code}