module Text.XML.HXT.Arrow.XmlState.ErrorHandling
where
import Control.Arrow                            
import Control.Arrow.ArrowList
import Control.Arrow.ArrowIf
import Control.Arrow.ArrowTree
import Control.Arrow.ArrowIO
import Control.Exception                ( SomeException )
import Data.Maybe
import Text.XML.HXT.DOM.Interface
import Text.XML.HXT.Arrow.XmlArrow
import Text.XML.HXT.Arrow.XmlState.TypeDefs
import System.IO                        ( hPutStrLn
                                        , hFlush
                                        , stderr
                                        )
changeErrorStatus       :: (Int -> Int -> Int) -> IOStateArrow s Int Int
changeErrorStatus :: (Int -> Int -> Int) -> IOStateArrow s Int Int
changeErrorStatus Int -> Int -> Int
f     = Selector XIOSysState Int
-> (Int -> Int -> Int) -> IOStateArrow s Int Int
forall c b s.
Selector XIOSysState c -> (b -> c -> c) -> IOStateArrow s b b
chgSysVar Selector XIOSysState Int
theErrorStatus Int -> Int -> Int
f
clearErrStatus          :: IOStateArrow s b b
clearErrStatus :: IOStateArrow s b b
clearErrStatus          = SysConfig -> IOStateArrow s b b
forall s c. SysConfig -> IOStateArrow s c c
configSysVar (SysConfig -> IOStateArrow s b b)
-> SysConfig -> IOStateArrow s b b
forall a b. (a -> b) -> a -> b
$ Selector XIOSysState Int -> Int -> SysConfig
forall s a. Selector s a -> a -> s -> s
setS Selector XIOSysState Int
theErrorStatus Int
0
setErrStatus            :: IOStateArrow s Int Int
setErrStatus :: IOStateArrow s Int Int
setErrStatus            = (Int -> Int -> Int) -> IOStateArrow s Int Int
forall s. (Int -> Int -> Int) -> IOStateArrow s Int Int
changeErrorStatus Int -> Int -> Int
forall a. Ord a => a -> a -> a
max
getErrStatus            :: IOStateArrow s XmlTree Int
getErrStatus :: IOStateArrow s XmlTree Int
getErrStatus            = Selector XIOSysState Int -> IOStateArrow s XmlTree Int
forall c s b. Selector XIOSysState c -> IOStateArrow s b c
getSysVar Selector XIOSysState Int
theErrorStatus
setErrMsgStatus         :: IOStateArrow s XmlTree XmlTree
setErrMsgStatus :: IOStateArrow s XmlTree XmlTree
setErrMsgStatus         = IOSLA (XIOState s) XmlTree Int -> IOStateArrow s XmlTree XmlTree
forall (a :: * -> * -> *) b c. ArrowList a => a b c -> a b b
perform
                          ( IOSLA (XIOState s) XmlTree Int
forall (a :: * -> * -> *). ArrowXml a => a XmlTree Int
getErrorLevel IOSLA (XIOState s) XmlTree Int
-> IOSLA (XIOState s) Int Int -> IOSLA (XIOState s) XmlTree Int
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) Int Int
forall s. IOStateArrow s Int Int
setErrStatus )
setErrorMsgHandler      :: Bool -> (String -> IO ()) -> IOStateArrow s b b
setErrorMsgHandler :: Bool -> (String -> IO ()) -> IOStateArrow s b b
setErrorMsgHandler Bool
c String -> IO ()
f  = SysConfig -> IOStateArrow s b b
forall s c. SysConfig -> IOStateArrow s c c
configSysVar (SysConfig -> IOStateArrow s b b)
-> SysConfig -> IOStateArrow s b b
forall a b. (a -> b) -> a -> b
$ Selector XIOSysState (Bool, String -> IO ())
-> (Bool, String -> IO ()) -> SysConfig
forall s a. Selector s a -> a -> s -> s
setS (Selector XIOSysState Bool
theErrorMsgCollect Selector XIOSysState Bool
-> Selector XIOSysState (String -> IO ())
-> Selector XIOSysState (Bool, String -> IO ())
forall s a b. Selector s a -> Selector s b -> Selector s (a, b)
.&&&. Selector XIOSysState (String -> IO ())
theErrorMsgHandler) (Bool
c, String -> IO ()
f)
sysErrorMsg             :: IOStateArrow s XmlTree XmlTree
sysErrorMsg :: IOStateArrow s XmlTree XmlTree
sysErrorMsg             = IOSLA (XIOState s) XmlTree () -> IOStateArrow s XmlTree XmlTree
forall (a :: * -> * -> *) b c. ArrowList a => a b c -> a b b
perform
                          ( IOSLA (XIOState s) XmlTree Int
forall (a :: * -> * -> *). ArrowXml a => a XmlTree Int
getErrorLevel IOSLA (XIOState s) XmlTree Int
-> IOSLA (XIOState s) XmlTree String
-> IOSLA (XIOState s) XmlTree (Int, String)
forall (a :: * -> * -> *) b c c'.
Arrow a =>
a b c -> a b c' -> a b (c, c')
&&& IOSLA (XIOState s) XmlTree String
forall (a :: * -> * -> *). ArrowXml a => a XmlTree String
getErrorMsg
                            IOSLA (XIOState s) XmlTree (Int, String)
