different flavours of Monad Template Library

I see now at least three MTL libraries at hackage, namely mtl mmtl mtl-tf They all define both the example data types and according type classes in modules with the same name. This way you can only use one of these packages in all packages you import. However the data types are defined the same way in the packages, only the classes differ. I wished, there would be one package defining only the datatypes, say "mtl-data", and three ones with the names "mtl", "mmtl", "mtl-tf" that define their classes with corresponding instances. These classes should be in different modules, so you can use different class frameworks in the same project. The data type package would be useful on its own and could be run on the simplest Haskell compilers, since no functional dependencies are required. However there is the compatibility problem: Currently Control.Monad.State exports also the MonadState class, which would no longer work. Maybe we can reserve Control.Monad.State for mtl, which exports Control.Monad.State.Data.Lazy from mtl-data and Control.Monad.State.Class from mtl. I assume that mmtl and mtl-tf are not as much used as mtl, such that it would not too bad to break compatibility for them. They could no longer export Control.Monad.State, but instead the user of mmtl has to import Control.Monad.State.Data from mtl-data. The class file of mmtl could be named Control.Monad.Modular.State.Class. (Replace "State" by "Writer", "Reader" and so on, and "mmtl" by "mtl-tf" in order to get all names that need to be adapted.)

On Sun, Jan 04, 2009 at 11:22:15PM +0100, Henning Thielemann wrote:
I see now at least three MTL libraries at hackage, namely mtl mmtl mtl-tf
They all define both the example data types and according type classes in modules with the same name. This way you can only use one of these packages in all packages you import. However the data types are defined the same way in the packages, only the classes differ.
I wished, there would be one package defining only the datatypes, say "mtl-data", and three ones with the names "mtl", "mmtl", "mtl-tf" that define their classes with corresponding instances. These classes should be in different modules, so you can use different class frameworks in the same project. The data type package would be useful on its own and could be run on the simplest Haskell compilers, since no functional dependencies are required.
I agree. I had a go at such a restructuring of mtl a while ago: http://darcs.haskell.org/packages/transformers/ http://darcs.haskell.org/packages/mtl-split/ The first is a Haskell 98 package that defines the monad transformers, operations and liftings, like the mtl-data suggestion. The second adds the FD-based classes. It's close to complete compatibility with mtl, except that State is a synonym for StateT Identity etc. The main problem was haddock's limitations with inter-package re-exports.
However there is the compatibility problem: Currently Control.Monad.State exports also the MonadState class, which would no longer work. Maybe we can reserve Control.Monad.State for mtl, which exports Control.Monad.State.Data.Lazy from mtl-data and Control.Monad.State.Class from mtl.
I used Control.Monad.Trans.State.Lazy for the transformer.

On Sun, 4 Jan 2009, Ross Paterson wrote:
I agree. I had a go at such a restructuring of mtl a while ago:
http://darcs.haskell.org/packages/transformers/ http://darcs.haskell.org/packages/mtl-split/
I wondered, where the packages were gone ...
The first is a Haskell 98 package that defines the monad transformers, operations and liftings, like the mtl-data suggestion. The second adds the FD-based classes. It's close to complete compatibility with mtl, except that State is a synonym for StateT Identity etc. The main problem was haddock's limitations with inter-package re-exports.
What is the current state, since Haddock has moved to GHC-API? At least 'transformers' seems to be distinct enough from current MTL and simple enough to be uploaded to Hackage right now. However, Control.Monad.Identity would conflict with MTL. Without that, 'transformers' could be even used together with the current MTL.

