module Main where import Text.XML.Expat.Tree import Text.XML.Expat.Pickle import qualified Data.ByteString as B import Data.ByteString.Internal (c2w, w2c) import qualified Data.ByteString.Lazy as L import Control.Monad infiniteDoc = ""++body 1 where body i = "\n "++body (i+1) toBL :: String -> L.ByteString toBL = L.fromChunks . chunkify where chunkify [] = [] chunkify str = let (start, rem) = splitAt 1024 str in (B.pack $ map c2w start):chunkify rem infiniteBL = toBL infiniteDoc xpItems :: PU (UNodes String) [Int] xpItems = xpElemNodes "infinite" $ xpList0 $ xpElemAttrs "item" $ xpAttr "idx" $ xpWrapEither (\i -> if i == 5000 then Left "5000 is evil" else Right i, id) $ xpickle main = do print $ unpickleXML Nothing (xpRoot xpItems) infiniteBL