\section{Miscellaneous} 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. Sequencing a fixed set of enumerators is easy, but for more complex cases, it's useful to have a small utility wrapper. :d unsorted utilities |apidoc Data.Enumerator.concatEnums| concatEnums :: Monad m => [Enumerator a m b] -> Enumerator a m b concatEnums = Prelude.foldl (>==>) returnI : {\tt joinI} is used to ``flatten'' enumeratees, to transform them into an {\tt Iteratee}. :d unsorted utilities |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 : :d unsorted utilities infixr 0 =$ |apidoc Data.Enumerator.(=$)| (=$) :: Monad m => Enumeratee ao ai m b -> Iteratee ai m b -> Iteratee ao m b enum =$ iter = joinI (enum $$ iter) : {\tt joinE} is similar, except it flattens an enumerator/enumeratee pair into a single enumerator. :d unsorted utilities |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" : :d unsorted utilities infixr 0 $= |apidoc Data.Enumerator.($=)| ($=) :: Monad m => Enumerator ao m (Step ai m b) -> Enumeratee ao ai m b -> Enumerator ai m b ($=) = joinE : {\tt sequence} repeatedly runs its parameter to transform the stream. :d unsorted utilities |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 : :d unsorted utilities |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 : 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. :d unsorted utilities |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 unsorted utilities |apidoc Data.Enumerator.isEOF| isEOF :: Monad m => Iteratee a m Bool isEOF = continue $ \s -> case s of EOF -> yield True s _ -> yield False s : When an enumerator has to interact with the outside world, it usually catches any exceptions that arise, and propagate them as {\tt Error} steps instead. {\tt tryIO} encapsulates that pattern. :d unsorted utilities |apidoc Data.Enumerator.tryIO| tryIO :: MonadIO m => IO b -> Iteratee a m b tryIO io = Iteratee $ do tried <- liftIO (Exc.try io) return $ case tried of Right b -> Yield b (Chunks []) Left err -> Error err : Another enumerator pattern that pops up often is a loop that ignores any non-{\tt Continue} steps. This is especially useful when implementing most enumerators. It's sort of an analogue to {\tt checkDone}, so I called it {\tt checkContinue}. It's actually implemented by various functions ({\tt checkContinue0}, {\tt checkContinue1}, etc), as most enumerators have some sort of state to pass around. :d unsorted utilities |apidoc Data.Enumerator.checkContinue0| checkContinue0 :: Monad m => (Enumerator a m b -> (Stream a -> Iteratee a m b) -> Iteratee a m b) -> Enumerator a m b checkContinue0 inner = loop where loop (Continue k) = inner loop k loop step = returnI step : :d unsorted utilities |apidoc Data.Enumerator.checkContinue1| checkContinue1 :: Monad m => ((s1 -> Enumerator a m b) -> s1 -> (Stream a -> Iteratee a m b) -> Iteratee a m b) -> s1 -> Enumerator a m b checkContinue1 inner = loop where loop s (Continue k) = inner loop s k loop _ step = returnI step : {\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.Char (toUpper, intToDigit, ord) import Data.Word (Word8) import qualified Data.Text as T import qualified Data.Text.Lazy as TL import Numeric (showIntAtBase) : :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 : {\tt text-0.8} added the useful {\tt toStrict} function; this wrapper lets {\tt enumerator} work with {\tt text-0.7}. :f Data/Enumerator/Util.hs textToStrict :: TL.Text -> T.Text #if MIN_VERSION_text(0,8,0) textToStrict = TL.toStrict #else textToStrict = T.concat . TL.toChunks #endif : \subsection{Supplemental instances} It can be pretty useful to define {\tt Typeable} instances for iteratees and streams. For example, they allow iteratee-based libraries to be loaded dynamically as plugins. Normally I'd use the {\tt DeriveDataTypeable} language extension, but many users have said they find {\tt enumerator} useful in large part because it doesn't rely on extensions. So instead, the instances are derived manually. :d Data.Enumerator imports import Data.Typeable ( Typeable, typeOf , Typeable1, typeOf1 , mkTyConApp, mkTyCon) : :d supplemental instances -- | Since: 0.4.8 instance Typeable1 Stream where typeOf1 _ = mkTyConApp tyCon [] where tyCon = mkTyCon "Data.Enumerator.Stream" : :d supplemental instances -- | Since: 0.4.6 instance (Typeable a, Typeable1 m) => Typeable1 (Iteratee a m) where typeOf1 i = let tyCon = mkTyCon "Data.Enumerator.Iteratee" (a, m) = peel i peel :: Iteratee a m b -> (a, m ()) peel = undefined in mkTyConApp tyCon [typeOf a, typeOf1 m] : :d supplemental instances -- | Since: 0.4.8 instance (Typeable a, Typeable1 m) => Typeable1 (Step a m) where typeOf1 s = let tyCon = mkTyCon "Data.Enumerator.Step" (a, m) = peel s peel :: Step a m b -> (a, m ()) peel = undefined in mkTyConApp tyCon [typeOf a, typeOf1 m] : It's probably possible to define {\tt Functor} and {\tt Applicative} instances for {\tt Iteratee} without a {\tt Monad} constraint, but I haven't bothered, since every useful operation requires {\tt m} to be a Monad anyway. :d supplemental instances instance Monad m => Functor (Iteratee a m) where fmap = CM.liftM : :d supplemental instances instance Monad m => A.Applicative (Iteratee a m) where pure = return (<*>) = CM.ap : :d supplemental instances instance Functor Stream where fmap f (Chunks xs) = Chunks (fmap f xs) fmap _ EOF = EOF -- | Since: 0.4.5 instance A.Applicative Stream where pure = return (<*>) = CM.ap : \subsection{Testing and debugging} Debugging enumerator-based code is mostly a question of what inputs are being passed around. {\tt printChunks} prints out exactly what chunks are being sent from an enumerator. :d utilities for testing and debugging |apidoc Data.Enumerator.printChunks| printChunks :: (MonadIO m, Show a) => Bool -- ^ Print empty chunks -> Iteratee a m () printChunks printEmpty = continue loop where loop (Chunks xs) = do let hide = null xs && not printEmpty CM.unless hide (liftIO (print xs)) continue loop loop EOF = do liftIO (putStrLn "EOF") yield () EOF : 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) : :d utilities for testing and debugging |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 :