restructuring the mtl

Iavor Diatchki iavor.diatchki at gmail.com
Thu Mar 8 20:57:43 EST 2007


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 <stefanor at cox.net> wrote:
> 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 at haskell.org
> http://www.haskell.org/mailman/listinfo/libraries
>


More information about the Libraries mailing list