-> IOSLA (XIOState s) (Int, String) ()
-> IOSLA (XIOState s) 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) -> String)
-> IOSLA (XIOState s) (Int, String) String
forall (a :: * -> * -> *) b c. Arrow a => (b -> c) -> a b c
arr (Int, String) -> String
formatErrorMsg
                            IOSLA (XIOState s) (Int, String) String
-> IOSLA (XIOState s) String ()
-> IOSLA (XIOState s) (Int, String) ()
forall k (cat :: k -> k -> *) (a :: k) (b :: k) (c :: k).
Category cat =>
cat a b -> cat b c -> cat a c
>>>
                            Selector XIOSysState (String -> IO ())
-> IOStateArrow s String (String -> IO ())
forall c s b. Selector XIOSysState c -> IOStateArrow s b c
getSysVar Selector XIOSysState (String -> IO ())
theErrorMsgHandler IOStateArrow s String (String -> IO ())
-> IOSLA (XIOState s) String String
-> IOSLA (XIOState s) String (String -> IO (), String)
forall (a :: * -> * -> *) b c c'.
Arrow a =>
a b c -> a b c' -> a b (c, c')
&&& IOSLA (XIOState s) String String
forall (a :: * -> * -> *) b. ArrowList a => a b b
this
                            IOSLA (XIOState s) String (String -> IO (), String)
-> IOSLA (XIOState s) (String -> IO (), String) ()
-> IOSLA (XIOState s) String ()
forall k (cat :: k -> k -> *) (a :: k) (b :: k) (c :: k).
Category cat =>
cat a b -> cat b c -> cat a c
>>>
                            ((String -> IO (), String) -> IO ())
-> IOSLA (XIOState s) (String -> IO (), String) ()
forall (a :: * -> * -> *) b c. ArrowIO a => (b -> IO c) -> a b c
arrIO (\ (String -> IO ()
h, String
msg) -> String -> IO ()
h String
msg)
                          )
    where
    formatErrorMsg :: (Int, String) -> String
formatErrorMsg (Int
level, String
msg) = String
"\n" String -> String -> String
forall a. [a] -> [a] -> [a]
++ Int -> String
errClass Int
level String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
": " String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
msg
    errClass :: Int -> String
errClass Int
l          = String -> Maybe String -> String
forall a. a -> Maybe a -> a
fromMaybe String
"fatal error" (Maybe String -> String)
-> ([(Int, String)] -> Maybe String) -> [(Int, String)] -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> [(Int, String)] -> Maybe String
forall a b. Eq a => a -> [(a, b)] -> Maybe b
lookup Int
l ([(Int, String)] -> String) -> [(Int, String)] -> String
forall a b. (a -> b) -> a -> b
$ [(Int, String)]
msgList
        where
        msgList :: [(Int, String)]
msgList         = [ (Int
c_ok,      String
"no error")
                          , (Int
c_warn,    String
"warning")
                          , (Int
c_err,     String
"error")
                          , (Int
c_fatal,   String
"fatal error")
                          ]
errorMsgStderr          :: IOStateArrow s b b
errorMsgStderr :: IOStateArrow s b b
errorMsgStderr          = Bool -> (String -> IO ()) -> IOStateArrow s b b
forall s b. Bool -> (String -> IO ()) -> IOStateArrow s b b
setErrorMsgHandler Bool
False (\ String
x ->
                                                    do Handle -> String -> IO ()
hPutStrLn Handle
stderr String
x
                                                       Handle -> IO ()
hFlush    Handle
stderr
                                                   )
