new major release of transformers package

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?

On Wed, Mar 7, 2012 at 7:43 PM, Ross Paterson
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
Hrmm. If the definitions of 'modify' ran through 'state' they could avoid a round trip through the monad. 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?
Ick. One of the things I liked about the recent change that brought the monad instance for Either into Control.Monad.Instances was that we didn't go out of our way to screw up a perfectly good monad in order to better support fail, and the same argument could be applied to pollute Codensity, which also currently requires nothing of 'm', but which has ContT r m-like uses involving types like Endo. I'm not a fan of 'slippery slope' arguments, but this strikes me as a slippery slope. ;) -Edward

On Thu, Mar 8, 2012 at 2:43 AM, Ross Paterson
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@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 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 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/Yes...

On Thu, Mar 8, 2012 at 10:18 AM, Michael Snoyman
My solution was to create a new typeclass[2]:
class MonadLift base m | m -> base where lift :: base a -> m a
Have you seen: http://hackage.haskell.org/package/transformers-base

2012/3/8 Gábor Lehel
On Thu, Mar 8, 2012 at 10:18 AM, Michael Snoyman
wrote: My solution was to create a new typeclass[2]:
class MonadLift base m | m -> base where lift :: base a -> m a
Have you seen: http://hackage.haskell.org/package/transformers-base
Sorry, that seems to be similar but different. AFAICT MonadBase actually lifts from the bottom-most, while MonadLift only goes one level down? Confusingly they both use the word 'base' :)

On Mar 8, 2012 11:43 AM, "Gábor Lehel"
On Thu, Mar 8, 2012 at 10:18 AM, Michael Snoyman
wrote:
My solution was to create a new typeclass[2]:
class MonadLift base m | m -> base where lift :: base a -> m a
Have you seen: http://hackage.haskell.org/package/transformers-base
Yes, I actually use it quite a bit via monad-control. However, MonadBase has a different purpoe: an instance of MonadBase for Widget would be intended to lift to IO, not to Handler. But perhaps transformers-base would be a good place to include a typeclass like MonadLift. Michael

On Thu, Mar 8, 2012 at 4:18 AM, Michael Snoyman
On Thu, Mar 8, 2012 at 2:43 AM, Ross Paterson
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@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/h... 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/Yes...
_______________________________________________ Libraries mailing list Libraries@haskell.org http://www.haskell.org/mailman/listinfo/libraries

On Thu, 8 Mar 2012, Ross Paterson wrote:
* 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
I'd prefer to call them stateT, readerT, writerT in order to keep 'state', 'reader', 'writer' with the restricted types. The restricted type should work without type annotations in cases where I really only want type 'State'. Actually stateT, readerT, writerT are only alternative constructors for StateT, ReaderT, WriterT with a restriction on 'm'. We might discuss, whether (Monad m) is too restrictive or whether it should be only (Functor m).

On Thu, Mar 8, 2012 at 6:09 AM, Henning Thielemann < lemming@henning-thielemann.de> wrote:
On Thu, 8 Mar 2012, Ross Paterson wrote:
* 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
I'd prefer to call them stateT, readerT, writerT in order to keep 'state', 'reader', 'writer' with the restricted types. The restricted type should work without type annotations in cases where I really only want type 'State'. Actually stateT, readerT, writerT are only alternative constructors for StateT, ReaderT, WriterT with a restriction on 'm'.
There was a discussion period on this about 6 months ago. We're just now finally getting it all integrated. I'd rather not add new names for the same operations. These definitions are the most natural definition of the properties of their appropriate transformers, by defining the monad homomorphism from the simpler monad. We might discuss, whether (Monad m) is too restrictive or whether it should
be only (Functor m).
The problem with Functor m in this situation is it can lead to places due to our broken class hierarchy where the end user can't apply them. If we get the class hierarchy fixed, I'd be more than happy to revisit this along with the thousands of other compromises we have had forced on us. ;) ______________________________**_________________
Libraries mailing list Libraries@haskell.org http://www.haskell.org/**mailman/listinfo/librarieshttp://www.haskell.org/mailman/listinfo/libraries

