module Text.XML.HXT.Arrow.DocumentOutput
( putXmlDocument
, putXmlTree
, putXmlSource
, encodeDocument
, encodeDocument'
)
where
import Control.Arrow
import Control.Arrow.ArrowExc
import Control.Arrow.ArrowIf
import Control.Arrow.ArrowIO
import Control.Arrow.ArrowList
import Control.Arrow.ArrowTree
import Control.Arrow.ListArrow
import qualified Data.ByteString.Lazy as BS
import Data.Maybe
import Data.String.Unicode (getOutputEncodingFct')
import Text.XML.HXT.DOM.Interface
import qualified Text.XML.HXT.DOM.ShowXml as XS
import Text.XML.HXT.Arrow.Edit (addHeadlineToXmlDoc,
addXmlPi,
addXmlPiEncoding,
escapeHtmlRefs,
escapeXmlRefs, indentDoc,
numberLinesInXmlDoc,
treeRepOfXmlDoc)
import Text.XML.HXT.Arrow.XmlArrow
import Text.XML.HXT.Arrow.XmlState
import Text.XML.HXT.Arrow.XmlState.TypeDefs
import System.IO (Handle, IOMode (..),
hClose, hPutStrLn,
hSetBinaryMode,
openBinaryFile, openFile,
stdout)
putXmlDocument :: Bool -> String -> IOStateArrow s XmlTree XmlTree
putXmlDocument textMode dst
= perform putDoc
where
putDoc
= ( if textMode
then ( xshow getChildren
>>>
tryA (arrIO (\ s -> hPutDocument (\h -> hPutStrLn h s)))
)
else ( xshowBlob getChildren
>>>
tryA (arrIO (\ s -> hPutDocument (\h -> do BS.hPutStr h s
BS.hPutStr h (stringToBlob "\n")
)
)
)
)
)
>>>
( ( traceMsg 1 ("io error, document not written to " ++ outFile)
>>>
arr show >>> mkError c_fatal
>>>
filterErrorMsg
)
|||
( traceMsg 2 ("document written to " ++ outFile ++ ", textMode = " ++ show textMode)
>>>
none
)
)
where
isStdout = null dst || dst == "-"
outFile = if isStdout
then "stdout"
else show dst
hPutDocument :: (Handle -> IO ()) -> IO ()
hPutDocument action
| isStdout
= do
hSetBinaryMode stdout (not textMode)
action stdout
hSetBinaryMode stdout False
| otherwise
= do
handle <- ( if textMode
then openFile
else openBinaryFile
) dst WriteMode
action handle
hClose handle
putXmlTree :: String -> IOStateArrow s XmlTree XmlTree
putXmlTree dst
= perform ( treeRepOfXmlDoc
>>>
addHeadlineToXmlDoc
>>>
putXmlDocument True dst
)
putXmlSource :: String -> IOStateArrow s XmlTree XmlTree
putXmlSource dst
= perform ( (this ) `whenNot` isRoot
>>>
indentDoc
>>>
numberLinesInXmlDoc
>>>
addHeadlineToXmlDoc
>>>
putXmlDocument True dst
)
getEncodingParam :: IOStateArrow s XmlTree String
getEncodingParam
= catA [ getSysVar theOutputEncoding
, getSysVar theInputEncoding
, constA utf8
]
>. (head . filter (not . null))
getOutputEncoding :: String -> IOStateArrow s XmlTree String
getOutputEncoding defaultEnc
= getEC $< getEncodingParam
where
getEC enc' = fromLA $ getOutputEncoding' defaultEnc enc'
encodeDocument :: Bool -> Bool -> String -> IOStateArrow s XmlTree XmlTree
encodeDocument quoteXml supressXmlPi defaultEnc
= encode $< getOutputEncoding defaultEnc
where
encode enc
= traceMsg 2 ("encodeDocument: encoding is " ++ show enc)
>>>
( encodeDocument' quoteXml supressXmlPi enc
`orElse`
( issueFatal ("encoding scheme not supported: " ++ show enc)
>>>
setDocumentStatusFromSystemState "encoding document"
)
)
isBinaryDoc :: LA XmlTree XmlTree
isBinaryDoc = ( ( getAttrValue transferMimeType >>^ stringToLower )
>>>
isA (\ t -> not (null t || isTextMimeType t || isXmlMimeType t))
)
`guards` this
getOutputEncoding' :: String -> String -> LA XmlTree String
getOutputEncoding' defaultEnc defaultEnc2
= catA [ isBinaryDoc
>>>
constA isoLatin1
, getChildren
>>>
( ( isPi >>> hasName t_xml )
`guards`
getAttrValue a_encoding
)
, constA defaultEnc
, getAttrValue a_output_encoding
, constA defaultEnc2
]
>. (head . filter (not . null))
encodeDocument' :: ArrowXml a => Bool -> Bool -> String -> a XmlTree XmlTree
encodeDocument' quoteXml supressXmlPi defaultEnc
= fromLA (encode $< getOutputEncoding' defaultEnc utf8)
where
encode :: String -> LA XmlTree XmlTree
encode encodingScheme
| encodingScheme == unicodeString
= replaceChildren
( (getChildren >. XS.xshow'' cQuot aQuot)
>>>
mkText
)
| isNothing encodeFct
= none
| otherwise
= ( if supressXmlPi
then processChildren (none `when` isXmlPi)
else ( addXmlPi
>>>
addXmlPiEncoding encodingScheme
)
)
>>>
( isLatin1Blob
`orElse`
encodeDoc (fromJust encodeFct)
)
>>>
addAttr a_output_encoding encodingScheme
where
(cQuot, aQuot)
| quoteXml = escapeXmlRefs
| otherwise = escapeHtmlRefs
encodeFct = getOutputEncodingFct' encodingScheme
encodeDoc ef = replaceChildren
( xshowBlobWithEnc cQuot aQuot ef getChildren
>>>
mkBlob
)
xshowBlobWithEnc cenc aenc enc f
= f >. XS.xshow' cenc aenc enc
isLatin1Blob
| encodingScheme /= isoLatin1
= none
| otherwise = childIsSingleBlob `guards` this
where
childIsSingleBlob
= listA getChildren
>>>
isA (length >>> (== 1))
>>>
unlistA
>>>
isBlob