errorMsgCollect         :: IOStateArrow s b b
errorMsgCollect :: IOStateArrow s b b
errorMsgCollect         = Bool -> (String -> IO ()) -> IOStateArrow s b b
forall s b. Bool -> (String -> IO ()) -> IOStateArrow s b b
setErrorMsgHandler Bool
True (IO () -> String -> IO ()
forall a b. a -> b -> a
const (IO () -> String -> IO ()) -> IO () -> String -> IO ()
forall a b. (a -> b) -> a -> b
$ () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ())
errorMsgStderrAndCollect        :: IOStateArrow s b b
errorMsgStderrAndCollect :: IOStateArrow s b b
errorMsgStderrAndCollect        = Bool -> (String -> IO ()) -> IOStateArrow s b b
forall s b. Bool -> (String -> IO ()) -> IOStateArrow s b b
setErrorMsgHandler Bool
True (Handle -> String -> IO ()
hPutStrLn Handle
stderr)
errorMsgIgnore          :: IOStateArrow s b b
errorMsgIgnore :: IOStateArrow s b b
errorMsgIgnore          = Bool -> (String -> IO ()) -> IOStateArrow s b b
forall s b. Bool -> (String -> IO ()) -> IOStateArrow s b b
setErrorMsgHandler Bool
False (IO () -> String -> IO ()
forall a b. a -> b -> a
const (IO () -> String -> IO ()) -> IO () -> String -> IO ()
forall a b. (a -> b) -> a -> b
$ () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ())
getErrorMessages        :: IOStateArrow s b XmlTree
getErrorMessages :: IOStateArrow s b XmlTree
getErrorMessages        = Selector XIOSysState XmlTrees -> IOStateArrow s b XmlTrees
forall c s b. Selector XIOSysState c -> IOStateArrow s b c
getSysVar Selector XIOSysState XmlTrees
theErrorMsgList
                          IOStateArrow s b XmlTrees
-> IOSLA (XIOState s) XmlTrees 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
>>>
                          SysConfig -> IOStateArrow s XmlTrees XmlTrees
forall s c. SysConfig -> IOStateArrow s c c
configSysVar (Selector XIOSysState XmlTrees -> XmlTrees -> SysConfig
forall s a. Selector s a -> a -> s -> s
setS Selector XIOSysState XmlTrees
theErrorMsgList [])
                          IOStateArrow s XmlTrees XmlTrees
-> IOSLA (XIOState s) XmlTrees XmlTree
-> IOSLA (XIOState s) XmlTrees XmlTree
forall k (cat :: k -> k -> *) (a :: k) (b :: k) (c :: k).
Category cat =>
cat a b -> cat b c -> cat a c
>>>
                          (XmlTrees -> XmlTrees) -> IOSLA (XIOState s) XmlTrees XmlTree
forall (a :: * -> * -> *) b c. ArrowList a => (b -> [c]) -> a b c
arrL XmlTrees -> XmlTrees
forall a. [a] -> [a]
reverse
addToErrorMsgList       :: IOStateArrow s XmlTree XmlTree
addToErrorMsgList :: IOStateArrow s XmlTree XmlTree
addToErrorMsgList       = Selector XIOSysState (Bool, XmlTrees)
-> (XmlTree -> (Bool, XmlTrees) -> (Bool, XmlTrees))
-> IOStateArrow s XmlTree XmlTree
forall c b s.
Selector XIOSysState c -> (b -> c -> c) -> IOStateArrow s b b
chgSysVar
                          ( Selector XIOSysState Bool
theErrorMsgCollect Selector XIOSysState Bool
-> Selector XIOSysState XmlTrees
-> Selector XIOSysState (Bool, XmlTrees)
forall s a b. Selector s a -> Selector s b -> Selector s (a, b)
.&&&. Selector XIOSysState XmlTrees
theErrorMsgList )
                          ( \ XmlTree
e (Bool
cs, XmlTrees
es) -> (Bool
cs, if Bool
cs then XmlTree
e XmlTree -> XmlTrees -> XmlTrees
forall a. a -> [a] -> [a]
: XmlTrees
es else XmlTrees
es) )
filterErrorMsg          :: IOStateArrow s XmlTree XmlTree
filterErrorMsg :: IOStateArrow s XmlTree XmlTree
filterErrorMsg          = ( IOStateArrow s XmlTree XmlTree
forall s. IOStateArrow s XmlTree XmlTree
setErrMsgStatus
                            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
sysErrorMsg
                            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
addToErrorMsgList
                            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 :: * -> * -> *) b c. ArrowList a => a b c
