[Haskell-cafe] Monad transformer to consume a list

Henning Thielemann lemming at henning-thielemann.de
Tue Apr 7 15:42:24 EDT 2009


On Tue, 7 Apr 2009, Stephan Friedrichs wrote:

> My solution is this transformer:
>
>
> newtype ConsumerT c m a
>    = ConsumerT { runConsumerT :: [c] -> m (a, [c]) }
>
> instance (Monad m) => Monad (ConsumerT c m) where
>    return x = ConsumerT $ \cs -> return (x, cs)
>    m >>= f  = ConsumerT $ \cs -> do
>                 ~(x, cs') <- runConsumerT m cs
>                 runConsumerT (f x) cs'
>    fail msg = ConsumerT $ const (fail msg)

But this is precisely the StateT, wrapped in a newtype and with restricted 
operations on it. You could as well define

newtype ConsumerT c m a =
    ConsumerT { runConsumerT :: StateT [c] m a }

instance (Monad m) => Monad (ConsumerT c m) where
    return x = ConsumerT $ return x
    m >>= f  = ConsumerT $ runConsumerT . f =<< runConsumerT m


More information about the Haskell-Cafe mailing list