Stricter WriterT (Part II)
Ross Paterson
R.Paterson at city.ac.uk
Mon Mar 18 17:43:01 CET 2013
On Sun, Mar 17, 2013 at 09:18:13AM -0700, Gabriel Gonzalez wrote:
> So I propose that we add an additional stricter WriterT (under say,
> "Control.Monad.Trans.Writer.Stricter") which is internally
> implemented as StateT, but hide the constructor so we don't expose
> the implementation:
>
> newtype WriterT w m a = WriterT { unWriterT :: w -> m (a, w) }
>
> instance (Monad m, Monoid w) => Monad (WriterT w m) where
> return a = WriterT $ \w -> return (a, w)
> m >>= f = WriterT $ \w -> do
> (a, w') <- unWriterT m w
> unWriterT (f a) w'
>
> And define `tell` and `runWriterT` as follows:
>
> tell :: (Monad m, Monoid w) => w -> WriterT w m ()
> tell w = WriterT $ \w' ->
> let wt = w `mappend` w'
> in wt `seq` return ((), w `mappend` w')
>
> runWriterT :: (Monoid w) => WriterT w m a -> m (a, w)
> runWriterT m = unWriterT m mempty
>
> If we do that, then WriterT becomes not only usable, but actually
> competitive with expertly tuned code.
Presumably we'll also need
writerT :: m (a, w) -> WriterT w m a
Is there any reason to keep Control.Monad.Trans.Writer.Strict, or
should this replace it?
More information about the Libraries
mailing list