You can not select more than 25 topics Topics must start with a letter or number, can include dashes ('-') and can be up to 35 characters long.

89 lines
3.2 KiB

{-# OPTIONS_HADDOCK hide #-}
14 years ago
module Text.XML.Stream.Elements where
import Control.Applicative ((<$>))
import Control.Monad.Trans.Class
import Control.Monad.Trans.Resource as R
14 years ago
import qualified Data.ByteString as BS
import qualified Data.Text as Text
import qualified Data.Text.Encoding as Text
import Data.XML.Types
import qualified Text.XML.Stream.Render as TXSR
import Text.XML.Unresolved as TXU
14 years ago
import Data.Conduit as C
import Data.Conduit.List as CL
14 years ago
import System.IO.Unsafe(unsafePerformIO)
14 years ago
compressNodes :: [Node] -> [Node]
compressNodes [] = []
compressNodes [x] = [x]
compressNodes (NodeContent (ContentText x) : NodeContent (ContentText y) : z) =
compressNodes $ NodeContent (ContentText $ x `Text.append` y) : z
14 years ago
compressNodes (x:xs) = x : compressNodes xs
elements :: R.MonadThrow m => C.Conduit Event m Element
elements = do
x <- C.await
14 years ago
case x of
Just (EventBeginElement n as) -> do
goE n as >>= C.yield
elements
Nothing -> return ()
14 years ago
_ -> lift $ R.monadThrow $ InvalidEventStream $ "not an element: " ++ show x
where
many' f =
14 years ago
go id
where
go front = do
x <- f
case x of
Left x -> return $ (x, front [])
Right y -> go (front . (:) y)
14 years ago
goE n as = do
(y, ns) <- many' goN
14 years ago
if y == Just (EventEndElement n)
then return $ Element n as $ compressNodes ns
else lift $ R.monadThrow $ InvalidEventStream $ "Missing end element for " ++ show n ++ ", got: " ++ show y
goN = do
x <- await
14 years ago
case x of
Just (EventBeginElement n as) -> (Right . NodeElement) <$> goE n as
Just (EventInstruction i) -> return $ Right $ NodeInstruction i
Just (EventContent c) -> return $ Right $ NodeContent c
Just (EventComment t) -> return $ Right $ NodeComment t
Just (EventCDATA t) -> return $ Right $ NodeContent $ ContentText t
_ -> return $ Left x
14 years ago
openElementToEvents :: Element -> [Event]
openElementToEvents (Element name as ns) = EventBeginElement name as : goN ns []
where
goE (Element name' as' ns') =
(EventBeginElement name' as' :)
. goN ns'
. (EventEndElement name' :)
14 years ago
goN [] = id
goN [x] = goN' x
goN (x:xs) = goN' x . goN xs
goN' (NodeElement e) = goE e
goN' (NodeInstruction i) = (EventInstruction i :)
goN' (NodeContent c) = (EventContent c :)
goN' (NodeComment t) = (EventComment t :)
elementToEvents :: Element -> [Event]
elementToEvents e@(Element name _ _) = openElementToEvents e ++ [EventEndElement name]
renderOpenElement :: Element -> BS.ByteString
renderOpenElement e = Text.encodeUtf8 . Text.concat . unsafePerformIO
$ CL.sourceList (openElementToEvents e) $$ TXSR.renderText def =$ CL.consume
renderElement :: Element -> BS.ByteString
renderElement e = Text.encodeUtf8 . Text.concat . unsafePerformIO
$ CL.sourceList (elementToEvents e) $$ TXSR.renderText def =$ CL.consume
ppElement :: Element -> String
ppElement = Text.unpack . Text.decodeUtf8 . renderElement