On Mon, Jan 05, 2009 at 01:07:00AM +0100, Henning Thielemann wrote:
On Sun, 4 Jan 2009, Ross Paterson wrote:
The main problem was haddock's limitations with inter-package re-exports.
What is the current state, since Haddock has moved to GHC-API?
That makes no difference to this issue (#24 on the Haddock trac; #13 is also relevant).
At least 'transformers' seems to be distinct enough from current MTL and simple enough to be uploaded to Hackage right now.
OK, I've done that.
However, Control.Monad.Identity would conflict with MTL.
Unfortunately that is necessary to make the split work. If we have a monad-classes-fd package, clients would have to depend on both it and transformers.

On Mon, 5 Jan 2009, Ross Paterson wrote:
On Mon, Jan 05, 2009 at 01:07:00AM +0100, Henning Thielemann wrote:
At least 'transformers' seems to be distinct enough from current MTL and simple enough to be uploaded to Hackage right now.
OK, I've done that.
However, Control.Monad.Identity would conflict with MTL.
Unfortunately that is necessary to make the split work. If we have a monad-classes-fd package, clients would have to depend on both it and transformers.
How about Control.Monad.Trans.Identity which is re-exported by Control.Monad.Identity in mtl? I also like to have a function 'state', which replaces the former 'State' constructor. I can also submit a patch if you want that.

On Mon, Jan 05, 2009 at 09:32:21AM +0100, Henning Thielemann wrote:
On Mon, 5 Jan 2009, Ross Paterson wrote:
On Mon, Jan 05, 2009 at 01:07:00AM +0100, Henning Thielemann wrote:
However, Control.Monad.Identity would conflict with MTL.
Unfortunately that is necessary to make the split work. If we have a monad-classes-fd package, clients would have to depend on both it and transformers.
How about Control.Monad.Trans.Identity which is re-exported by Control.Monad.Identity in mtl?
Hmm, it's a conflict between co-existing with mtl and using the Right Name for the transformers package, which is intended to be usable by itself. I prefer the latter, myself.
I also like to have a function 'state', which replaces the former 'State' constructor. I can also submit a patch if you want that.
You mean state :: (s -> (a, s)) -> State s a state f = StateT (Identity . f) and similarly for all the others? Sounds reasonable.

On Mon, 5 Jan 2009, Ross Paterson wrote:
On Mon, Jan 05, 2009 at 09:32:21AM +0100, Henning Thielemann wrote:
How about Control.Monad.Trans.Identity which is re-exported by Control.Monad.Identity in mtl?
Hmm, it's a conflict between co-existing with mtl and using the Right Name for the transformers package, which is intended to be usable by itself. I prefer the latter, myself.
You mean that Control.Monad.Trans.Identity is not a good name, because Identity is not a transformer? Then, how about Control.Monad.Base.Identity, Control.Monad.Primitive.Identity or so? Since mtl-split is not a drop-in replacement for mtl, we cannot expect a quick change from mtl to mtl-split in all the packages that currently import mtl. Thus we have to think about a route of transition and a package which can be installed in parallel to mtl is a first step, I think.
I also like to have a function 'state', which replaces the former 'State' constructor. I can also submit a patch if you want that.
You mean
state :: (s -> (a, s)) -> State s a state f = StateT (Identity . f)
and similarly for all the others? Sounds reasonable.
That's what I mean.

On Mon, Jan 05, 2009 at 12:54:20PM +0100, Henning Thielemann wrote:
You mean that Control.Monad.Trans.Identity is not a good name, because Identity is not a transformer?
Yes, and that Control.Monad.Identity is the right name (and that the transformers package is supposed to be usable in its own right).
Since mtl-split is not a drop-in replacement for mtl, we cannot expect a quick change from mtl to mtl-split in all the packages that currently import mtl. Thus we have to think about a route of transition and a package which can be installed in parallel to mtl is a first step, I think.
My understanding is that GHC will allow both to be installed, and allow packages that use transformers and those that use mtl to be used together in the same program. What you can't do is use both transformers and mtl directly in the same package, but that's no big loss.

On Mon, 5 Jan 2009, Ross Paterson wrote:
On Mon, Jan 05, 2009 at 12:54:20PM +0100, Henning Thielemann wrote:
Since mtl-split is not a drop-in replacement for mtl, we cannot expect a quick change from mtl to mtl-split in all the packages that currently import mtl. Thus we have to think about a route of transition and a package which can be installed in parallel to mtl is a first step, I think.
My understanding is that GHC will allow both to be installed, and allow packages that use transformers and those that use mtl to be used together in the same program. What you can't do is use both transformers and mtl directly in the same package, but that's no big loss.
If this is true, then I will no longer complain. What about Hugs and others?

On Mon, Jan 05, 2009 at 01:43:14PM +0100, Henning Thielemann wrote:
On Mon, 5 Jan 2009, Ross Paterson wrote:
My understanding is that GHC will allow both to be installed, and allow packages that use transformers and those that use mtl to be used together in the same program. What you can't do is use both transformers and mtl directly in the same package, but that's no big loss.
If this is true, then I will no longer complain. What about Hugs and others?
Hugs should be OK: it won't complain about a conflict, and the modules of the same name will be compatible. I don't think any other compilers support functional dependencies, so they would have no mtl to preserve.

On Mon, 5 Jan 2009, Ross Paterson wrote:
On Mon, Jan 05, 2009 at 09:32:21AM +0100, Henning Thielemann wrote:
I also like to have a function 'state', which replaces the former 'State' constructor. I can also submit a patch if you want that.
You mean
state :: (s -> (a, s)) -> State s a state f = StateT (Identity . f)
and similarly for all the others? Sounds reasonable.
You have already added them, thanks! Maybe you can even add 'stateT' and the likes in order to give programmers a way of staying independent from the particular definition of StateT.

On Mon, 5 Jan 2009, Ross Paterson wrote:
On Mon, Jan 05, 2009 at 09:32:21AM +0100, Henning Thielemann wrote:
How about Control.Monad.Trans.Identity which is re-exported by Control.Monad.Identity in mtl?
Hmm, it's a conflict between co-existing with mtl and using the Right Name for the transformers package, which is intended to be usable by itself. I prefer the latter, myself.
It's me again ... The package contains Control.Monad.Trans which also conflicts with mtl. Maybe it can be split into Control.Monad.Trans.Class Control.Monad.IO.Class Which would no longer conflict with mtl and is cleaner I think (or did anyone, who wanted to import MonadIO class, expect it in Control.Monad.Trans?)

I have uploaded these to hackage. The packages are: transformers: monad transformers, operations and liftings. This is all Haskell 98, and be used on its own, or as a base for packages defining monad classes. monads-fd: monad classes using functional dependencies, with instances for the transformers in the transformers package. This is mostly backwards-compatible with mtl. monads-tf: monad classes using type families, with instances for the transformers in the transformers package. This is mostly backwards-compatible with mtl-tf.

On Sat, 10 Jan 2009, Ross Paterson wrote:
I have uploaded these to hackage. The packages are:
transformers: monad transformers, operations and liftings. This is all Haskell 98, and be used on its own, or as a base for packages defining monad classes.
monads-fd: monad classes using functional dependencies, with instances for the transformers in the transformers package. This is mostly backwards-compatible with mtl.
monads-tf: monad classes using type families, with instances for the transformers in the transformers package. This is mostly backwards-compatible with mtl-tf.
Great! (will all people associate 'transformers' with 'monad transformers'?)

On Sat, 10 Jan 2009, Ross Paterson wrote:
I have uploaded these to hackage. The packages are:
transformers: monad transformers, operations and liftings. This is all Haskell 98, and be used on its own, or as a base for packages defining monad classes.
What are the changes from transformers-0.0.1.0 to transformers-0.1.0.0 ?

On Sat, 10 Jan 2009, Ross Paterson wrote:
On Sat, Jan 10, 2009 at 10:20:59PM +0100, Henning Thielemann wrote:
What are the changes from transformers-0.0.1.0 to transformers-0.1.0.0 ?
Instances for Applicative and Alternative.
In order to let this work with old versions of base, you will have to import the special-functors compatibility package.

Am Samstag, 10. Januar 2009 22:30 schrieb Ross Paterson:
On Sat, Jan 10, 2009 at 10:20:59PM +0100, Henning Thielemann wrote:
What are the changes from transformers-0.0.1.0 to transformers-0.1.0.0 ?
Instances for Applicative and Alternative.
Great! And we should try to make Applicative a superclass of Monad and drop MonadPlus in favor of Alternative + Monad. It would be probably even better to have somethink like Alternative/MonadPlus for functors (since functors are the most general concept at this point) and drop Alternative and MonadPlus (or use the name „Alternative“ for this new class). It’s terrible to explain all this legacy (Applicative not being superclass of Monad, two different classes for monoid functors) to students and to mention Applicative in a class context which already mentions Monad. However, we’ll probably need something like John Meachem’s class alias proposal to make such a transition as smooth as possible. Anyone who wants to hack GHC in this regard? Best wishes, Wolfgang

On Mon, Jan 12, 2009 at 04:26:16PM +0100, Wolfgang Jeltsch wrote:
And we should try to make Applicative a superclass of Monad and drop MonadPlus in favor of Alternative + Monad. It would be probably even better to have somethink like Alternative/MonadPlus for functors (since functors are the most general concept at this point) and drop Alternative and MonadPlus (or use the name 'Alternative' for this new class). It's terrible to explain all this legacy (Applicative not being superclass of Monad, two different classes for monoid functors) to students and to mention Applicative in a class context which already mentions Monad.
The legacy hierarchy is a problem with transformers. Some of them are Applicative transformers: instance (Monoid w, Applicative m) => Applicative (WriterT w m) instance (Applicative m) => Applicative (ReaderT r m) so they're also defined as Functor transformers: instance (Functor m) => Functor (WriterT w m) instance (Functor m) => Functor (ReaderT r m) So far so good. But some others require the argument to be a Monad: instance (Monad m) => Applicative (StateT s m) instance (Monad m) => Applicative (ErrorT e m) but to be Applicative they must also be Functor, so we keep the old instances: instance (Monad m) => Functor (StateT s m) instance (Monad m) => Functor (ErrorT e m) We could change these to assume Functor, but then we'd have to add a Functor constraint to the Applicative instances. Hmm, on second thoughts that's probably the right way to go.

G'day all.
Quoting Ross Paterson
I agree. I had a go at such a restructuring of mtl a while ago:
http://darcs.haskell.org/packages/transformers/ http://darcs.haskell.org/packages/mtl-split/
I'm curious if anyone has tried restructuring MTL with coproducts rather than transformers. Coproducts seem more "natural", if slightly harder to write. Cheers, Andrew Bromage

Am Montag, 5. Januar 2009 01:53 schrieb ajb@spamcop.net:
I'm curious if anyone has tried restructuring MTL with coproducts rather than transformers. Coproducts seem more "natural", if slightly harder to write.
Don’t know about coproducts but it sounds interesting. ;-) Do coproducts provide a way to compose different kinds of effects (state transformations, environment dependencies, etc.)? I always found it a bit annoying that types like StateT don’t cover just one concept but two: a specific effect (state transformations in this case) and composition of effects. Best wishes, Wolfgang

