Stricter WriterT (Part II)

I previously asked on this mailing list about getting a stricter WriterT added to transformers here: http://www.haskell.org/pipermail/libraries/2012-October/018599.html To recap, neither of the two WriterT implementations in transformers keep the accumulator strictly evaluated. In the previous request, I presented four implementations, only one of which runs in constant space, all of which are in this hpaste: http://hpaste.org/75837 To summarize the four implementations: Version #1: WriterT from Control.Monad.Trans.Writer.Strict Version #2: Same as Version1, except the monad bind strictly evaluates the mappended result Version #3: WriterT reimplemented as StateT, but no strictness annotations Version #4: Same as Version3, except 'tell' strictly evaluates the mappended result Only version #4 works and runs in constant space. Actually, not only does it run in constant space, but I failed to realize at the time that it also compiles to very efficient core when you add an `Int` type annotation to the summand. For example, if you try to sum 1 billion `Int`s in the naive way using Version #4: main :: IO () main = (print =<<) $ runWriterT4 $ replicateM_ 1000000000 $ tell4 $ Sum (1 :: Int) ... and compile it with -O2, it generates the following very nice core: $wa1 = \ (w_s25b :: Int#) (ww_s25e :: Int#) (w1_s25g :: State# RealWorld) -> case <=# w_s25b 1 of _ { False -> $wa1 (-# w_s25b 1) (+# 1 ww_s25e) w1_s25g; True -> (# w1_s25g, ((), (I# (+# 1 ww_s25e)) ) #) } ... and runs in 4.6 seconds on my netbook: time ./writer ((),Sum {getSum = 1000000000}) real 0m4.580s user 0m4.560s sys 0m0.008s ... which is about 4.6 nanoseconds per element. This is quite impressive when you consider it is factoring everything through the 'IO' monad. If you use `Identity` as the base monad: main4 = print $ runIdentity $ runWriterT4 $ replicateM_ n $ tell4 $ Sum (1 :: Int) ... then it gets slightly faster: real 0m3.678s user 0m3.668s sys 0m0.000s ... with an even nicer inner loop: $wa1 = \ (w_s25v :: Int#) (ww_s25y :: Int#) -> case <=# w_s25v 1 of _ { False -> $wa1 (-# w_s25v 1) (+# 1 ww_s25y); True -> (# (), (I# (+# 1 ww_s25y)) #) } The reason this stalled last time is that Edward and I agreed that I should first investigate if there is a "smaller" type that gives the same behavior. Now I'm revisiting the issue because I can safely conclude that the answer is "no". The StateT implementation is the smallest type that gives the correct behavior. To explain why, it helps to compare the definition of `(>>=)` for both WriterT and StateT: m >>= k = WriterT $ do (a, w) <- runWriterT m (b, w') <- runWriterT (k a) return (b, w `mappend` w') m >>= k = StateT $ \s -> do (a, s') <- runStateT m s runStateT (k a) s' The `WriterT` fails to run in constant space because of the pattern of binding the continuation before mappending the results. This results in N nested binds before it can compute even the very first `mappend`. This not only leaks space, but also punishes the case where your base monad is a free monad, since it builds up a huge chain of left-associated binds. The canonical solution to avoid this sort of nested bind is to use a continuation-passing-style transformation where you pass the second `runWriterT` a continuation saying what you want to do with its monoid result. My first draft of such a solution looked like this: newtype WriterT w m a = WriterT { unWriterT :: (w -> w) -> m (a, w) } m >>= k = WriterT $ \f -> do (a, w) <- runWriterT m f runWriterT (k a) (mappend w) tell w = WriterT $ \f -> return ((), f w) runWriterT m = unWriterT m id ... but then I realized that there is no need to pass a general function. I only ever use mappend, so why not just pass in the monoid that I want to mappend and let `tell` just supply the `mappend`: newtype WriterT w m a = WriterT { unWriterT :: w -> m (a, w) } m >>= k = WriterT $ \w -> do (a, w') <- runWriterT m f runWriterT (k a) w' tell w' = WriterT $ \w -> return ((), mappend w w') runWriterT m = unWriterT m mempty Notice that this just reinvents the StateT monad transformer. In other words, StateT *is* the continuation-passing-style transformation of WriterT, which is why you can't do any better than to reformulate WriterT as StateT internally. 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.

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?

On Sun, Mar 17, 2013 at 9:18 AM, Gabriel Gonzalez
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:
Nice work. If we end up adding a new module (instead of e.g. replacing the current one), lets try to have a more descriptive name. The -er names quickly get out of hand: New, Newer, MoreNewer, Newerest! Better to include a word that explains in what sense the writer is strict. Let the bikeshedding begin!

Gabriel Gonzalez
I previously asked on this mailing list about getting a stricter WriterT added to transformers here:
It seems that this thread has died an unfortunate premature death. I, for one, would love to see this make its way upstream. Will this be happening? Cheers, - Ben

The question was about a Writer that basically calls seq on the mappend operation if I recall correctly? I'd be in on that. A practical example that I frequently come across is having Reader+State, but I can't use RWS because of the "mappend ()" thunk buildup when using "RWS r () s". +1 David

On 05/20/2013 06:11 AM, Ben Gamari wrote:
Gabriel Gonzalez
writes: I previously asked on this mailing list about getting a stricter WriterT added to transformers here:
It seems that this thread has died an unfortunate premature death. I, for one, would love to see this make its way upstream. Will this be happening?
Cheers,
- Ben
I agree. We might optionally consider combining two changes to `transformers`: * Adding the stricter `WriterT` * Adding `EitherT`

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) }
That would be slightly less transparent than the other transformers, and it wouldn't be perfectly parallel to the existing versions of WriterT: - the Applicative and Alternative instances would have different contexts - there would be no Foldable or Traversable instances On Tue, Mar 19, 2013 at 08:33:37PM -0400, Edward Kmett wrote:
I use them fairly heavily, mostly so I can make packages that work with arbitrary transformer stacks.
There are several packages like this, that pass various stuff through all the transformers. Relatively few seem to use the strict writer for itself: alms darcswatch ghc-heap-view Glob GPipe-Collada Haschoo hbayes nemesis satchmo shake storable XmlHtmlWriter I wonder if these users were expecting the linear behaviour that Gabriel was exploring. So perhaps the best thing would be to deprecate Writer.Strict in favour of State.Strict.
participants (5)
-
Ben Gamari
-
David Luposchainsky
-
Gabriel Gonzalez
-
Johan Tibell
-
Ross Paterson