\begin{code}
-- |  
-- Maintainer : silva.samuel@alumni.uminho.pt
-- Stability  : experimental
-- Portability: HaXML
-- 
module Text.XML.MusicXML.Link where
import Text.XML.MusicXML.Common 
import Text.XML.HaXml.Types (Content, Attribute)
import Prelude (Maybe, Show, Eq, Monad(..), String, (++))
\end{code} \begin{musicxml} The link-attributes entity includes all the simple XLink attributes supported in the MusicXML format. \end{musicxml} \begin{code}
-- * XLink
-- |
type Link_Attributes = (CDATA, CDATA, CDATA, 
    Maybe CDATA, Maybe CDATA,
    Link_Attributes_A, Link_Attributes_B)
-- |
read_Link_Attributes :: STM Result [Attribute] Link_Attributes
read_Link_Attributes = do
    y1 <- read_FIXED "xmlns:xlink" read_CDATA "http://www.w3.org/1999/xlink"
    y2 <- read_REQUIRED "xlink:href" read_CDATA
    y3 <- read_FIXED "xlink:type" read_CDATA "simple"
    y4 <- read_IMPLIED "xlink:role" read_CDATA
    y5 <- read_IMPLIED "xlink:title" read_CDATA
    y6 <- read_DEFAULT "xlink:show" read_Link_Attributes_A Link_Attributes_2
    y7 <- read_DEFAULT "xlink:actuate" read_Link_Attributes_B Link_Attributes_6
    return (y1,y2,y3,y4,y5,y6,y7) 
-- |
show_Link_Attributes :: Link_Attributes -> [Attribute]
show_Link_Attributes (a,b,c,d,e,f,g) = 
    show_FIXED "xmlns:xlink" show_CDATA a ++
    show_REQUIRED "xlink:href" show_CDATA b ++
    show_FIXED "xlink:type" show_CDATA c ++
    show_IMPLIED "xlink:role" show_CDATA d ++
    show_IMPLIED "xlink:title" show_CDATA e ++
    show_DEFAULT "xlink:show" show_Link_Attributes_A f ++
    show_DEFAULT "xlink:actuate" show_Link_Attributes_B g
-- |
data Link_Attributes_A = Link_Attributes_1 
                       | Link_Attributes_2
                       | Link_Attributes_3
                       | Link_Attributes_4
                       | Link_Attributes_5
                         deriving (Eq, Show)
-- |
read_Link_Attributes_A :: Prelude.String -> Result Link_Attributes_A
read_Link_Attributes_A "new" = return Link_Attributes_1
read_Link_Attributes_A "replace" = return Link_Attributes_2
read_Link_Attributes_A "embed" = return Link_Attributes_3
read_Link_Attributes_A "other" = return Link_Attributes_4
read_Link_Attributes_A "none" = return Link_Attributes_5
read_Link_Attributes_A x = fail x
-- |
show_Link_Attributes_A :: Link_Attributes_A -> Prelude.String
show_Link_Attributes_A Link_Attributes_1 = "new"
show_Link_Attributes_A Link_Attributes_2 = "replace"
show_Link_Attributes_A Link_Attributes_3 = "embed"
show_Link_Attributes_A Link_Attributes_4 = "other"
show_Link_Attributes_A Link_Attributes_5 = "none"

-- |
data Link_Attributes_B = Link_Attributes_6
                       | Link_Attributes_7
                       | Link_Attributes_8
                       | Link_Attributes_9
                         deriving (Eq, Show)
-- |
read_Link_Attributes_B :: Prelude.String -> Result Link_Attributes_B
read_Link_Attributes_B "onRequest" = return Link_Attributes_6
read_Link_Attributes_B "onLoad" = return Link_Attributes_7
read_Link_Attributes_B "other" = return Link_Attributes_8
read_Link_Attributes_B "none" = return Link_Attributes_9
read_Link_Attributes_B x = fail x
-- |
show_Link_Attributes_B :: Link_Attributes_B -> Prelude.String
show_Link_Attributes_B Link_Attributes_6 = "onRequest"
show_Link_Attributes_B Link_Attributes_7 = "onLoad"
show_Link_Attributes_B Link_Attributes_8 = "other"
show_Link_Attributes_B Link_Attributes_9 = "none"
\end{code} \begin{musicxml} The element and position attributes are new as of Version 2.0. They allow for bookmarks and links to be positioned at higher resolution than the level of music-data elements. When no element and position attributes are present, the bookmark or link element refers to the next sibling element in the MusicXML file. The element attribute specifies an element type for a descendant of the next sibling element that is not a link or bookmark. The position attribute specifies the position of this descendant element, where the first position is 1. The position attribute is ignored if the element attribute is not present. For instance, an element value of "beam" and a position value of "2" defines the link or bookmark to refer to the second beam descendant of the next sibling element that is not a link or bookmark. This is equivalent to an XPath test of [.//beam[2]] done in the context of the sibling element. \end{musicxml} \begin{code}
-- * Link
-- |
type Link = ((Link_Attributes, 
        Maybe CDATA, Maybe CDATA, Maybe CDATA, Position), ())
-- |
read_Link :: Eq i => STM Result [Content i] Link
read_Link = do
    y <- read_ELEMENT "link"
    y1 <- read_5 read_Link_Attributes (read_IMPLIED "name" read_CDATA)
                 (read_IMPLIED "element" read_CDATA) 
                 (read_IMPLIED "position" read_CDATA) 
                 read_Position (attributes y)
    return (y1,())
-- |
show_Link :: Link -> [Content ()]
show_Link ((a,b,c,d,e),_) = 
    show_ELEMENT "link" (show_Link_Attributes a ++ 
                         show_IMPLIED "name" show_CDATA b ++
                         show_IMPLIED "element" show_CDATA c ++
                         show_IMPLIED "position" show_CDATA d ++
                         show_Position e) []
-- * Bookmark
-- |
type Bookmark = ((ID, Maybe CDATA, Maybe CDATA, Maybe CDATA), ())
-- |
read_Bookmark :: Eq i => STM Result [Content i] Bookmark
read_Bookmark = do
    y <- read_ELEMENT "bookmark"
    y1 <- read_4 (read_REQUIRED "id" read_ID) 
                 (read_IMPLIED "name" read_CDATA)
                 (read_IMPLIED "element" read_CDATA) 
                 (read_IMPLIED "position" read_CDATA) 
                 (attributes y)
    return (y1,())
-- |
show_Bookmark :: Bookmark -> [Content ()]
show_Bookmark ((a,b,c,d),_) = 
    show_ELEMENT "bookmark" (show_REQUIRED "id" show_ID a ++ 
                             show_IMPLIED "name" show_CDATA b ++
                             show_IMPLIED "element" show_CDATA c ++
                             show_IMPLIED "position" show_CDATA d) []
\end{code}