transformers

Ross Paterson ross at soi.city.ac.uk
Thu Jan 27 11:54:05 CET 2011


On Wed, Jan 26, 2011 at 03:56:12PM -0500, Edward Kmett wrote:
> 1.) Data.Functor.Product admits a useful monad instance.

Yes (once the typos are fixed), and it's compatible with the Applicative
instance.  While we're at it, we might as well add the MonadPlus and
MonadFix instances:

instance (MonadPlus f, MonadPlus g) => MonadPlus (Product f g) where
    mzero = Pair mzero mzero
    Pair x1 y1 `mplus` Pair x2 y2 = Pair (x1 `mplus` x2) (y1 `mplus` y2)

instance (MonadFix f, MonadFix g) => MonadFix (Product f g) where
    mfix f = Pair (mfix (fstP . f)) (mfix (sndP . f))
      where
        fstP (Pair a _) = a
        sndP (Pair _ b) = b

> 2.) The instance for Applicative for MaybeT doesn't really follow the other
> instances for Applicative in transformers.

David Menendez has explained that this is needed for compatibility
with the Monad instance.

> 3.) Data.Functor.Constant is rather redundant given the existence
> of the identical Const functor in Control.Applicative (which is a
> module that Data.Functor.Constant depends upon!) The main thing
> that would need to be fixed is the addition of Traversable and
> Foldable to Control.Applicative.Const, which shouldn't be all that
> controversial. I'll propose that more formally separately, as that
> does directly fall under the libraries processes.

Yes, that was an oversight, considering I wrote both instances.  I think
it's better not to abbreviate the name, so I'd suggest moving Constant
into Control.Applicative (re-exported by Data.Functor.Constant) and
deprecating Const.  (Or just hiding Const in Control.Applicative.)

> 4.) For completeness, I'm including this here, although I sent it in
> a separate email to Ross the other day. A large number of the monad
> transformers admit reasonable definitions for Foldable/Traversable.

These all look good, though let's write the ErrorT ones as

instance (Foldable f) => Foldable (ErrorT e f) where
    foldMap f (ErrorT a) = foldMap (either (const mempty) f) a

instance (Traversable f) => Traversable (ErrorT e f) where
    traverse f (ErrorT a) =
        ErrorT <$> traverse (either (pure . Left) (fmap Right . f)) a

so we don't have to wait for the Either instances to appear in base.

5.) While we're talking about transformers, do you have an opinion on
#4517: Add Data.Functor.Backwards to transformers
(http://www.haskell.org/pipermail/libraries/2010-December/015296.html)?
It's just a choice between designs using one functor or two.



More information about the Libraries mailing list