restructuring the mtl

I propose that we restructure and split the mtl into two packages: mtl-base: a Haskell-98 package containing the monad transformers and non-overloaded versions of the operations, e.g. module Control.Monad.Trans.State where newtype StateT s m a = StateT { runStateT :: s -> m (a,s) } type State s = StateT s Identity instance (Functor m) => Functor (StateT s m) instance (Monad m) => Monad (StateT s m) instance (MonadPlus m) => MonadPlus (StateT s m) instance (MonadFix m) => MonadFix (StateT s m) get :: (Monad m) => StateT s m s put :: (Monad m) => s -> StateT s m () liftStateT :: Monad m => m a -> StateT s m a mtl (depending on mtl-base): multi-parameter+FD type classes with instances for the transformers in mtl-base, e.g. module Control.Monad.State where import qualified Control.Monad.Trans.Error as Error import qualified Control.Monad.Trans.Reader as Reader import qualified Control.Monad.Trans.State as State import qualified Control.Monad.Trans.Writer as Writer class (Monad m) => MonadState s m | m -> s where get :: m s put :: s -> m () instance (Monad m) => MonadState s (StateT s m) instance (Error e, MonadState s m) => MonadState s (ErrorT e m) instance (MonadState s m) => MonadState s (ReaderT r m) instance (Monoid w, MonadState s m) => MonadState s (WriterT w m) One benefit is that it would be possible to use monad transformers in portable programs, at the cost of a little explicit lifting of operations. Often when I use a stack of monad transformers, I define aliases for the new monad and its operations, so this wouldn't be much extra effort. A second benefit is that one could introduce other packages with other interfaces, e.g. one using associated types. The revised mtl would be almost compatible with the existing one, except 1) The monad transformer and corresponding monad would have the same strictness (this has already been done in the HEAD). 2) It wouldn't be possible to declare instances for the corresponding monad.

