iteratee Using monad-control in enumerators

John Lato jwlato at gmail.com
Fri Sep 23 13:23:16 BST 2011


Hello,

I am considering this change for the 0.9 release, which will also
include controlIO instances for Iteratee.  It would mean that users
couldn't use enum* functions with ContT-based stacks, which may or may
not be a good thing depending on your point of view (I suspect it's a
net improvement).

However, last time I tested this it turned out that performance was
worse than the current code.  I think that allocaBytes etc. don't
provide any efficiency benefits with long-lived memory.

I'll test it again with ghc-7.2 and if performance isn't too much
worse I'll make the change.  There are other good reasons to move away
from MonadCatchIO.

As for when 0.9 will be released, that's another question.  There's
some cleanup I want to do, but the most compelling issues would be
related to enee* functions.  That's not quite ready yet, but maybe I
could consider 0.9 a preview release and then do an 0.10 (or 1.0?) to
really polish it up.

John

On Fri, Sep 23, 2011 at 1:04 PM, Bas van Dijk <v.dijk.bas at gmail.com> wrote:
> Hello,
>
> I would like to propose using controlIO (from monad-control) in the
> definition of enumFd and friends.
>
> One of the advantages of using controlIO is that you can use control
> operators like allocaBytes which are (far?) more efficient that the
> manual mallocBytes and free. Another advantage is that you need fewer
> "liftings" of IO actions into 'm' (I only need one controlIO per
> iteration of the loop):
>
> ---------------------------------------------------------------------
> import Control.Monad.IO.Control
>
> type Run s m a = Stream s -> IO (m (Iteratee s m a))
>
> enumFd :: forall s el m a
>       .  (NullPoint s, ReadableChunk s el, MonadControlIO m)
>       => Int
>       -> Fd
>       -> Enumerator s m a
> enumFd bs fd = \iter ->
>    controlIO $ \runInIO -> do
>      let bufsize = bs * (sizeOf (undefined :: el))
>      allocaBytes bufsize $ \p ->
>          let loop :: Enumerator s m a
>              loop i = runIter i idoneM onCont
>
>              onCont :: (Stream s -> Iteratee s m a)
>                     -> Maybe SomeException
>                     -> m (Iteratee s m a)
>              onCont _ (Just e) = return $ throwErr e
>              onCont k Nothing =
>                  controlIO $ \runInIO' -> do
>
>                    let stop, cont :: Run s m a
>                        stop = return   . return . k
>                        cont = runInIO' . loop   . k
>
>                    n <- myfdRead fd (castPtr p)
>                                     (fromIntegral bufsize)
>                    case n of
>                      Left  _  -> stop $ EOF $ Just
>                                    (error "myfdRead failed")
>                      Right 0  -> do yield -- Why is this needed?
>                                     stop $ Chunk empty
>                      Right n' -> readFromPtr p (fromIntegral n') >>=
>                                    cont . Chunk
>          in runInIO $ loop iter
> ---------------------------------------------------------------------
>
> Note that I already use this approach in usb-iteratee[1].
>
> Finally note that this change does not require Iteratee to be an
> instance of MonadControlIO.
>
> What do you think?
>
> Bas
>
> [1] http://hackage.haskell.org/package/usb-iteratee
>
> _______________________________________________
> Iteratee mailing list
> Iteratee at projects.haskell.org
> http://projects.haskell.org/cgi-bin/mailman/listinfo/iteratee
>



More information about the Iteratee mailing list