new major release of transformers package

Edward Kmett ekmett at gmail.com
Thu Mar 8 14:21:14 CET 2012


On Thu, Mar 8, 2012 at 4:18 AM, Michael Snoyman <michael at snoyman.com> wrote:

> On Thu, Mar 8, 2012 at 2:43 AM, Ross Paterson <ross at soi.city.ac.uk> wrote:
> > Seeking views before a new major release of transformers package.
> > The docs are here:
> >
> >
> http://code.haskell.org/~ross/transformers/dist/doc/html/transformers/
> >
> > The source is here:
> >
> >        darcs get http://code.haskell.org/~ross/transformers
> >
> > The major changes from version 0.2.2.0 are:
> >
> > * Foldable and Traversable instances for transformers that support them.
> > * extra Monad instances:
> >
> >        instance (MonadFix m) => MonadFix (MaybeT m)
> >        instance (MonadFix m) => MonadFix (IdentityT m)
> >        instance (Monad f, Monad g) => Monad (Product f g)
> >        instance (MonadPlus f, MonadPlus g) => MonadPlus (Product f g)
> >        instance (MonadFix f, MonadFix g) => MonadFix (Product f g)
> >
> > * new functors Backwards and Reverse
> > * a new Lift transformer, a generalization of Errors
> > * generalized constructor functions:
> >
> >        state :: Monad m => (s -> (a, s)) -> StateT s m a
> >        reader :: Monad m => (r -> a) -> ReaderT r m a
> >        writer :: Monad m => (a, w) -> WriterT w m a
> >
> > Another issue that has been raised is: should the instance
> >
> >        instance Monad (ContT r m)
> >
> > have a Monad constraint so that it can define fail?
> >
> > _______________________________________________
> > Libraries mailing list
> > Libraries at haskell.org
> > http://www.haskell.org/mailman/listinfo/libraries
>
> I doubt that this change could actually be merged into transformers,
> since it requires either FunDeps or Type Families, but I thought I'd
> mention it anyway. In Yesod, we have the monads Handler and Widget,
> which are essentially:
>
> newtype Handler a = Handler (ReaderT HandlerData IO a)
> newtype Widget a = Widget (WriterT WidgetData Handler a)
>
> We could in theory make the underlying monad a type variable as well,
> but this would produce confusing type signatures and error
> messages[1], as well as falsely give the impression that it would be
> valid to use different monads as the base for each of these.
>
> The result? We have something which is essentially a transformer, but
> actually isn't. Therefore, even though we *want* to have a `lift`
> function, we can't define a `MonadTrans` instance.
>
> My solution was to create a new typeclass[2]:
>
> class MonadLift base m | m -> base where
>    lift :: base a -> m a
>

On a slightly related note, there is an interesting concept available for
(almost) all monad transformers.

class MonadHoist t where
  hoist :: (Monad m, Monad n) => (forall a. m a -> n a) -> t m a -> t n a

which witnesses the canonical lifting of a monad homomorphism from m to n
into a homomorphism from t m to t n.

However, this class isn't Haskell 98 and requires a rank 2 type, and the
invariant that the user supplies you with a monad homomorphism, not merely
a natural transformation.

That said, you can make a Haskell 98 version of it supports the special
case of lifting the canonical monad homomorphism from the Identity functor
to your monad, which comes from (return . runIdentity):

class MonadHoist t where
  hoist :: Monad m => t Identity a -> t m a

I have the comonadic analog in

http://hackage.haskell.org/packages/archive/comonad-transformers/2.0.3/doc/html/Control-Comonad-Hoist-Class.html


This is roughly analogous to the class you proposed, but it is compatible
with everything in transformers and the mtl and is Haskell 98. It doesn't
satisfy your need because your pseudo-transformers aren't, but I figured
you might be interested.

It's simple to automatically make all instances of MonadTrans an
> instance of MonadLift:
>
> instance (Monad m, MonadTrans t) => MonadLift m (t m) where
>    lift = Control.Monad.Trans.Class.lift
>

This is actually a really awful instance, since it pretty much ensures that
no other instances for a type of kind (* -> *) -> * -> * can be made
without overlap. Sadly the 'correct' if far more tedious thing to do is to
go through and build them all as you go. =/

and still make separate instances for Handler and Widget.
>
> As I said, I'm not really trying to push this into transformers, but I
> thought I would mention it. I think being able to make non-MonadTrans
> transformers can often be a good API design, and it would be nice to
> support it in the libraries.
>
> Michael
>
> [1] The type aren't quite as simple as I've presented them here.
> [2]
> http://hackage.haskell.org/packages/archive/yesod-core/0.10.2.1/doc/html/Yesod-Handler.html#t:MonadLift
>
> _______________________________________________
> 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/20120308/3d314a82/attachment.htm>


More information about the Libraries mailing list