Hello, it’s already problematic, that State, StateT etc. are under Control.Monad. While they are monads, they are also applicative functors, for example. And some “monad transformers” are also applicative functor transformers and probably all of them are functor transformers. There are situations where you want to use these types only as applicative functors, for example when composing context-free parsers. Since they are all functors at least, it might be sensible to put them under Control.Functor. Or it might be a good idea to put them under Data in the module hierarchy. That way, a compatibility package could provide the old interface under Control.Monad and new stuff would be situated under Control.Functor or Data. During this restructuring, we could also rename State to StateTrans since values of State are not states but state transformers. There are similar problems with Cont since values of Cont type are not continuations but functions from continuations to results. It’s problematic when you deal with states and state transformers or continuations and Cont values. How do you name your local variables? I’d like to say “state” for a state but it would also be sensible to say “state” for a value of type State, i.e., a state transformer. Comments? Ideas? Best wishes, Wolfgang

On Mon, 12 Jan 2009, Wolfgang Jeltsch wrote:
Hello,
it?s already problematic, that State, StateT etc. are under Control.Monad. While they are monads, they are also applicative functors, for example. And some ?monad transformers? are also applicative functor transformers and probably all of them are functor transformers. There are situations where you want to use these types only as applicative functors, for example when composing context-free parsers.
I already posted something similar, with no response: http://www.haskell.org/pipermail/libraries/2007-October/008274.html Maybe this time is better?
During this restructuring, we could also rename State to StateTrans since values of State are not states but state transformers.
Right, I also like to use 'state' as identifier for a state, not for a stateful action. And I was confused, by Reader not being really a counterpart to Writer. If I want to read, what I wrote with Writer, I usually have to use a State monad, not Reader. 'Context' or 'Environment' seems to be a better name for 'Reader'.
participants (4)
-
ajb@spamcop.net
-
Henning Thielemann
-
Ross Paterson
-
Wolfgang Jeltsch