\section{Misc. utilities} A few special-case utilities that are used by similar libraries, or were present in previous versions of {\tt enumerator}, or otherwise don't have a good place to go. :d Data.Enumerator exports -- * Misc. utilities : \subsection{Enumeratees} Sequencing a fixed set of enumerators is easy, but for more complex cases, it's useful to have a small utility wrapper. :f Data/Enumerator.hs |apidoc Data.Enumerator.concatEnums| concatEnums :: Monad m => [Enumerator a m b] -> Enumerator a m b concatEnums = Prelude.foldl (>==>) returnI : :d Data.Enumerator exports , concatEnums : {\tt joinI} is used to ``flatten'' enumeratees, to transform them into an {\tt Iteratee}. :f Data/Enumerator.hs |apidoc Data.Enumerator.joinI| joinI :: Monad m => Iteratee a m (Step a' m b) -> Iteratee a m b joinI outer = outer >>= check where check (Continue k) = k EOF >>== \s -> case s of Continue _ -> error "joinI: divergent iteratee" _ -> check s check (Yield x _) = return x check (Error e) = throwError e : {\tt joinE} is similar, except it flattens an enumerator/enumeratee pair into a single enumerator. :f Data/Enumerator.hs |apidoc Data.Enumerator.joinE| joinE :: Monad m => Enumerator ao m (Step ai m b) -> Enumeratee ao ai m b -> Enumerator ai m b joinE enum enee s = Iteratee $ do step <- runIteratee (enumEOF $$ enum $$ enee s) case step of Error err -> return (Error err) Yield x _ -> return x Continue _ -> error "joinE: divergent iteratee" : {\tt sequence} repeatedly runs its parameter to transform the stream. :f Data/Enumerator.hs |apidoc Data.Enumerator.sequence| sequence :: Monad m => Iteratee ao m ai -> Enumeratee ao ai m b sequence i = loop where loop = checkDone check check k = isEOF >>= \f -> if f then yield (Continue k) EOF else step k step k = i >>= \v -> k (Chunks [v]) >>== loop : Another small, useful enumerator separates an input list into chunks, and sends them to the iteratee. This is useful for testing iteratees in pure code. :d Data.Enumerator imports import Data.List (genericSplitAt) : :f Data/Enumerator.hs |apidoc Data.Enumerator.enumList| enumList :: Monad m => Integer -> [a] -> Enumerator a m b enumList n = loop where loop xs (Continue k) | not (null xs) = let (s1, s2) = genericSplitAt n xs in k (Chunks s1) >>== loop s2 loop _ step = returnI step : :d Data.Enumerator exports , joinI , joinE , Data.Enumerator.sequence , enumList : \subsection{Running iteratees} To simplify running iteratees, {\tt run} sends {\tt EOF} and then examines the result. It is not possible for the result to be {\tt Continue}, because {\tt enumEOF} calls {\tt error} for divergent iteratees. :f Data/Enumerator.hs |apidoc Data.Enumerator.run| run :: Monad m => Iteratee a m b -> m (Either Exc.SomeException b) run i = do mStep <- runIteratee $ enumEOF ==<< i case mStep of Error err -> return $ Left err Yield x _ -> return $ Right x Continue _ -> error "run: divergent iteratee" : :f Data/Enumerator.hs |apidoc Data.Enumerator.enumEOF| enumEOF :: Monad m => Enumerator a m b enumEOF (Yield x _) = yield x EOF enumEOF (Error err) = throwError err enumEOF (Continue k) = k EOF >>== check where check (Continue _) = error "enumEOF: divergent iteratee" check s = enumEOF s : {\tt run\_} is even more simplified; it's used in simple scripts, where the user doesn't care about error handling. :f Data/Enumerator.hs |apidoc Data.Enumerator.run_| run_ :: Monad m => Iteratee a m b -> m b run_ i = run i >>= either Exc.throw return : :d Data.Enumerator exports , enumEOF , run , run_ : \subsection{{\tt checkDone} and {\tt checkDoneEx}} A common pattern in {\tt Enumeratee} implementations is to check whether the inner {\tt Iteratee} has finished, and if so, to return its output. {\tt checkDone} passes its parameter a continuation if the {\tt Iteratee} can still consume input, or yields otherwise. Oleg's version of {\tt checkDone} has a problem---when the enumeratee has some sort of input buffer, but the underlying iteratee enters {\tt Yield}, it will discard the output buffer. {\tt checkDoneEx} corrects this; for backwards compatibility, {\tt checkDone} remains. :f Data/Enumerator.hs |apidoc Data.Enumerator.checkDoneEx| checkDoneEx :: Monad m => Stream a' -> ((Stream a -> Iteratee a m b) -> Iteratee a' m (Step a m b)) -> Enumeratee a' a m b checkDoneEx _ f (Continue k) = f k checkDoneEx extra _ step = yield step extra |apidoc Data.Enumerator.checkDone| checkDone :: Monad m => ((Stream a -> Iteratee a m b) -> Iteratee a' m (Step a m b)) -> Enumeratee a' a m b checkDone = checkDoneEx (Chunks []) : :d Data.Enumerator exports , checkDone , checkDoneEx : :f Data/Enumerator.hs |apidoc Data.Enumerator.isEOF| isEOF :: Monad m => Iteratee a m Bool isEOF = continue $ \s -> case s of EOF -> yield True s _ -> yield False s : :d Data.Enumerator exports , isEOF : {\tt Data.Enumerator.Util} is a hidden module for functions used by several public modules, but not logically part of the {\tt enumerator} API. :f Data/Enumerator/Util.hs {-# LANGUAGE CPP #-} module Data.Enumerator.Util where import Data.Enumerator import Data.Char (toUpper, intToDigit, ord) import Data.Word (Word8) import qualified Data.Text as T import qualified Data.Text.Lazy as TL import Control.Monad.IO.Class (MonadIO, liftIO) import qualified Control.Exception as Exc import Numeric (showIntAtBase) : :f Data/Enumerator/Util.hs tryStep :: MonadIO m => IO t -> (t -> Iteratee a m b) -> Iteratee a m b tryStep get io = do tried <- liftIO (Exc.try get) case tried of Right t -> io t Left err -> throwError (err :: Exc.SomeException) : :f Data/Enumerator/Util.hs pad0 :: Int -> String -> String pad0 size str = padded where len = Prelude.length str padded = if len >= size then str else Prelude.replicate (size - len) '0' ++ str : :f Data/Enumerator/Util.hs reprChar :: Char -> String reprChar c = "U+" ++ (pad0 4 (showIntAtBase 16 (toUpper . intToDigit) (ord c) "")) : :f Data/Enumerator/Util.hs reprWord :: Word8 -> String reprWord w = "0x" ++ (pad0 2 (showIntAtBase 16 (toUpper . intToDigit) w "")) : {\tt text-0.11} changed some function names to appease a few bikeshedding idiots in -cafe; to support it, a bit of compatibility code is needed. I had a choice between using the preprocessor, or a separate module plus some Cabal magic. It turns out that {\tt cabal sdist} doesn't properly handle multiple source directories selected by flags, so the preprocessor is used for now. :f Data/Enumerator/Util.hs tSpanBy :: (Char -> Bool) -> T.Text -> (T.Text, T.Text) tlSpanBy :: (Char -> Bool) -> TL.Text -> (TL.Text, TL.Text) #if MIN_VERSION_text(0,11,0) tSpanBy = T.span tlSpanBy = TL.span #else tSpanBy = T.spanBy tlSpanBy = TL.spanBy #endif :