On Wed, Mar 07, 2007 at 11:59:24PM +0000, Ross Paterson wrote:
I propose that we restructure and split the mtl into two packages:
Thank you, I was just thinking the same thing, but I would never have thought to publically challenge the mtl folks :)
mtl-base: a Haskell-98 package containing the monad transformers and non-overloaded versions of the operations, e.g.
Why can't we have: class MonadTrans t where lift :: Monad m => m a -> t m a looks perfectly H98 to me. both ghci-6.7.20070223 -fno-glasgow-exts and hugs +98 accept it.
mtl (depending on mtl-base): multi-parameter+FD type classes with instances for the transformers in mtl-base, e.g.
Would it also now be possible to get my metalift operation in mtl? class MonadTrans t where lift :: Monad m => m a -> t m a metalift :: (Monad m, Monad m') => (forall a. m1 a -> m2 a) -> t m a -> t m' b It is often useful in practice, for instance metalift lift can be used at type State s a -> StateT s IO a (a suprisingly common request on #haskell). Disclaimer: I have been able to write instances for all mtl transformers *except ContT*, and it seems plausible that ContT may force the class to be split. Stefan

On Wed, Mar 07, 2007 at 04:11:59PM -0800, Stefan O'Rear wrote:
Why can't we have:
class MonadTrans t where lift :: Monad m => m a -> t m a
Yes, we could.
metalift :: (Monad m, Monad m') => (forall a. m a -> m' a) -> t m a -> t m' b
This is a functor on the category of monads -- definitely useful.
Disclaimer: I have been able to write instances for all mtl transformers *except ContT*, and it seems plausible that ContT may force the class to be split.
You and Moggi both (Remark 4.1.11 of "An Abstract View of Programming Languages").

Hi,
If you like metalift you might like these too :-)
-Iavor
newtype Morph m n = M (forall a. m a -> n a)
-- indexed monad on the category of monads
class (MonadT (t i), MonadT (t j), MonadT (t k))
=> TMon t i j k | t i j -> k where
bindT :: (Monad m) => Morph m (t i m) -> t j m a -> t k m a
instance TMon ReaderT i j (i,j) where
bindT (M f) m = do ~(i,j) <- ask
lift (runReaderT i (f (runReaderT j m)))
instance TMon StateT i j (i,j) where
bindT (M f) m = do ~(i,j) <- get
~(~(a,i'),j') <- lift (runStateT i (f (runStateT j m)))
set (i,j)
return a
instance (Monoid i, Monoid j) => TMon WriterT i j (i,j) where
bindT (M f) m = do ~(~(a,j),i) <- lift (runWriterT (f (runWriterT m)))
put (i,j)
return a
instance TMon ExceptionT i j (Either i j) where
bindT (M f) m = do x <- lift (runExceptionT (f (runExceptionT m)))
case x of
Left i -> raise (Left i)
Right (Left j) -> raise (Right j)
Right (Right a) -> return a
On 3/7/07, Stefan O'Rear
On Wed, Mar 07, 2007 at 11:59:24PM +0000, Ross Paterson wrote:
I propose that we restructure and split the mtl into two packages:
Thank you, I was just thinking the same thing, but I would never have thought to publically challenge the mtl folks :)
mtl-base: a Haskell-98 package containing the monad transformers and non-overloaded versions of the operations, e.g.
Why can't we have:
class MonadTrans t where lift :: Monad m => m a -> t m a
looks perfectly H98 to me. both ghci-6.7.20070223 -fno-glasgow-exts and hugs +98 accept it.
mtl (depending on mtl-base): multi-parameter+FD type classes with instances for the transformers in mtl-base, e.g.
Would it also now be possible to get my metalift operation in mtl?
class MonadTrans t where lift :: Monad m => m a -> t m a metalift :: (Monad m, Monad m') => (forall a. m1 a -> m2 a) -> t m a -> t m' b
It is often useful in practice, for instance metalift lift can be used at type State s a -> StateT s IO a (a suprisingly common request on #haskell).
Disclaimer: I have been able to write instances for all mtl transformers *except ContT*, and it seems plausible that ContT may force the class to be split.
Stefan _______________________________________________ Libraries mailing list Libraries@haskell.org http://www.haskell.org/mailman/listinfo/libraries

ross:
I propose that we restructure and split the mtl into two packages:
mtl-base: a Haskell-98 package containing the monad transformers and non-overloaded versions of the operations, e.g.
module Control.Monad.Trans.State where
newtype StateT s m a = StateT { runStateT :: s -> m (a,s) }
type State s = StateT s Identity
instance (Functor m) => Functor (StateT s m) instance (Monad m) => Monad (StateT s m) instance (MonadPlus m) => MonadPlus (StateT s m) instance (MonadFix m) => MonadFix (StateT s m)
get :: (Monad m) => StateT s m s put :: (Monad m) => s -> StateT s m ()
liftStateT :: Monad m => m a -> StateT s m a
mtl (depending on mtl-base): multi-parameter+FD type classes with instances for the transformers in mtl-base, e.g.
module Control.Monad.State where
import qualified Control.Monad.Trans.Error as Error import qualified Control.Monad.Trans.Reader as Reader import qualified Control.Monad.Trans.State as State import qualified Control.Monad.Trans.Writer as Writer
class (Monad m) => MonadState s m | m -> s where get :: m s put :: s -> m ()
instance (Monad m) => MonadState s (StateT s m)
instance (Error e, MonadState s m) => MonadState s (ErrorT e m) instance (MonadState s m) => MonadState s (ReaderT r m) instance (Monoid w, MonadState s m) => MonadState s (WriterT w m)
One benefit is that it would be possible to use monad transformers in portable programs, at the cost of a little explicit lifting of operations. Often when I use a stack of monad transformers, I define aliases for the new monad and its operations, so this wouldn't be much extra effort.
A second benefit is that one could introduce other packages with other interfaces, e.g. one using associated types.
The revised mtl would be almost compatible with the existing one, except 1) The monad transformer and corresponding monad would have the same strictness (this has already been done in the HEAD). 2) It wouldn't be possible to declare instances for the corresponding monad.
I think this is a great idea. The use of monads and monad transformers from the mtl is really a key part of larger Haskell programming these days. We need to ensure this is as portable as possible. -- Don

yes. I like this idea very much. on a related note dealing with the mtl, can we get rid of the reexporting of names from different modules? it is a real pain whenever you need to hide something. I have code like import Control.Monad hiding(join) import Control.Monad.State hiding(join) ... import Prelude hiding(and,or,any,all,(&&),(||)) import Data.List hiding(and,or,any,all) ... in my opinion there are only a couple valid times to re-export names from a different module 1) when providing a public interface to a private implementation. such as the re-exporting of names from GHC.*. but note, this should only be done if the implementation truely is private and not normally used. 2) when providing an omnibus collection of related public interfaces. such as Foreign.C, the important thing is that it _just_ re-exports names. it does not add any new functions so you will never be forced to include Foreign.C, it just might be more convinient sometimes depending on what you are doing. Control.Monad.* and Prelude + haskell98 libraries are particularly bad about this sort of thing. John -- John Meacham - ⑆repetae.net⑆john⑈