none
                          )
                          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
isError
issueWarn               :: String -> IOStateArrow s b b
issueWarn :: String -> IOStateArrow s b b
issueWarn String
msg           = IOSLA (XIOState s) b XmlTree -> IOStateArrow s b b
forall (a :: * -> * -> *) b c. ArrowList a => a b c -> a b b
perform (String -> IOSLA (XIOState s) b XmlTree
forall (a :: * -> * -> *) n. ArrowXml a => String -> a n XmlTree
warn String
msg  IOSLA (XIOState s) b XmlTree
-> IOSLA (XIOState s) XmlTree XmlTree
-> IOSLA (XIOState 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
>>> IOSLA (XIOState s) XmlTree XmlTree
forall s. IOStateArrow s XmlTree XmlTree
filterErrorMsg)
issueErr                :: String -> IOStateArrow s b b
issueErr :: String -> IOStateArrow s b b
issueErr String
msg            = IOSLA (XIOState s) b XmlTree -> IOStateArrow s b b
forall (a :: * -> * -> *) b c. ArrowList a => a b c -> a b b
perform (String -> IOSLA (XIOState s) b XmlTree
forall (a :: * -> * -> *) n. ArrowXml a => String -> a n XmlTree
err String
msg   IOSLA (XIOState s) b XmlTree
-> IOSLA (XIOState s) XmlTree XmlTree
-> IOSLA (XIOState 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
>>> IOSLA (XIOState s) XmlTree XmlTree
forall s. IOStateArrow s XmlTree XmlTree
filterErrorMsg)
issueFatal              :: String -> IOStateArrow s b b
issueFatal :: String -> IOStateArrow s b b
issueFatal String
msg          = IOSLA (XIOState s) b XmlTree -> IOStateArrow s b b
forall (a :: * -> * -> *) b c. ArrowList a => a b c -> a b b
perform (String -> IOSLA (XIOState s) b XmlTree
forall (a :: * -> * -> *) n. ArrowXml a => String -> a n XmlTree
fatal String
msg IOSLA (XIOState s) b XmlTree
-> IOSLA (XIOState s) XmlTree XmlTree
-> IOSLA (XIOState 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
>>> IOSLA (XIOState s) XmlTree XmlTree
forall s. IOStateArrow s XmlTree XmlTree
filterErrorMsg)
issueExc                :: String -> IOStateArrow s SomeException b
issueExc :: String -> IOStateArrow s SomeException b
issueExc String
m              = ( String -> IOStateArrow s SomeException SomeException
forall s b. String -> IOStateArrow s b b
issueFatal (String -> IOStateArrow s SomeException SomeException)
-> IOSLA (XIOState s) SomeException String
-> IOStateArrow s SomeException SomeException
forall (a :: * -> * -> *) c b d.
ArrowList a =>
(c -> a b d) -> a b c -> a b d
$< (SomeException -> String)
-> IOSLA (XIOState s) SomeException String
forall (a :: * -> * -> *) b c. Arrow a => (b -> c) -> a b c
arr  ((String
msg String -> String -> String
forall a. [a] -> [a] -> [a]
++) (String -> String)
-> (SomeException -> String) -> SomeException -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SomeException -> String
forall a. Show a => a -> String
show) )
                          IOStateArrow s SomeException SomeException
-> IOStateArrow s SomeException b -> IOStateArrow s SomeException b
forall k (cat :: k -> k -> *) (a :: k) (b :: k) (c :: k).
Category cat =>
cat a b -> cat b c -> cat a c
>>>
                          IOStateArrow s SomeException b
forall (a :: * -> * -> *) b c. ArrowList a => a b c
none
    where
    msg :: String
msg | String -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null String
m        = String
"Exception: "
        | Bool
otherwise     = String
"Exception in " String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
m String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
": "
setDocumentStatus       :: Int -> String -> IOStateArrow s XmlTree XmlTree
setDocumentStatus :: Int -> String -> IOStateArrow s XmlTree XmlTree
setDocumentStatus Int
level String
msg
                        = ( IOStateArrow s XmlTree XmlTree -> IOStateArrow s XmlTree XmlTree
forall (a :: * -> * -> *).
ArrowXml a =>
a XmlTree XmlTree -> a XmlTree XmlTree
addAttrl ( String -> String -> IOStateArrow s XmlTree XmlTree
forall (a :: * -> * -> *) n.
ArrowXml a =>
String -> String -> a n XmlTree
sattr String
a_status (Int -> String
forall a. Show a => a -> String
show Int
level)
                                       IOStateArrow s XmlTree XmlTree
-> IOStateArrow s XmlTree XmlTree -> IOStateArrow s XmlTree XmlTree
forall (a :: * -> * -> *) b c.
ArrowPlus a =>
a b c -> a b c -> a b c
<+>
                                       String -> String -> IOStateArrow s XmlTree XmlTree
forall (a :: * -> * -> *) n.
ArrowXml a =>
String -> String -> a n XmlTree
sattr String
a_module String
msg
                                     )
                            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 Int
level Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= Int
c_err
                              then XmlTrees -> IOStateArrow s XmlTree XmlTree
forall (a :: * -> * -> *) (t :: * -> *) b.
(ArrowTree a, Tree t) =>
[t b] -> a (t b) (t b)
setChildren []
                              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
isRoot
setDocumentStatusFromSystemState        :: String -> IOStateArrow s XmlTree XmlTree
setDocumentStatusFromSystemState :: String -> IOStateArrow s XmlTree XmlTree
setDocumentStatusFromSystemState String
msg
                                = Int -> IOStateArrow s XmlTree XmlTree
forall s. Int -> IOSLA (XIOState s) XmlTree XmlTree
setStatus (Int -> IOStateArrow s XmlTree XmlTree)
-> IOSLA (XIOState s) XmlTree Int -> IOStateArrow s XmlTree XmlTree
forall (a :: * -> * -> *) c b d.
ArrowList a =>
(c -> a b d) -> a b c -> a b d
$< IOSLA (XIOState s) XmlTree Int
forall s. IOStateArrow s XmlTree Int
getErrStatus
    where
    setStatus :: Int -> IOSLA (XIOState s) XmlTree XmlTree
setStatus Int
level
        | Int
level Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<= Int
c_warn       = IOSLA (XIOState s) XmlTree XmlTree
forall (a :: * -> * -> *) b. ArrowList a => a b b
this
        | Bool
otherwise             = Int -> String -> IOSLA (XIOState s) XmlTree XmlTree
forall s. Int -> String -> IOStateArrow s XmlTree XmlTree
setDocumentStatus Int
level String
msg
documentStatusOk        :: ArrowXml a => a XmlTree XmlTree
documentStatusOk :: a XmlTree XmlTree
documentStatusOk        = a XmlTree XmlTree
forall (a :: * -> * -> *). ArrowXml a => a XmlTree XmlTree
isRoot
                          a XmlTree XmlTree -> a XmlTree XmlTree -> a 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 -> a XmlTree String
forall (a :: * -> * -> *). ArrowXml a => String -> a XmlTree String
getAttrValue String
a_status
                             a XmlTree String -> a String String -> a XmlTree String
forall k (cat :: k -> k -> *) (a :: k) (b :: k) (c :: k).
Category cat =>
cat a b -> cat b c -> cat a c
>>>
                             (String -> Bool) -> a String String
forall (a :: * -> * -> *) b. ArrowList a => (b -> Bool) -> a b b
isA (\ String
v -> String -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null String
v Bool -> Bool -> Bool
|| ((String -> Int
forall a. Read a => String -> a
read String
v)::Int) Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<= Int
c_warn)
                            )
                            a XmlTree String -> a XmlTree XmlTree -> a XmlTree XmlTree
forall (a :: * -> * -> *) b c d.
ArrowIf a =>
a b c -> a b d -> a b d
`guards`
                            a XmlTree XmlTree
forall (a :: * -> * -> *) b. ArrowList a => a b b
this
                          )
errorOutputToStderr     :: String -> IO ()
errorOutputToStderr :: String -> IO ()
errorOutputToStderr String
msg
                        = do
                          Handle -> String -> IO ()
hPutStrLn Handle
stderr String
msg
                          Handle -> IO ()
hFlush Handle
stderr