module Text.XML.HXT.Arrow.XmlArrow
( module Text.XML.HXT.Arrow.XmlArrow )
where
import Control.Arrow
import Control.Arrow.ArrowList
import Control.Arrow.ArrowIf
import Control.Arrow.ArrowTree
import Control.Arrow.ListArrow
import Control.Arrow.StateListArrow
import Control.Arrow.IOListArrow
import Control.Arrow.IOStateListArrow
import Data.Char.Properties.XMLCharProps ( isXmlSpaceChar )
import Data.Maybe
import Text.XML.HXT.DOM.Interface
import qualified Text.XML.HXT.DOM.XmlNode as XN
import qualified Text.XML.HXT.DOM.ShowXml as XS
infixl 7 +=
class (Arrow a, ArrowList a, ArrowTree a) => ArrowXml a where
isText :: a XmlTree XmlTree
isText = isA XN.isText
isBlob :: a XmlTree XmlTree
isBlob = isA XN.isBlob
isCharRef :: a XmlTree XmlTree
isCharRef = isA XN.isCharRef
isEntityRef :: a XmlTree XmlTree
isEntityRef = isA XN.isEntityRef
isCmt :: a XmlTree XmlTree
isCmt = isA XN.isCmt
isCdata :: a XmlTree XmlTree
isCdata = isA XN.isCdata
isPi :: a XmlTree XmlTree
isPi = isA XN.isPi
isXmlPi :: a XmlTree XmlTree
isXmlPi = isPi >>> hasName "xml"
isElem :: a XmlTree XmlTree
isElem = isA XN.isElem
isDTD :: a XmlTree XmlTree
isDTD = isA XN.isDTD
isAttr :: a XmlTree XmlTree
isAttr = isA XN.isAttr
isError :: a XmlTree XmlTree
isError = isA XN.isError
isRoot :: a XmlTree XmlTree
isRoot = isA XN.isRoot
hasText :: (String -> Bool) -> a XmlTree XmlTree
hasText p = (isText >>> getText >>> isA p) `guards` this
isWhiteSpace :: a XmlTree XmlTree
isWhiteSpace = hasText (all isXmlSpaceChar)
hasNameWith :: (QName -> Bool) -> a XmlTree XmlTree
hasNameWith p = (getQName >>> isA p) `guards` this
hasQName :: QName -> a XmlTree XmlTree
hasQName n = (getQName >>> isA (== n)) `guards` this
hasName :: String -> a XmlTree XmlTree
hasName n = (getName >>> isA (== n)) `guards` this
hasLocalPart :: String -> a XmlTree XmlTree
hasLocalPart n = (getLocalPart >>> isA (== n)) `guards` this
hasNamePrefix :: String -> a XmlTree XmlTree
hasNamePrefix n = (getNamePrefix >>> isA (== n)) `guards` this
hasNamespaceUri :: String -> a XmlTree XmlTree
hasNamespaceUri n = (getNamespaceUri >>> isA (== n)) `guards` this
hasAttr :: String -> a XmlTree XmlTree
hasAttr n = (getAttrl >>> hasName n) `guards` this
hasQAttr :: QName -> a XmlTree XmlTree
hasQAttr n = (getAttrl >>> hasQName n) `guards` this
hasAttrValue :: String -> (String -> Bool) -> a XmlTree XmlTree
hasAttrValue n p = (getAttrl >>> hasName n >>> xshow getChildren >>> isA p) `guards` this
hasQAttrValue :: QName -> (String -> Bool) -> a XmlTree XmlTree
hasQAttrValue n p = (getAttrl >>> hasQName n >>> xshow getChildren >>> isA p) `guards` this
mkText :: a String XmlTree
mkText = arr XN.mkText
mkBlob :: a Blob XmlTree
mkBlob = arr XN.mkBlob
mkCharRef :: a Int XmlTree
mkCharRef = arr XN.mkCharRef
mkEntityRef :: a String XmlTree
mkEntityRef = arr XN.mkEntityRef
mkCmt :: a String XmlTree
mkCmt = arr XN.mkCmt
mkCdata :: a String XmlTree
mkCdata = arr XN.mkCdata
mkError :: Int -> a String XmlTree
mkError level = arr (XN.mkError level)
mkElement :: QName -> a n XmlTree -> a n XmlTree -> a n XmlTree
mkElement n af cf = (listA af &&& listA cf)
>>>
arr2 (\ al cl -> XN.mkElement n al cl)
mkAttr :: QName -> a n XmlTree -> a n XmlTree
mkAttr qn f = listA f >>> arr (XN.mkAttr qn)
mkPi :: QName -> a n XmlTree -> a n XmlTree
mkPi qn f = listA f >>> arr (XN.mkPi qn)
mkqelem :: QName -> [a n XmlTree] -> [a n XmlTree] -> a n XmlTree
mkqelem n afs cfs = mkElement n (catA afs) (catA cfs)
mkelem :: String -> [a n XmlTree] -> [a n XmlTree] -> a n XmlTree
mkelem n afs cfs = mkElement (mkName n) (catA afs) (catA cfs)
aelem :: String -> [a n XmlTree] -> a n XmlTree
aelem n afs = catA afs >. \ al -> XN.mkElement (mkName n) al []
selem :: String -> [a n XmlTree] -> a n XmlTree
selem n cfs = catA cfs >. XN.mkElement (mkName n) []
eelem :: String -> a n XmlTree
eelem n = constA (XN.mkElement (mkName n) [] [])
root :: [a n XmlTree] -> [a n XmlTree] -> a n XmlTree
root = mkelem t_root
qattr :: QName -> a n XmlTree -> a n XmlTree
qattr = mkAttr
attr :: String -> a n XmlTree -> a n XmlTree
attr = mkAttr . mkName
txt :: String -> a n XmlTree
txt = constA . XN.mkText
blb :: Blob -> a n XmlTree
blb = constA . XN.mkBlob
charRef :: Int -> a n XmlTree
charRef = constA . XN.mkCharRef
entityRef :: String -> a n XmlTree
entityRef = constA . XN.mkEntityRef
cmt :: String -> a n XmlTree
cmt = constA . XN.mkCmt
warn :: String -> a n XmlTree
warn = constA . (XN.mkError c_warn)
err :: String -> a n XmlTree
err = constA . (XN.mkError c_err)
fatal :: String -> a n XmlTree
fatal = constA . (XN.mkError c_fatal)
spi :: String -> String -> a n XmlTree
spi piName piCont = constA (XN.mkPi (mkName piName) [XN.mkAttr (mkName a_value) [XN.mkText piCont]])
sqattr :: QName -> String -> a n XmlTree
sqattr an av = constA (XN.mkAttr an [XN.mkText av])
sattr :: String -> String -> a n XmlTree
sattr an av = constA (XN.mkAttr (mkName an) [XN.mkText av])
getText :: a XmlTree String
getText = arrL (maybeToList . XN.getText)
getCharRef :: a XmlTree Int
getCharRef = arrL (maybeToList . XN.getCharRef)
getEntityRef :: a XmlTree String
getEntityRef = arrL (maybeToList . XN.getEntityRef)
getCmt :: a XmlTree String
getCmt = arrL (maybeToList . XN.getCmt)
getCdata :: a XmlTree String
getCdata = arrL (maybeToList . XN.getCdata)
getPiName :: a XmlTree QName
getPiName = arrL (maybeToList . XN.getPiName)
getPiContent :: a XmlTree XmlTree
getPiContent = arrL (fromMaybe [] . XN.getPiContent)
getElemName :: a XmlTree QName
getElemName = arrL (maybeToList . XN.getElemName)
getAttrl :: a XmlTree XmlTree
getAttrl = arrL (fromMaybe [] . XN.getAttrl)
getDTDPart :: a XmlTree DTDElem
getDTDPart = arrL (maybeToList . XN.getDTDPart)
getDTDAttrl :: a XmlTree Attributes
getDTDAttrl = arrL (maybeToList . XN.getDTDAttrl)
getAttrName :: a XmlTree QName
getAttrName = arrL (maybeToList . XN.getAttrName)
getErrorLevel :: a XmlTree Int
getErrorLevel = arrL (maybeToList . XN.getErrorLevel)
getErrorMsg :: a XmlTree String
getErrorMsg = arrL (maybeToList . XN.getErrorMsg)
getQName :: a XmlTree QName
getQName = arrL (maybeToList . XN.getName)
getName :: a XmlTree String
getName = arrL (maybeToList . XN.getQualifiedName)
getUniversalName :: a XmlTree String
getUniversalName = arrL (maybeToList . XN.getUniversalName)
getUniversalUri :: a XmlTree String
getUniversalUri = arrL (maybeToList . XN.getUniversalUri)
getLocalPart :: a XmlTree String
getLocalPart = arrL (maybeToList . XN.getLocalPart)
getNamePrefix :: a XmlTree String
getNamePrefix = arrL (maybeToList . XN.getNamePrefix)
getNamespaceUri :: a XmlTree String
getNamespaceUri = arrL (maybeToList . XN.getNamespaceUri)
getAttrValue :: String -> a XmlTree String
getAttrValue n = xshow (getAttrl >>> hasName n >>> getChildren)
getAttrValue0 :: String -> a XmlTree String
getAttrValue0 n = getAttrl >>> hasName n >>> xshow getChildren
getQAttrValue :: QName -> a XmlTree String
getQAttrValue n = xshow (getAttrl >>> hasQName n >>> getChildren)
getQAttrValue0 :: QName -> a XmlTree String
getQAttrValue0 n = getAttrl >>> hasQName n >>> xshow getChildren
changeText :: (String -> String) -> a XmlTree XmlTree
changeText cf = arr (XN.changeText cf) `when` isText
changeBlob :: (Blob -> Blob) -> a XmlTree XmlTree
changeBlob cf = arr (XN.changeBlob cf) `when` isBlob
changeCmt :: (String -> String) -> a XmlTree XmlTree
changeCmt cf = arr (XN.changeCmt cf) `when` isCmt
changeQName :: (QName -> QName) -> a XmlTree XmlTree
changeQName cf = arr (XN.changeName cf) `when` getQName
changeElemName :: (QName -> QName) -> a XmlTree XmlTree
changeElemName cf = arr (XN.changeElemName cf) `when` isElem
changeAttrName :: (QName -> QName) -> a XmlTree XmlTree
changeAttrName cf = arr (XN.changeAttrName cf) `when` isAttr
changePiName :: (QName -> QName) -> a XmlTree XmlTree
changePiName cf = arr (XN.changePiName cf) `when` isPi
changeAttrValue :: (String -> String) -> a XmlTree XmlTree
changeAttrValue cf = replaceChildren ( xshow getChildren
>>> arr cf
>>> mkText
)
`when` isAttr
changeAttrl :: (XmlTrees -> XmlTrees -> XmlTrees) -> a XmlTree XmlTree -> a XmlTree XmlTree
changeAttrl cf f = ( ( listA f &&& this )
>>>
arr2 changeAL
)
`when`
( isElem <+> isPi )
where
changeAL as x = XN.changeAttrl (\ xs -> cf xs as) x
setQName :: QName -> a XmlTree XmlTree
setQName n = changeQName (const n)
setElemName :: QName -> a XmlTree XmlTree
setElemName n = changeElemName (const n)
setAttrName :: QName -> a XmlTree XmlTree
setAttrName n = changeAttrName (const n)
setPiName :: QName -> a XmlTree XmlTree
setPiName n = changePiName (const n)
setAttrl :: a XmlTree XmlTree -> a XmlTree XmlTree
setAttrl = changeAttrl (const id)
addAttrl :: a XmlTree XmlTree -> a XmlTree XmlTree
addAttrl = changeAttrl (XN.mergeAttrl)
addAttr :: String -> String -> a XmlTree XmlTree
addAttr an av = addAttrl (sattr an av)
removeAttr :: String -> a XmlTree XmlTree
removeAttr an = processAttrl (none `when` hasName an)
removeQAttr :: QName -> a XmlTree XmlTree
removeQAttr an = processAttrl (none `when` hasQName an)
processAttrl :: a XmlTree XmlTree -> a XmlTree XmlTree
processAttrl f = setAttrl (getAttrl >>> f)
processTopDownWithAttrl :: a XmlTree XmlTree -> a XmlTree XmlTree
processTopDownWithAttrl f = processTopDown ( f >>> ( processAttrl (processTopDown f) `when` isElem))
(+=) :: a b XmlTree -> a b XmlTree -> a b XmlTree
tf += cf = (tf &&& listA cf) >>> arr2 addChildren
where
addChildren :: XmlTree -> XmlTrees -> XmlTree
addChildren t cs
= foldl addChild t cs
addChild :: XmlTree -> XmlTree -> XmlTree
addChild t c
| not (XN.isElem t)
= t
| XN.isAttr c
= XN.changeAttrl (XN.addAttr c) t
| otherwise
= XN.changeChildren (++ [c]) t
xshow :: a n XmlTree -> a n String
xshow f = f >. XS.xshow
xshowBlob :: a n XmlTree -> a n Blob
xshowBlob f = f >. XS.xshowBlob
class (ArrowXml a) => ArrowDTD a where
isDTDDoctype :: a XmlTree XmlTree
isDTDDoctype = isA (maybe False (== DOCTYPE ) . XN.getDTDPart)
isDTDElement :: a XmlTree XmlTree
isDTDElement = isA (maybe False (== ELEMENT ) . XN.getDTDPart)
isDTDContent :: a XmlTree XmlTree
isDTDContent = isA (maybe False (== CONTENT ) . XN.getDTDPart)
isDTDAttlist :: a XmlTree XmlTree
isDTDAttlist = isA (maybe False (== ATTLIST ) . XN.getDTDPart)
isDTDEntity :: a XmlTree XmlTree
isDTDEntity = isA (maybe False (== ENTITY ) . XN.getDTDPart)
isDTDPEntity :: a XmlTree XmlTree
isDTDPEntity = isA (maybe False (== PENTITY ) . XN.getDTDPart)
isDTDNotation :: a XmlTree XmlTree
isDTDNotation = isA (maybe False (== NOTATION) . XN.getDTDPart)
isDTDCondSect :: a XmlTree XmlTree
isDTDCondSect = isA (maybe False (== CONDSECT) . XN.getDTDPart)
isDTDName :: a XmlTree XmlTree
isDTDName = isA (maybe False (== NAME ) . XN.getDTDPart)
isDTDPERef :: a XmlTree XmlTree
isDTDPERef = isA (maybe False (== PEREF ) . XN.getDTDPart)
hasDTDAttr :: String -> a XmlTree XmlTree
hasDTDAttr n = isA (isJust . lookup n . fromMaybe [] . XN.getDTDAttrl)
getDTDAttrValue :: String -> a XmlTree String
getDTDAttrValue n = arrL (maybeToList . lookup n . fromMaybe [] . XN.getDTDAttrl)
setDTDAttrValue :: String -> String -> a XmlTree XmlTree
setDTDAttrValue n v = arr (XN.changeDTDAttrl (addEntry n v)) `when` isDTD
mkDTDElem :: DTDElem -> Attributes -> a n XmlTree -> a n XmlTree
mkDTDElem e al cf = listA cf >>> arr (XN.mkDTDElem e al)
mkDTDDoctype :: Attributes -> a n XmlTree -> a n XmlTree
mkDTDDoctype = mkDTDElem DOCTYPE
mkDTDElement :: Attributes -> a n XmlTree
mkDTDElement al = mkDTDElem ELEMENT al none
mkDTDEntity :: Attributes -> a n XmlTree
mkDTDEntity al = mkDTDElem ENTITY al none
mkDTDPEntity :: Attributes -> a n XmlTree
mkDTDPEntity al = mkDTDElem PENTITY al none
instance ArrowXml LA
instance ArrowXml (SLA s)
instance ArrowXml IOLA
instance ArrowXml (IOSLA s)
instance ArrowDTD LA
instance ArrowDTD (SLA s)
instance ArrowDTD IOLA
instance ArrowDTD (IOSLA s)