On Wed, Mar 07, 2007 at 11:59:24PM +0000, Ross Paterson wrote:
I propose that we restructure and split the mtl into two packages:
mtl-base: a Haskell-98 package containing the monad transformers and non-overloaded versions of the operations, [...]
mtl (depending on mtl-base): multi-parameter+FD type classes with instances for the transformers in mtl-base, [...]
One benefit is that it would be possible to use monad transformers in portable programs, at the cost of a little explicit lifting of operations. Often when I use a stack of monad transformers, I define aliases for the new monad and its operations, so this wouldn't be much extra effort.
A second benefit is that one could introduce other packages with other interfaces, e.g. one using associated types.
The revised mtl would be almost compatible with the existing one, except 1) The monad transformer and corresponding monad would have the same strictness (this has already been done in the HEAD). 2) It wouldn't be possible to declare instances for the corresponding monad.
I have had a go at this re-organization: src: darcs get http://darcs.haskell.org/packages/mtl-split docs: http://www.soi.city.ac.uk/~ross/mtl-split/ The plan is to split Control.Monad.Identity, Control.Monad.Trans and Control.Monad.Trans.* off into a separate (portable) package.

Hi I'm not a massive Control.Monad user, but:
The plan is to split Control.Monad.Identity, Control.Monad.Trans and Control.Monad.Trans.* off into a separate (portable) package.
Isn't Control.Monad.Identity very simple, very short and totally Haskell 98? Why can't it go in the standard MTL? I've only used State and Identity out of all the monads in MTL. Thanks Neil

On Mon, Mar 26, 2007 at 08:18:53PM +0100, Neil Mitchell wrote:
The plan is to split Control.Monad.Identity, Control.Monad.Trans and Control.Monad.Trans.* off into a separate (portable) package.
Isn't Control.Monad.Identity very simple, very short and totally Haskell 98? Why can't it go in the standard MTL?
The point was to make all the above modules pure Haskell 98, leaving a non-portable (but mostly backward-compatible) mtl package as a thin wrapper.

Speaking of Identity, are there compelling reasons for it to be under
Control.Monad? Of course Identity is a Monad, but it's in many other type
classes as well. Similarly, I wonder why Monad is under Control, since
monads are not always about control.
More deeply, I wonder if type classes and module hierarchy are adversarial
notions. Type classes are powerful because they cut across many different
kinds of uses. Thus exactly where they're useful, they're also hard to
classify (assign to a slot in the hierarchy).
Just to be clear: I'm raising an issue for discussion. I don't have a
proposal or even a direction.
- Conal
On 3/26/07, Neil Mitchell
Hi
I'm not a massive Control.Monad user, but:
The plan is to split Control.Monad.Identity, Control.Monad.Trans and Control.Monad.Trans.* off into a separate (portable) package.
Isn't Control.Monad.Identity very simple, very short and totally Haskell 98? Why can't it go in the standard MTL? I've only used State and Identity out of all the monads in MTL.
Thanks
Neil _______________________________________________ Libraries mailing list Libraries@haskell.org http://www.haskell.org/mailman/listinfo/libraries
participants (7)
-
Conal Elliott
-
dons@cse.unsw.edu.au
-
Iavor Diatchki
-
John Meacham
-
Neil Mitchell
-
Ross Paterson
-
Stefan O'Rear