Proposal: merge either into transformers

Edward Kmett ekmett at gmail.com
Wed Apr 30 05:11:19 UTC 2014


As a straw man, if we really don't export the constructor and implement the
writerT API abstractly you can actually can implement Show/Read/Ord/Eq
correctly.

Under the assumption that it only uses the state as a writer context: we
could safely pass it the mempty state for display purposes to capture the
information present.

instance (Show1 m, Show e, Monoid e) => Show1 (WriterT e m) where
  showsPrec1 d (WriterT f) = showParen (d > 10) $
    showString "writerT " . showsPrec1 11 (f mempty)

instance (Eq1 m, Eq e, Monoid e) => Eq1 (WriterT e m) where
  eq1 (WriterT f) (WriterT g) = f mempty == g mempty

...

writerT :: (Monad m, Monoid e) => m (e, a) -> WriterT e m a
writerT mea = WriterT $ \s -> do
  (e, a) <- mea
  return $! (s <> e, a)

runWriterT :: Monoid e => WriterT e m a -> m (e, a)
runWriterT (WriterT f) = f mempty

...

On Tue, Apr 29, 2014 at 8:46 PM, Ross Paterson <R.Paterson at city.ac.uk>wrote:

> On Mon, Apr 28, 2014 at 07:00:25PM +0300, Michael Snoyman wrote:
> > On Mon, Apr 28, 2014 at 4:15 PM, Ross Paterson <R.Paterson at city.ac.uk>
> wrote:
> >     The Applicative and Alternative instances would have different
> >     contexts, and there would be no instances for Foldable, Traversable,
> >     Eq, Ord, Read or Show.
> >
> > If we have deprecation of the module in its entirety on the table,
> > I think it's acceptable to consider dropping some instances. However,
> > I don't see Eq, Ord, Read, or Show instances for strict WriterT in
> > transformers 0.3. Applicative seems like it should be identical in
> > behavior to what we have right now. I'm not completely certain, but
> > it seems the same is true for Alternative.
>
> I was more concerned with consistency across the interface in the
> new version.  Here the Applicative and Alternative instances for the
> state-based WriterT would have Monad constraints, while the lazy one
> just had Applicative constraints, and the lazy transformer would have Eq,
> Ord, Read, or Show instances while the strict one wouldn't.
>
> > Here's the question I'd ask, which I honestly don't know the
> > answer to. We have three proposed WriterT implementations: lazy,
> > current-strict, and state-strict.  We have two conflicting desires:
> > program termination and space savings. We know there are cases where
> > lazy allows termination where state-strict does not. We know there
> > are cases where state-strict allows space savings where neither lazy
> > nor current-strict do.
> >
> > The question is: are there cases where current-strict:
> >
> > 1. Gives space savings that lazy does not?
> > 2. Gives termination where state-strict does not?
> >
> > I *think* the answers to these questions are "no" and "yes", meaning that
> > current-strict in its current form can *always* be replaced by lazy,
> without
> > losing anything. If that's the case, I'd say this is a very simple
> transition
> > in 0.4.
>
> Of course strictness sometimes means more space, but you may be right on
> the termination issue.
> _______________________________________________
> Libraries mailing list
> Libraries at haskell.org
> http://www.haskell.org/mailman/listinfo/libraries
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://www.haskell.org/pipermail/libraries/attachments/20140430/ad05f09b/attachment.html>


More information about the Libraries mailing list