On Thu, 8 Mar 2012, Edward Kmett wrote:
On Thu, Mar 8, 2012 at 6:09 AM, Henning Thielemann
wrote: I'd prefer to call them stateT, readerT, writerT in order to keep 'state', 'reader', 'writer' with the restricted types. The restricted type should work without type annotations in cases where I really only want type 'State'. Actually stateT, readerT, writerT are only alternative constructors for StateT, ReaderT, WriterT with a restriction on 'm'.
There was a discussion period on this about 6 months ago. We're just now finally getting it all integrated. I'd rather not add new names for the same operations.
I can't remember that. I just scanned http://www.haskell.org/pipermail/libraries/2011-August/ http://www.haskell.org/pipermail/libraries/2011-September/ and did not find the keyword "transformer". Nevertheless, Ross is right that the proposed 'state' function is still closer to the old 'state' function than to the current 'StateT' constructor. Maybe the problem with type inference is not as bad as I thought first, since evalState will keep the restricted State type. Thus a combination of evalState and state in the same function will still work without type annotation. If evalState and state are in separate functions, then the type signature of the functions will fix the type to State. It's just that I originally proposed the 'state' function as a replacement for the 'State' constructor that was gone due to redefining 'State s' as type synonym to 'StateT s Identity'.

On Thu, 8 Mar 2012, Henning Thielemann wrote:
On Thu, 8 Mar 2012, Edward Kmett wrote:
On Thu, Mar 8, 2012 at 6:09 AM, Henning Thielemann
wrote: I'd prefer to call them stateT, readerT, writerT in order to keep 'state', 'reader', 'writer' with the restricted types. The restricted type should work without type annotations in cases where I really only want type 'State'. Actually stateT, readerT, writerT are only alternative constructors for StateT, ReaderT, WriterT with a restriction on 'm'.
There was a discussion period on this about 6 months ago. We're just now finally getting it all integrated. I'd rather not add new names for the same operations.
I can't remember that. I just scanned http://www.haskell.org/pipermail/libraries/2011-August/ http://www.haskell.org/pipermail/libraries/2011-September/ and did not find the keyword "transformer".
Do you mean this one: http://www.haskell.org/pipermail/libraries/2011-September/016812.html ? But this is about generalized 'state' function in mtl and the MonadState class, not about transformers. Nonetheless changing 'state' as discussed here is certainly analogous to the generalization of 'state' in mtl.

On Thu, Mar 8, 2012 at 5:08 AM, Edward Kmett
There was a discussion period on this about 6 months ago. We're just now finally getting it all integrated. I'd rather not add new names for the same operations.
As a meta point, I fully sympathize that it can be annoying having old decisions questioned after the fact, but I think we should still re-consider them *iff* truly new information is brought forward. I don't know if that's the case here or not as I didn't follow the original discussion. Cheers, Johan

On Thu, Mar 8, 2012 at 4:26 PM, Johan Tibell
On Thu, Mar 8, 2012 at 5:08 AM, Edward Kmett
wrote: There was a discussion period on this about 6 months ago. We're just now finally getting it all integrated. I'd rather not add new names for the same operations.
As a meta point, I fully sympathize that it can be annoying having old decisions questioned after the fact, but I think we should still re-consider them *iff* truly new information is brought forward. I don't know if that's the case here or not as I didn't follow the original discussion.
Of course, I wasn't trying to lay down the law. Just that it was a rather late amendment and to indicate that I was personally on the other side of the divide. The proposal spoke about mtl, the fact that it impacts transformers was more realized in hindsight. http://haskell.1045720.n5.nabble.com/Proposal-add-state-to-the-MonadState-cl... http://hackage.haskell.org/trac/ghc/ticket/5714 At the time I'd said I'd get it in, I hadn't realized how much of it actually fell to Ross as the maintainer of transformers. -Edward

On Thu, Mar 08, 2012 at 11:09:35AM +0000, Henning Thielemann wrote:
On Thu, 8 Mar 2012, Ross Paterson wrote:
* 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
I'd prefer to call them stateT, readerT, writerT in order to keep 'state', 'reader', 'writer' with the restricted types. The restricted type should work without type annotations in cases where I really only want type 'State'. Actually stateT, readerT, writerT are only alternative constructors for StateT, ReaderT, WriterT with a restriction on 'm'.
But this means they would have different types from StateT :: (s -> m (a, s)) -> StateT s m a ReaderT :: (r -> m a) -> ReaderT r m a WriterT :: m (a, w) -> WriterT w m a
participants (6)
-
Edward Kmett
-
Gábor Lehel
-
Henning Thielemann
-
Johan Tibell
-
Michael Snoyman
-
Ross Paterson