\section{Primitives} \subsection{Operators} Because {\tt Iteratee a m b} is semantically equivalent to {\tt m (Step a m b)}, several of the monadic combinators ({\tt (>>=)}, {\tt (>=>)}, etc) are useful to save typing when constructing enumerators and enumeratees. {\tt (>>==)} corresponds to {\tt (>>=)}, {\tt (>==>)} to {\tt (>=>)}, and so on. :d iteratee operators infixl 1 >>== infixr 1 ==<< infixr 0 $$ infixr 1 >==> infixr 1 <==< |apidoc Data.Enumerator.(>>==)| (>>==) :: Monad m => Iteratee a m b -> (Step a m b -> Iteratee a' m b') -> Iteratee a' m b' i >>== f = Iteratee (runIteratee i >>= runIteratee . f) |apidoc Data.Enumerator.(==<<)| (==<<) :: Monad m => (Step a m b -> Iteratee a' m b') -> Iteratee a m b -> Iteratee a' m b' (==<<) = flip (>>==) |apidoc Data.Enumerator.($$)| ($$) :: Monad m => (Step a m b -> Iteratee a' m b') -> Iteratee a m b -> Iteratee a' m b' ($$) = (==<<) |apidoc Data.Enumerator.(>==>)| (>==>) :: Monad m => Enumerator a m b -> (Step a m b -> Iteratee a' m b') -> Step a m b -> Iteratee a' m b' (>==>) e1 e2 s = e1 s >>== e2 |apidoc Data.Enumerator.(<==<)| (<==<) :: Monad m => (Step a m b -> Iteratee a' m b') -> Enumerator a m b -> Step a m b -> Iteratee a' m b' (<==<) = flip (>==>) : \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. :d primitives |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" : {\tt run\_} is even more simplified; it's used in simple scripts, where the user doesn't care about error handling. :d primitives |apidoc Data.Enumerator.run_| run_ :: Monad m => Iteratee a m b -> m b run_ i = run i >>= either Exc.throw return : \subsection{Error handling} Most real-world applications have to deal with error conditions; however, libraries have various ways of reporting errors. Some throw exceptions, others use callbacks, and many just use {\tt Either}. Heterogeneous error handling makes composing code very difficult; therefore, all enumerator-based code simply uses the standard {\tt Control.Exception} module and its types. Instances for the {\tt MonadError} class are provided in auxiliary libraries, to avoid extraneous dependencies. :d primitives |apidoc Data.Enumerator.throwError| throwError :: (Monad m, Exc.Exception e) => e -> Iteratee a m b throwError exc = returnI (Error (Exc.toException exc)) : Handling errors has a caveat: any input consumed before the error was thrown can't be recovered. If an iteratee needs to continue parsing after an error, either buffer the input stream or use a separate framing mechanism. This limitation means that {\tt catchError} is mostly only useful for transforming or logging errors, not ignoring them. :d primitives |apidoc Data.Enumerator.catchError| catchError :: Monad m => Iteratee a m b -> (Exc.SomeException -> Iteratee a m b) -> Iteratee a m b catchError i h = go i where go iter = Iteratee $ do step <- runIteratee iter case step of Yield _ _ -> return step Error err -> runIteratee (h err) Continue k -> return (Continue (wrap k)) wrap k EOF = Iteratee $ do res <- run (k EOF) case res of Left err -> runIteratee (enumEOF $$ h err) Right b -> return (Yield b EOF) wrap k stream = Iteratee $ do step <- runIteratee (k stream) case step of Yield _ _ -> return step Error err -> do step' <- runIteratee (h err) case step' of Continue k' -> runIteratee (k' stream) _ -> return step' Continue k' -> return (Continue (wrap k')) :