module Text.XML.HXT.Arrow.ProcessDocument
( parseXmlDocument
, parseXmlDocumentWithExpat
, parseHtmlDocument
, validateDocument
, propagateAndValidateNamespaces
, andValidateNamespaces
, getDocumentContents
)
where
import Control.Arrow
import Control.Arrow.ArrowIf
import Control.Arrow.ArrowList
import Control.Arrow.ArrowTree
import Control.Arrow.ListArrow (fromLA)
import Control.Arrow.NTreeEdit
import Text.XML.HXT.DOM.Interface
import Text.XML.HXT.Arrow.XmlArrow
import Text.XML.HXT.Arrow.XmlState
import Text.XML.HXT.Arrow.XmlState.TypeDefs
import Text.XML.HXT.Arrow.ParserInterface (parseHtmlDoc,
parseXmlDoc)
import Text.XML.HXT.Arrow.Edit (substAllXHTMLEntityRefs,
transfAllCharRef)
import Text.XML.HXT.Arrow.GeneralEntitySubstitution (processGeneralEntities)
import Text.XML.HXT.Arrow.DTDProcessing (processDTD)
import Text.XML.HXT.Arrow.DocumentInput (getXmlContents)
import Text.XML.HXT.Arrow.Namespace (propagateNamespaces, validateNamespaces)
import Text.XML.HXT.DTDValidation.Validation (generalEntitiesDefined,
getDTDSubset,
transform,
validate)
parseXmlDocument :: Bool -> Bool -> Bool -> Bool -> IOStateArrow s XmlTree XmlTree
parseXmlDocument :: Bool -> Bool -> Bool -> Bool -> IOStateArrow s XmlTree XmlTree
parseXmlDocument Bool
validateD Bool
substDTD Bool
substHTML Bool
validateRX
= ( IOStateArrow s XmlTree XmlTree -> IOStateArrow s XmlTree XmlTree
forall (a :: * -> * -> *) (t :: * -> *) b.
(ArrowTree a, Tree t) =>
a (t b) (t b) -> a (t b) (t b)
replaceChildren ( ( String -> IOSLA (XIOState s) XmlTree String
forall (a :: * -> * -> *). ArrowXml a => String -> a XmlTree String
getAttrValue String
a_source
IOSLA (XIOState s) XmlTree String
-> IOSLA (XIOState s) XmlTree String
-> IOSLA (XIOState s) XmlTree (String, String)
forall (a :: * -> * -> *) b c c'.
Arrow a =>
a b c -> a b c' -> a b (c, c')
&&&
IOStateArrow s XmlTree XmlTree -> IOSLA (XIOState s) XmlTree String
forall (a :: * -> * -> *) n.
ArrowXml a =>
a n XmlTree -> a n String
xshow IOStateArrow s XmlTree XmlTree
forall (a :: * -> * -> *) (t :: * -> *) b.
(ArrowTree a, Tree t) =>
a (t b) (t b)
getChildren
)
IOSLA (XIOState s) XmlTree (String, String)
-> IOSLA (XIOState s) (String, String) XmlTree
-> IOStateArrow s XmlTree XmlTree
forall k (cat :: k -> k -> *) (a :: k) (b :: k) (c :: k).
Category cat =>
cat a b -> cat b c -> cat a c
>>>
IOSLA (XIOState s) (String, String) XmlTree
forall (a :: * -> * -> *). ArrowXml a => a (String, String) XmlTree
parseXmlDoc
IOSLA (XIOState s) (String, String) XmlTree
-> IOStateArrow s XmlTree XmlTree
-> IOSLA (XIOState s) (String, String) XmlTree
forall k (cat :: k -> k -> *) (a :: k) (b :: k) (c :: k).
Category cat =>
cat a b -> cat b c -> cat a c
>>>
IOStateArrow s XmlTree XmlTree
forall s. IOStateArrow s XmlTree XmlTree
filterErrorMsg
)
IOStateArrow s XmlTree XmlTree
-> IOStateArrow s XmlTree XmlTree -> IOStateArrow s XmlTree XmlTree
forall k (cat :: k -> k -> *) (a :: k) (b :: k) (c :: k).
Category cat =>
cat a b -> cat b c -> cat a c
>>>
String -> IOStateArrow s XmlTree XmlTree
forall s. String -> IOStateArrow s XmlTree XmlTree
setDocumentStatusFromSystemState String
"parse XML document"
IOStateArrow s XmlTree XmlTree
-> IOStateArrow s XmlTree XmlTree -> IOStateArrow s XmlTree XmlTree
forall k (cat :: k -> k -> *) (a :: k) (b :: k) (c :: k).
Category cat =>
cat a b -> cat b c -> cat a c
>>>
( IOStateArrow s XmlTree XmlTree
-> IOStateArrow s XmlTree XmlTree
-> IOStateArrow s XmlTree XmlTree
-> IOStateArrow s XmlTree XmlTree
forall (a :: * -> * -> *) b c d.
ArrowIf a =>
a b c -> a b d -> a b d -> a b d
ifA (LA XmlTree XmlTree -> IOStateArrow s XmlTree XmlTree
forall (a :: * -> * -> *) b c. ArrowList a => LA b c -> a b c
fromLA LA XmlTree XmlTree
getDTDSubset)
( IOStateArrow s XmlTree XmlTree
forall s. IOStateArrow s XmlTree XmlTree
processDTDandEntities
IOStateArrow s XmlTree XmlTree
-> IOStateArrow s XmlTree XmlTree -> IOStateArrow s XmlTree XmlTree
forall k (cat :: k -> k -> *) (a :: k) (b :: k) (c :: k).
Category cat =>
cat a b -> cat b c -> cat a c
>>>
( if Bool
validate'
then IOStateArrow s XmlTree XmlTree
forall s. IOStateArrow s XmlTree XmlTree
validateDocument
else IOStateArrow s XmlTree XmlTree
forall (a :: * -> * -> *) b. ArrowList a => a b b
this
)
)
( if Bool
validate'
then Int -> String -> IOStateArrow s XmlTree XmlTree
forall s b. Int -> String -> IOStateArrow s b b
traceMsg Int
2 String
"checkUndefinedEntityRefs: looking for undefined entity refs"
IOStateArrow s XmlTree XmlTree
-> IOStateArrow s XmlTree XmlTree -> IOStateArrow s XmlTree XmlTree
forall k (cat :: k -> k -> *) (a :: k) (b :: k) (c :: k).
Category cat =>
cat a b -> cat b c -> cat a c
>>>
IOStateArrow s XmlTree XmlTree -> IOStateArrow s XmlTree XmlTree
forall (a :: * -> * -> *) b c. ArrowList a => a b c -> a b b
perform IOStateArrow s XmlTree XmlTree
forall s. IOStateArrow s XmlTree XmlTree
checkUndefinedEntityRefs
IOStateArrow s XmlTree XmlTree
-> IOStateArrow s XmlTree XmlTree -> IOStateArrow s XmlTree XmlTree
forall k (cat :: k -> k -> *) (a :: k) (b :: k) (c :: k).
Category cat =>
cat a b -> cat b c -> cat a c
>>>
Int -> String -> IOStateArrow s XmlTree XmlTree
forall s b. Int -> String -> IOStateArrow s b b
traceMsg Int
2 String
"checkUndefinedEntityRefs: looking for undefined entity refs done"
IOStateArrow s XmlTree XmlTree
-> IOStateArrow s XmlTree XmlTree -> IOStateArrow s XmlTree XmlTree
forall k (cat :: k -> k -> *) (a :: k) (b :: k) (c :: k).
Category cat =>
cat a b -> cat b c -> cat a c
>>>
String -> IOStateArrow s XmlTree XmlTree
forall s. String -> IOStateArrow s XmlTree XmlTree
setDocumentStatusFromSystemState String
"decoding document"
else IOStateArrow s XmlTree XmlTree
forall (a :: * -> * -> *) b. ArrowList a => a b b
this
)
)
)
IOStateArrow s XmlTree XmlTree
-> IOStateArrow s XmlTree XmlTree -> IOStateArrow s XmlTree XmlTree
forall (a :: * -> * -> *) b c. ArrowIf a => a b b -> a b c -> a b b
`when` IOStateArrow s XmlTree XmlTree
forall (a :: * -> * -> *). ArrowXml a => a XmlTree XmlTree
documentStatusOk
where
validate' :: Bool
validate'
= Bool
validateD Bool -> Bool -> Bool
&& Bool -> Bool
not Bool
validateRX
processDTDandEntities :: IOSLA (XIOState s) XmlTree XmlTree
processDTDandEntities
= ( if Bool
validateD Bool -> Bool -> Bool
|| Bool
substDTD
then IOSLA (XIOState s) XmlTree XmlTree
forall s. IOStateArrow s XmlTree XmlTree
processDTD
else IOSLA (XIOState s) XmlTree XmlTree
forall (a :: * -> * -> *) b. ArrowList a => a b b
this
)
IOSLA (XIOState s) XmlTree XmlTree
-> IOSLA (XIOState s) XmlTree XmlTree
-> IOSLA (XIOState s) XmlTree XmlTree
forall k (cat :: k -> k -> *) (a :: k) (b :: k) (c :: k).
Category cat =>
cat a b -> cat b c -> cat a c
>>>
( if Bool
substDTD
then ( IOSLA (XIOState s) XmlTree XmlTree
forall s. IOStateArrow s XmlTree XmlTree
processGeneralEntities
IOSLA (XIOState s) XmlTree XmlTree
-> IOSLA (XIOState s) XmlTree XmlTree
-> IOSLA (XIOState s) XmlTree XmlTree
forall (a :: * -> * -> *) b c. ArrowIf a => a b b -> a b c -> a b b
`when`
LA XmlTree XmlTree -> IOSLA (XIOState s) XmlTree XmlTree
forall (a :: * -> * -> *) b c. ArrowList a => LA b c -> a b c
fromLA LA XmlTree XmlTree
generalEntitiesDefined
)
else if Bool
substHTML
then IOSLA (XIOState s) XmlTree XmlTree
forall (a :: * -> * -> *). ArrowXml a => a XmlTree XmlTree
substAllXHTMLEntityRefs
else IOSLA (XIOState s) XmlTree XmlTree
forall (a :: * -> * -> *) b. ArrowList a => a b b
this
)
IOSLA (XIOState s) XmlTree XmlTree
-> IOSLA (XIOState s) XmlTree XmlTree
-> IOSLA (XIOState s) XmlTree XmlTree
forall k (cat :: k -> k -> *) (a :: k) (b :: k) (c :: k).
Category cat =>
cat a b -> cat b c -> cat a c
>>>
IOSLA (XIOState s) XmlTree XmlTree
forall (a :: * -> * -> *). ArrowXml a => a XmlTree XmlTree
transfAllCharRef
checkUndefinedEntityRefs :: IOStateArrow s XmlTree XmlTree
checkUndefinedEntityRefs :: IOStateArrow s XmlTree XmlTree
checkUndefinedEntityRefs
= IOStateArrow s XmlTree XmlTree -> IOStateArrow s XmlTree XmlTree
forall (a :: * -> * -> *) (t :: * -> *) b c.
(ArrowTree a, Tree t) =>
a (t b) c -> a (t b) c
deep IOStateArrow s XmlTree XmlTree
forall (a :: * -> * -> *). ArrowXml a => a XmlTree XmlTree
isEntityRef
IOStateArrow s XmlTree XmlTree
-> IOStateArrow s XmlTree XmlTree -> IOStateArrow s XmlTree XmlTree
forall k (cat :: k -> k -> *) (a :: k) (b :: k) (c :: k).
Category cat =>
cat a b -> cat b c -> cat a c
>>>
IOSLA (XIOState s) XmlTree String
forall (a :: * -> * -> *). ArrowXml a => a XmlTree String
getEntityRef
IOSLA (XIOState s) XmlTree String
-> IOSLA (XIOState s) String XmlTree
-> IOStateArrow s XmlTree XmlTree
forall k (cat :: k -> k -> *) (a :: k) (b :: k) (c :: k).
Category cat =>
cat a b -> cat b c -> cat a c
>>>
(String -> String) -> IOSLA (XIOState s) String String
forall (a :: * -> * -> *) b c. Arrow a => (b -> c) -> a b c
arr (\ String
en -> String
"general entity reference \"&" String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
en String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
";\" is undefined")
IOSLA (XIOState s) String String
-> IOSLA (XIOState s) String XmlTree
-> IOSLA (XIOState s) String XmlTree
forall k (cat :: k -> k -> *) (a :: k) (b :: k) (c :: k).
Category cat =>
cat a b -> cat b c -> cat a c
>>>
Int -> IOSLA (XIOState s) String XmlTree
forall (a :: * -> * -> *). ArrowXml a => Int -> a String XmlTree
mkError Int
c_err
IOSLA (XIOState s) String XmlTree
-> IOStateArrow s XmlTree XmlTree
-> IOSLA (XIOState s) String XmlTree
forall k (cat :: k -> k -> *) (a :: k) (b :: k) (c :: k).
Category cat =>
cat a b -> cat b c -> cat a c
>>>
IOStateArrow s XmlTree XmlTree
forall s. IOStateArrow s XmlTree XmlTree
filterErrorMsg
parseXmlDocumentWithExpat :: IOStateArrow s XmlTree XmlTree
parseXmlDocumentWithExpat :: IOStateArrow s XmlTree XmlTree
parseXmlDocumentWithExpat
= ( IOSArrow XmlTree XmlTree -> IOStateArrow s XmlTree XmlTree
forall b c s0. IOSArrow b c -> IOStateArrow s0 b c
withoutUserState (IOSArrow XmlTree XmlTree -> IOStateArrow s XmlTree XmlTree)
-> IOSLA (XIOState s) XmlTree (IOSArrow XmlTree XmlTree)
-> IOStateArrow s XmlTree XmlTree
forall (a :: * -> * -> *) c b d.
ArrowList a =>
(c -> a b d) -> a b c -> a b d
$< Selector XIOSysState (IOSArrow XmlTree XmlTree)
-> IOSLA (XIOState s) XmlTree (IOSArrow XmlTree XmlTree)
forall c s b. Selector XIOSysState c -> IOStateArrow s b c
getSysVar Selector XIOSysState (IOSArrow XmlTree XmlTree)
theExpatParser
)
IOStateArrow s XmlTree XmlTree
-> IOStateArrow s XmlTree XmlTree -> IOStateArrow s XmlTree XmlTree
forall (a :: * -> * -> *) b c. ArrowIf a => a b b -> a b c -> a b b
`when` IOStateArrow s XmlTree XmlTree
forall (a :: * -> * -> *). ArrowXml a => a XmlTree XmlTree
documentStatusOk
parseHtmlDocument :: IOStateArrow s XmlTree XmlTree
parseHtmlDocument :: IOStateArrow s XmlTree XmlTree
parseHtmlDocument
= ( IOSLA (XIOState s) XmlTree String -> IOStateArrow s XmlTree XmlTree
forall (a :: * -> * -> *) b c. ArrowList a => a b c -> a b b
perform ( String -> IOSLA (XIOState s) XmlTree String
forall (a :: * -> * -> *). ArrowXml a => String -> a XmlTree String
getAttrValue String
a_source
IOSLA (XIOState s) XmlTree String
-> IOSLA (XIOState s) String String
-> IOSLA (XIOState s) XmlTree String
forall k (cat :: k -> k -> *) (a :: k) (b :: k) (c :: k).
Category cat =>
cat a b -> cat b c -> cat a c
>>>
Int -> (String -> String) -> IOSLA (XIOState s) String String
forall b s. Int -> (b -> String) -> IOStateArrow s b b
traceValue Int
1 ((String
"parseHtmlDoc: parse HTML document " String -> String -> String
forall a. [a] -> [a] -> [a]
++) (String -> String) -> (String -> String) -> String -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> String
forall a. Show a => a -> String
show)
)
IOStateArrow s XmlTree XmlTree
-> IOStateArrow s XmlTree XmlTree -> IOStateArrow s XmlTree XmlTree
forall k (cat :: k -> k -> *) (a :: k) (b :: k) (c :: k).
Category cat =>
cat a b -> cat b c -> cat a c
>>>
( (Bool, Bool) -> IOStateArrow s XmlTree XmlTree
forall s0. (Bool, Bool) -> IOSLA (XIOState s0) XmlTree XmlTree
parseHtml ((Bool, Bool) -> IOStateArrow s XmlTree XmlTree)
-> IOSLA (XIOState s) XmlTree (Bool, Bool)
-> IOStateArrow s XmlTree XmlTree
forall (a :: * -> * -> *) c b d.
ArrowList a =>
(c -> a b d) -> a b c -> a b d
$< Selector XIOSysState (Bool, Bool)
-> IOSLA (XIOState s) XmlTree (Bool, Bool)
forall c s b. Selector XIOSysState c -> IOStateArrow s b c
getSysVar (Selector XIOSysState Bool
theTagSoup Selector XIOSysState Bool
-> Selector XIOSysState Bool -> Selector XIOSysState (Bool, Bool)
forall s a b. Selector s a -> Selector s b -> Selector s (a, b)
.&&&. Selector XIOSysState Bool
theExpat) )
IOStateArrow s XmlTree XmlTree
-> IOStateArrow s XmlTree XmlTree -> IOStateArrow s XmlTree XmlTree
forall k (cat :: k -> k -> *) (a :: k) (b :: k) (c :: k).
Category cat =>
cat a b -> cat b c -> cat a c
>>>
( (Bool, Bool) -> IOStateArrow s XmlTree XmlTree
forall s0. (Bool, Bool) -> IOSLA (XIOState s0) XmlTree XmlTree
removeWarnings ((Bool, Bool) -> IOStateArrow s XmlTree XmlTree)
-> IOSLA (XIOState s) XmlTree (Bool, Bool)
-> IOStateArrow s XmlTree XmlTree
forall (a :: * -> * -> *) c b d.
ArrowList a =>
(c -> a b d) -> a b c -> a b d
$< Selector XIOSysState (Bool, Bool)
-> IOSLA (XIOState s) XmlTree (Bool, Bool)
forall c s b. Selector XIOSysState c -> IOStateArrow s b c
getSysVar (Selector XIOSysState Bool
theWarnings Selector XIOSysState Bool
-> Selector XIOSysState Bool -> Selector XIOSysState (Bool, Bool)
forall s a b. Selector s a -> Selector s b -> Selector s (a, b)
.&&&. Selector XIOSysState Bool
theTagSoup) )
IOStateArrow s XmlTree XmlTree
-> IOStateArrow s XmlTree XmlTree -> IOStateArrow s XmlTree XmlTree
forall k (cat :: k -> k -> *) (a :: k) (b :: k) (c :: k).
Category cat =>
cat a b -> cat b c -> cat a c
>>>
String -> IOStateArrow s XmlTree XmlTree
forall s. String -> IOStateArrow s XmlTree XmlTree
setDocumentStatusFromSystemState String
"parse HTML document"
IOStateArrow s XmlTree XmlTree
-> IOStateArrow s XmlTree XmlTree -> IOStateArrow s XmlTree XmlTree
forall k (cat :: k -> k -> *) (a :: k) (b :: k) (c :: k).
Category cat =>
cat a b -> cat b c -> cat a c
>>>
IOStateArrow s XmlTree XmlTree
forall s. IOStateArrow s XmlTree XmlTree
traceTree
IOStateArrow s XmlTree XmlTree
-> IOStateArrow s XmlTree XmlTree -> IOStateArrow s XmlTree XmlTree
forall k (cat :: k -> k -> *) (a :: k) (b :: k) (c :: k).
Category cat =>
cat a b -> cat b c -> cat a c
>>>
IOStateArrow s XmlTree XmlTree
forall s. IOStateArrow s XmlTree XmlTree
traceSource
IOStateArrow s XmlTree XmlTree
-> IOStateArrow s XmlTree XmlTree -> IOStateArrow s XmlTree XmlTree
forall k (cat :: k -> k -> *) (a :: k) (b :: k) (c :: k).
Category cat =>
cat a b -> cat b c -> cat a c
>>>
IOSLA (XIOState s) XmlTree String -> IOStateArrow s XmlTree XmlTree
forall (a :: * -> * -> *) b c. ArrowList a => a b c -> a b b
perform ( String -> IOSLA (XIOState s) XmlTree String
forall (a :: * -> * -> *). ArrowXml a => String -> a XmlTree String
getAttrValue String
a_source
IOSLA (XIOState s) XmlTree String
-> IOSLA (XIOState s) String String
-> IOSLA (XIOState s) XmlTree String
forall k (cat :: k -> k -> *) (a :: k) (b :: k) (c :: k).
Category cat =>
cat a b -> cat b c -> cat a c
>>>
Int -> (String -> String) -> IOSLA (XIOState s) String String
forall b s. Int -> (b -> String) -> IOStateArrow s b b
traceValue Int
1 (\ String
src -> String
"parse HTML document " String -> String -> String
forall a. [a] -> [a] -> [a]
++ String -> String
forall a. Show a => a -> String
show String
src String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
" finished")
)
)
IOStateArrow s XmlTree XmlTree
-> IOStateArrow s XmlTree XmlTree -> IOStateArrow s XmlTree XmlTree
forall (a :: * -> * -> *) b c. ArrowIf a => a b b -> a b c -> a b b
`when` IOStateArrow s XmlTree XmlTree
forall (a :: * -> * -> *). ArrowXml a => a XmlTree XmlTree
documentStatusOk
where
parseHtml :: (Bool, Bool) -> IOSLA (XIOState s0) XmlTree XmlTree
parseHtml (Bool
withTagSoup', Bool
withExpat')
| Bool
withExpat' = IOSArrow XmlTree XmlTree -> IOSLA (XIOState s0) XmlTree XmlTree
forall b c s0. IOSArrow b c -> IOStateArrow s0 b c
withoutUserState (IOSArrow XmlTree XmlTree -> IOSLA (XIOState s0) XmlTree XmlTree)
-> IOSLA (XIOState s0) XmlTree (IOSArrow XmlTree XmlTree)
-> IOSLA (XIOState s0) XmlTree XmlTree
forall (a :: * -> * -> *) c b d.
ArrowList a =>
(c -> a b d) -> a b c -> a b d
$< Selector XIOSysState (IOSArrow XmlTree XmlTree)
-> IOSLA (XIOState s0) XmlTree (IOSArrow XmlTree XmlTree)
forall c s b. Selector XIOSysState c -> IOStateArrow s b c
getSysVar Selector XIOSysState (IOSArrow XmlTree XmlTree)
theExpatParser
| Bool
withTagSoup' = IOSArrow XmlTree XmlTree -> IOSLA (XIOState s0) XmlTree XmlTree
forall b c s0. IOSArrow b c -> IOStateArrow s0 b c
withoutUserState (IOSArrow XmlTree XmlTree -> IOSLA (XIOState s0) XmlTree XmlTree)
-> IOSLA (XIOState s0) XmlTree (IOSArrow XmlTree XmlTree)
-> IOSLA (XIOState s0) XmlTree XmlTree
forall (a :: * -> * -> *) c b d.
ArrowList a =>
(c -> a b d) -> a b c -> a b d
$< Selector XIOSysState (IOSArrow XmlTree XmlTree)
-> IOSLA (XIOState s0) XmlTree (IOSArrow XmlTree XmlTree)
forall c s b. Selector XIOSysState c -> IOStateArrow s b c
getSysVar Selector XIOSysState (IOSArrow XmlTree XmlTree)
theTagSoupParser
| Bool
otherwise = Int -> String -> IOSLA (XIOState s0) XmlTree XmlTree
forall s b. Int -> String -> IOStateArrow s b b
traceMsg Int
1 (String
"parse document with parsec HTML parser")
IOSLA (XIOState s0) XmlTree XmlTree
-> IOSLA (XIOState s0) XmlTree XmlTree
-> IOSLA (XIOState s0) XmlTree XmlTree
forall k (cat :: k -> k -> *) (a :: k) (b :: k) (c :: k).
Category cat =>
cat a b -> cat b c -> cat a c
>>>
IOSLA (XIOState s0) XmlTree XmlTree
-> IOSLA (XIOState s0) XmlTree XmlTree
forall (a :: * -> * -> *) (t :: * -> *) b.
(ArrowTree a, Tree t) =>
a (t b) (t b) -> a (t b) (t b)
replaceChildren
( ( String -> IOSLA (XIOState s0) XmlTree String
forall (a :: * -> * -> *). ArrowXml a => String -> a XmlTree String
getAttrValue String
a_source
IOSLA (XIOState s0) XmlTree String
-> IOSLA (XIOState s0) XmlTree String
-> IOSLA (XIOState s0) XmlTree (String, String)
forall (a :: * -> * -> *) b c c'.
Arrow a =>
a b c -> a b c' -> a b (c, c')
&&&
IOSLA (XIOState s0) XmlTree XmlTree
-> IOSLA (XIOState s0) XmlTree String
forall (a :: * -> * -> *) n.
ArrowXml a =>
a n XmlTree -> a n String
xshow IOSLA (XIOState s0) XmlTree XmlTree
forall (a :: * -> * -> *) (t :: * -> *) b.
(ArrowTree a, Tree t) =>
a (t b) (t b)
getChildren
)
IOSLA (XIOState s0) XmlTree (String, String)
-> IOSLA (XIOState s0) (String, String) XmlTree
-> IOSLA (XIOState s0) XmlTree XmlTree
forall k (cat :: k -> k -> *) (a :: k) (b :: k) (c :: k).
Category cat =>
cat a b -> cat b c -> cat a c
>>>
IOSLA (XIOState s0) (String, String) XmlTree
forall (a :: * -> * -> *).
ArrowList a =>
a (String, String) XmlTree
parseHtmlDoc
)
removeWarnings :: (Bool, Bool) -> IOSLA (XIOState s) XmlTree XmlTree
removeWarnings (Bool
warnings, Bool
withTagSoup')
| Bool
warnings = IOSLA (XIOState s) XmlTree XmlTree
-> IOSLA (XIOState s) XmlTree XmlTree
forall (a :: * -> * -> *).
ArrowXml a =>
a XmlTree XmlTree -> a XmlTree XmlTree
processTopDownWithAttrl
IOSLA (XIOState s) XmlTree XmlTree
forall s. IOStateArrow s XmlTree XmlTree
filterErrorMsg
| Bool
withTagSoup' = IOSLA (XIOState s) XmlTree XmlTree
forall (a :: * -> * -> *) b. ArrowList a => a b b
this
| Bool
otherwise = LA XmlTree XmlTree -> IOSLA (XIOState s) XmlTree XmlTree
forall (a :: * -> * -> *) b c. ArrowList a => LA b c -> a b c
fromLA (LA XmlTree XmlTree -> IOSLA (XIOState s) XmlTree XmlTree)
-> LA XmlTree XmlTree -> IOSLA (XIOState s) XmlTree XmlTree
forall a b. (a -> b) -> a -> b
$
[IfThen (LA XmlTree XmlTree) (LA XmlTree XmlTree)]
-> LA XmlTree XmlTree
forall b c.
[IfThen (LA (NTree b) c) (LA (NTree b) (NTree b))]
-> LA (NTree b) (NTree b)
editNTreeA [LA XmlTree XmlTree
forall (a :: * -> * -> *). ArrowXml a => a XmlTree XmlTree
isError LA XmlTree XmlTree
-> LA XmlTree XmlTree
-> IfThen (LA XmlTree XmlTree) (LA XmlTree XmlTree)
forall a b. a -> b -> IfThen a b
:-> LA XmlTree XmlTree
forall (a :: * -> * -> *) b c. ArrowList a => a b c
none]
validateDocument :: IOStateArrow s XmlTree XmlTree
validateDocument :: IOStateArrow s XmlTree XmlTree
validateDocument
= ( Int -> String -> IOStateArrow s XmlTree XmlTree
forall s b. Int -> String -> IOStateArrow s b b
traceMsg Int
1 String
"validating document"
IOStateArrow s XmlTree XmlTree
-> IOStateArrow s XmlTree XmlTree -> IOStateArrow s XmlTree XmlTree
forall k (cat :: k -> k -> *) (a :: k) (b :: k) (c :: k).
Category cat =>
cat a b -> cat b c -> cat a c
>>>
IOStateArrow s XmlTree XmlTree -> IOStateArrow s XmlTree XmlTree
forall (a :: * -> * -> *) b c. ArrowList a => a b c -> a b b
perform ( IOStateArrow s XmlTree XmlTree
forall (a :: * -> * -> *). ArrowList a => a XmlTree XmlTree
validateDoc
IOStateArrow s XmlTree XmlTree
-> IOStateArrow s XmlTree XmlTree -> IOStateArrow s XmlTree XmlTree
forall k (cat :: k -> k -> *) (a :: k) (b :: k) (c :: k).
Category cat =>
cat a b -> cat b c -> cat a c
>>>
IOStateArrow s XmlTree XmlTree
forall s. IOStateArrow s XmlTree XmlTree
filterErrorMsg
)
IOStateArrow s XmlTree XmlTree
-> IOStateArrow s XmlTree XmlTree -> IOStateArrow s XmlTree XmlTree
forall k (cat :: k -> k -> *) (a :: k) (b :: k) (c :: k).
Category cat =>
cat a b -> cat b c -> cat a c
>>>
String -> IOStateArrow s XmlTree XmlTree
forall s. String -> IOStateArrow s XmlTree XmlTree
setDocumentStatusFromSystemState String
"document validation"
IOStateArrow s XmlTree XmlTree
-> IOStateArrow s XmlTree XmlTree -> IOStateArrow s XmlTree XmlTree
forall k (cat :: k -> k -> *) (a :: k) (b :: k) (c :: k).
Category cat =>
cat a b -> cat b c -> cat a c
>>>
Int -> String -> IOStateArrow s XmlTree XmlTree
forall s b. Int -> String -> IOStateArrow s b b
traceMsg Int
1 String
"document validated, transforming doc with respect to DTD"
IOStateArrow s XmlTree XmlTree
-> IOStateArrow s XmlTree XmlTree -> IOStateArrow s XmlTree XmlTree
forall k (cat :: k -> k -> *) (a :: k) (b :: k) (c :: k).
Category cat =>
cat a b -> cat b c -> cat a c
>>>
IOStateArrow s XmlTree XmlTree
forall (a :: * -> * -> *). ArrowList a => a XmlTree XmlTree
transformDoc
IOStateArrow s XmlTree XmlTree
-> IOStateArrow s XmlTree XmlTree -> IOStateArrow s XmlTree XmlTree
forall k (cat :: k -> k -> *) (a :: k) (b :: k) (c :: k).
Category cat =>
cat a b -> cat b c -> cat a c
>>>
Int -> String -> IOStateArrow s XmlTree XmlTree
forall s b. Int -> String -> IOStateArrow s b b
traceMsg Int
1 String
"document transformed"
IOStateArrow s XmlTree XmlTree
-> IOStateArrow s XmlTree XmlTree -> IOStateArrow s XmlTree XmlTree
forall k (cat :: k -> k -> *) (a :: k) (b :: k) (c :: k).
Category cat =>
cat a b -> cat b c -> cat a c
>>>
IOStateArrow s XmlTree XmlTree
forall s. IOStateArrow s XmlTree XmlTree
traceSource
IOStateArrow s XmlTree XmlTree
-> IOStateArrow s XmlTree XmlTree -> IOStateArrow s XmlTree XmlTree
forall k (cat :: k -> k -> *) (a :: k) (b :: k) (c :: k).
Category cat =>
cat a b -> cat b c -> cat a c
>>>
IOStateArrow s XmlTree XmlTree
forall s. IOStateArrow s XmlTree XmlTree
traceTree
)
IOStateArrow s XmlTree XmlTree
-> IOStateArrow s XmlTree XmlTree -> IOStateArrow s XmlTree XmlTree
forall (a :: * -> * -> *) b c. ArrowIf a => a b b -> a b c -> a b b
`when`
IOStateArrow s XmlTree XmlTree
forall (a :: * -> * -> *). ArrowXml a => a XmlTree XmlTree
documentStatusOk
propagateAndValidateNamespaces :: IOStateArrow s XmlTree XmlTree
propagateAndValidateNamespaces :: IOStateArrow s XmlTree XmlTree
propagateAndValidateNamespaces
= ( Int -> String -> IOStateArrow s XmlTree XmlTree
forall s b. Int -> String -> IOStateArrow s b b
traceMsg Int
1 String
"propagating namespaces"
IOStateArrow s XmlTree XmlTree
-> IOStateArrow s XmlTree XmlTree -> IOStateArrow s XmlTree XmlTree
forall k (cat :: k -> k -> *) (a :: k) (b :: k) (c :: k).
Category cat =>
cat a b -> cat b c -> cat a c
>>>
IOStateArrow s XmlTree XmlTree
forall (a :: * -> * -> *). ArrowXml a => a XmlTree XmlTree
propagateNamespaces
IOStateArrow s XmlTree XmlTree
-> IOStateArrow s XmlTree XmlTree -> IOStateArrow s XmlTree XmlTree
forall k (cat :: k -> k -> *) (a :: k) (b :: k) (c :: k).
Category cat =>
cat a b -> cat b c -> cat a c
>>>
String -> IOStateArrow s XmlTree XmlTree
forall s. String -> IOStateArrow s XmlTree XmlTree
traceDoc String
"propagating namespaces done"
IOStateArrow s XmlTree XmlTree
-> IOStateArrow s XmlTree XmlTree -> IOStateArrow s XmlTree XmlTree
forall k (cat :: k -> k -> *) (a :: k) (b :: k) (c :: k).
Category cat =>
cat a b -> cat b c -> cat a c
>>>
IOStateArrow s XmlTree XmlTree
forall s. IOStateArrow s XmlTree XmlTree
andValidateNamespaces
)
IOStateArrow s XmlTree XmlTree
-> IOStateArrow s XmlTree XmlTree -> IOStateArrow s XmlTree XmlTree
forall (a :: * -> * -> *) b c. ArrowIf a => a b b -> a b c -> a b b
`when`
IOStateArrow s XmlTree XmlTree
forall (a :: * -> * -> *). ArrowXml a => a XmlTree XmlTree
documentStatusOk
andValidateNamespaces :: IOStateArrow s XmlTree XmlTree
andValidateNamespaces :: IOStateArrow s XmlTree XmlTree
andValidateNamespaces
= ( Int -> String -> IOStateArrow s XmlTree XmlTree
forall s b. Int -> String -> IOStateArrow s b b
traceMsg Int
1 String
"validating namespaces"
IOStateArrow s XmlTree XmlTree
-> IOStateArrow s XmlTree XmlTree -> IOStateArrow s XmlTree XmlTree
forall k (cat :: k -> k -> *) (a :: k) (b :: k) (c :: k).
Category cat =>
cat a b -> cat b c -> cat a c
>>>
( String -> IOStateArrow s XmlTree XmlTree
forall s. String -> IOStateArrow s XmlTree XmlTree
setDocumentStatusFromSystemState String
"namespace propagation"
IOStateArrow s XmlTree XmlTree
-> IOStateArrow s XmlTree XmlTree -> IOStateArrow s XmlTree XmlTree
forall (a :: * -> * -> *) b c. ArrowIf a => a b b -> a b c -> a b b
`when`
( IOStateArrow s XmlTree XmlTree
forall (a :: * -> * -> *). ArrowXml a => a XmlTree XmlTree
validateNamespaces IOStateArrow s XmlTree XmlTree
-> IOStateArrow s XmlTree XmlTree -> IOStateArrow s XmlTree XmlTree
forall k (cat :: k -> k -> *) (a :: k) (b :: k) (c :: k).
Category cat =>
cat a b -> cat b c -> cat a c
>>> IOStateArrow s XmlTree XmlTree -> IOStateArrow s XmlTree XmlTree
forall (a :: * -> * -> *) b c. ArrowList a => a b c -> a b b
perform IOStateArrow s XmlTree XmlTree
forall s. IOStateArrow s XmlTree XmlTree
filterErrorMsg )
)
IOStateArrow s XmlTree XmlTree
-> IOStateArrow s XmlTree XmlTree -> IOStateArrow s XmlTree XmlTree
forall k (cat :: k -> k -> *) (a :: k) (b :: k) (c :: k).
Category cat =>
cat a b -> cat b c -> cat a c
>>>
Int -> String -> IOStateArrow s XmlTree XmlTree
forall s b. Int -> String -> IOStateArrow s b b
traceMsg Int
1 String
"namespace validation finished"
)
IOStateArrow s XmlTree XmlTree
-> IOStateArrow s XmlTree XmlTree -> IOStateArrow s XmlTree XmlTree
forall (a :: * -> * -> *) b c. ArrowIf a => a b b -> a b c -> a b b
`when`
IOStateArrow s XmlTree XmlTree
forall (a :: * -> * -> *). ArrowXml a => a XmlTree XmlTree
documentStatusOk
getDocumentContents :: String -> IOStateArrow s b XmlTree
getDocumentContents :: String -> IOStateArrow s b XmlTree
getDocumentContents String
src
= [IOStateArrow s b XmlTree]
-> [IOStateArrow s b XmlTree] -> IOStateArrow s b XmlTree
forall (a :: * -> * -> *) n.
ArrowXml a =>
[a n XmlTree] -> [a n XmlTree] -> a n XmlTree
root [] []
IOStateArrow s b XmlTree
-> IOSLA (XIOState s) XmlTree XmlTree -> IOStateArrow s b XmlTree
forall k (cat :: k -> k -> *) (a :: k) (b :: k) (c :: k).
Category cat =>
cat a b -> cat b c -> cat a c
>>>
String -> String -> IOSLA (XIOState s) XmlTree XmlTree
forall (a :: * -> * -> *).
ArrowXml a =>
String -> String -> a XmlTree XmlTree
addAttr String
a_source String
src
IOSLA (XIOState s) XmlTree XmlTree
-> IOSLA (XIOState s) XmlTree XmlTree
-> IOSLA (XIOState s) XmlTree XmlTree
forall k (cat :: k -> k -> *) (a :: k) (b :: k) (c :: k).
Category cat =>
cat a b -> cat b c -> cat a c
>>>
Int -> String -> IOSLA (XIOState s) XmlTree XmlTree
forall s b. Int -> String -> IOStateArrow s b b
traceMsg Int
1 (String
"readDocument: start processing document " String -> String -> String
forall a. [a] -> [a] -> [a]
++ String -> String
forall a. Show a => a -> String
show String
src)
IOSLA (XIOState s) XmlTree XmlTree
-> IOSLA (XIOState s) XmlTree XmlTree
-> IOSLA (XIOState s) XmlTree XmlTree
forall k (cat :: k -> k -> *) (a :: k) (b :: k) (c :: k).
Category cat =>
cat a b -> cat b c -> cat a c
>>>
IOSLA (XIOState s) XmlTree XmlTree
forall s. IOStateArrow s XmlTree XmlTree
getXmlContents
validateDoc :: ArrowList a => a XmlTree XmlTree
validateDoc :: a XmlTree XmlTree
validateDoc = LA XmlTree XmlTree -> a XmlTree XmlTree
forall (a :: * -> * -> *) b c. ArrowList a => LA b c -> a b c
fromLA ( LA XmlTree XmlTree
validate
LA XmlTree XmlTree -> LA XmlTree XmlTree -> LA XmlTree XmlTree
forall (a :: * -> * -> *) b c. ArrowIf a => a b b -> a b c -> a b b
`when`
LA XmlTree XmlTree
getDTDSubset
)
transformDoc :: ArrowList a => a XmlTree XmlTree
transformDoc :: a XmlTree XmlTree
transformDoc = LA XmlTree XmlTree -> a XmlTree XmlTree
forall (a :: * -> * -> *) b c. ArrowList a => LA b c -> a b c
fromLA LA XmlTree XmlTree
transform