module Text.XML.Expat.Internal.NodeClass where
import Control.Monad (mzero, liftM)
import Data.Functor.Identity
import Data.List.Class
import Data.Monoid (Monoid)
import Text.XML.Expat.SAX (GenericXMLString)
type Attributes tag text = [(tag, text)]
type UAttributes text = Attributes text text
textContent :: (NodeClass n [], Monoid text) => n [] tag text -> text
textContent node = runIdentity $ textContentM node
type family ListOf n
class (Functor c, List c) => NodeClass n c where
isElement :: n c tag text -> Bool
isText :: n c tag text -> Bool
isCData :: n c tag text -> Bool
isProcessingInstruction :: n c tag text -> Bool
isComment :: n c tag text -> Bool
textContentM :: Monoid text => n c tag text -> ItemM c text
isNamed :: Eq tag => tag -> n c tag text -> Bool
getName :: Monoid tag => n c tag text -> tag
hasTarget :: Eq text => text -> n c tag text -> Bool
getTarget :: Monoid text => n c tag text -> text
getAttributes :: n c tag text -> [(tag,text)]
getChildren :: n c tag text -> c (n c tag text)
getText :: Monoid text => n c tag text -> text
modifyName :: (tag -> tag)
-> n c tag text
-> n c tag text
modifyAttributes :: ([(tag, text)] -> [(tag, text)])
-> n c tag text
-> n c tag text
modifyChildren :: (c (n c tag text) -> c (n c tag text))
-> n c tag text
-> n c tag text
modifyElement :: ((tag, [(tag, text)], c (n c tag text))
-> (tag', [(tag', text)], c (n c tag' text)))
-> n c tag text
-> n c tag' text
mapAllTags :: (tag -> tag')
-> n c tag text
-> n c tag' text
mapNodeContainer :: List c' =>
(forall a . c a -> ItemM c (c' a))
-> n c tag text
-> ItemM c (n c' tag text)
mkText :: text -> n c tag text
mapElement :: NodeClass n c =>
((tag, [(tag, text)], c (n c tag text))
-> (tag', [(tag', text)], c (n c tag' text)))
-> n c tag text
-> n c tag' text
mapElement = modifyElement
mapNodeListContainer :: (NodeClass n c, List c') =>
(forall a . c a -> ItemM c (c' a))
-> c (n c tag text)
-> ItemM c (c' (n c' tag text))
mapNodeListContainer f = f . mapL (mapNodeContainer f)
fromNodeContainer :: (NodeClass n c, List c') =>
n c tag text
-> ItemM c (n c' tag text)
fromNodeContainer = mapNodeContainer (\l -> fromList `liftM` toList l)
fromNodeListContainer :: (NodeClass n c, List c') =>
c (n c tag text)
-> ItemM c (c' (n c' tag text))
fromNodeListContainer = mapNodeListContainer (\l -> fromList `liftM` toList l)
class NodeClass n c => MkElementClass n c where
mkElement :: tag -> Attributes tag text -> c (n c tag text) -> n c tag text
getAttribute :: (NodeClass n c, GenericXMLString tag) => n c tag text -> tag -> Maybe text
getAttribute n t = lookup t $ getAttributes n
setAttribute :: (Eq tag, NodeClass n c, GenericXMLString tag) => tag -> text -> n c tag text -> n c tag text
setAttribute t newValue = modifyAttributes set
where
set [] = [(t, newValue)]
set ((name, _):atts) | name == t = (name, newValue):atts
set (att:atts) = att:set atts
deleteAttribute :: (Eq tag, NodeClass n c, GenericXMLString tag) => tag -> n c tag text -> n c tag text
deleteAttribute t = modifyAttributes del
where
del [] = []
del ((name, _):atts) | name == t = atts
del (att:atts) = att:del atts
alterAttribute :: (Eq tag, NodeClass n c, GenericXMLString tag) => tag -> Maybe text -> n c tag text -> n c tag text
alterAttribute t (Just newValue) = setAttribute t newValue
alterAttribute t Nothing = deleteAttribute t
fromElement :: (NodeClass n c, MkElementClass n' c, Monoid tag, Monoid text) =>
n c tag text
-> n' c tag text
fromElement = fromElement_ mkElement
fromElement_ :: (NodeClass n c, NodeClass n' c, Monoid tag, Monoid text) =>
(tag -> Attributes tag text -> c (n' c tag text) -> n' c tag text)
-> n c tag text
-> n' c tag text
fromElement_ mkElement elt | isElement elt =
mkElement (getName elt) (getAttributes elt) (fromNodes_ mkElement $ getChildren elt)
fromElement_ _ _ = error "fromElement requires an Element"
fromNodes :: (NodeClass n c, MkElementClass n' c, Monoid tag, Monoid text) =>
c (n c tag text)
-> c (n' c tag text)
fromNodes = fromNodes_ mkElement
fromNodes_ :: (NodeClass n c, NodeClass n' c, Monoid tag, Monoid text) =>
(tag -> Attributes tag text -> c (n' c tag text) -> n' c tag text)
-> c (n c tag text)
-> c (n' c tag text)
fromNodes_ mkElement l = joinL $ do
li <- runList l
return $ case li of
Nil -> mzero
Cons elt l' | isElement elt -> fromElement_ mkElement elt `cons` fromNodes_ mkElement l'
Cons txt l' | isText txt -> mkText (getText txt) `cons` fromNodes_ mkElement l'
Cons _ l' -> fromNodes_ mkElement l'