How to define a common return and bind?

Hello, Suppose you have defined a monad transformer such as:
newtype T1 m a = T1 { unT1 :: A1 m a }
Where 'A1 m' is an arbitrary monad of your choosing. For this discussion we just take the identity:
type A1 m a = m a -- (can be any monad)
If you want to define a Monad instance for 'T1 m' you generally do this: instance Monad m => Monad (T1 m) where return = T1 . return m >>= f = T1 $ unT1 m >>= unT1 . f (I know I can use the 'GeneralizedNewtypeDeriving' language extension to automatically derive a Monad but suppose that isn't available) Now when I define a new monad transformer:
newtype T2 m a = T2 { unT2 :: A2 m a }
Where 'A2 m' is again an arbitrary monad of your choosing but for now just the identity:
type A2 m a = m a -- (can be any monad)
The Monad instance for it is almost completely identical to the former: instance Monad m => Monad (T2 m) where return = T2 . return m >>= f = T2 $ unT2 m >>= unT2 . f Note that the only differences are: * a function to convert from the outer monad _to_ the inner monad: 'unT1' and 'unT2' * a function to convert _from_ the inner monad to the outer monad: 'T1' and 'T2' The common parts seem to be: liftReturn from = from . return liftBind from to m f = from $ to m >>= to . f My question is: can these be given suitable and general enough types so that they can be used to define Monad instances for monad transformers? In other words can I use them to write: instance Monad m => Monad (T1 m) where return = liftReturn T1 (>>=) = liftBind T1 unT1 and: instance Monad m => Monad (T2 m) where return = liftReturn T2 (>>=) = liftBind T2 unT2 Thanks, Bas

Hi,
You can do things like that for "new" monads that are isomorphic to
existing ones. Take a look at the MonadLib.Derive package from
MonadLib (http://hackage.haskell.org/packages/archive/monadLib/3.5.2/doc/html/MonadLib...).
More specifically, the functions "derive_return" and "derive_bind"
might be of interest. A more general property for monad transformers
is that you can always define the "return" of the new monad in terms
of the "return" of the underlying monad and "lift":
return_new x = lift (return x)
This works because, in general, "lift" should be a "monad morphism".
Hope that this helps,
Iavor
On Thu, Apr 9, 2009 at 3:40 AM, Bas van Dijk
Hello,
Suppose you have defined a monad transformer such as:
newtype T1 m a = T1 { unT1 :: A1 m a }
Where 'A1 m' is an arbitrary monad of your choosing. For this discussion we just take the identity:
type A1 m a = m a -- (can be any monad)
If you want to define a Monad instance for 'T1 m' you generally do this:
instance Monad m => Monad (T1 m) where return = T1 . return m >>= f = T1 $ unT1 m >>= unT1 . f
(I know I can use the 'GeneralizedNewtypeDeriving' language extension to automatically derive a Monad but suppose that isn't available)
Now when I define a new monad transformer:
newtype T2 m a = T2 { unT2 :: A2 m a }
Where 'A2 m' is again an arbitrary monad of your choosing but for now just the identity:
type A2 m a = m a -- (can be any monad)
The Monad instance for it is almost completely identical to the former:
instance Monad m => Monad (T2 m) where return = T2 . return m >>= f = T2 $ unT2 m >>= unT2 . f
Note that the only differences are:
* a function to convert from the outer monad _to_ the inner monad: 'unT1' and 'unT2'
* a function to convert _from_ the inner monad to the outer monad: 'T1' and 'T2'
The common parts seem to be:
liftReturn from = from . return liftBind from to m f = from $ to m >>= to . f
My question is: can these be given suitable and general enough types so that they can be used to define Monad instances for monad transformers?
In other words can I use them to write:
instance Monad m => Monad (T1 m) where return = liftReturn T1 (>>=) = liftBind T1 unT1
and:
instance Monad m => Monad (T2 m) where return = liftReturn T2 (>>=) = liftBind T2 unT2
Thanks,
Bas _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

On Fri, Apr 10, 2009 at 5:19 AM, Iavor Diatchki
You can do things like that for "new" monads that are isomorphic to existing ones. Take a look at the MonadLib.Derive package from MonadLib
Thanks! This is exactly what I want: ---------------------------------------- import MonadLib.Derive newtype T1 m a = T1 { unT1 :: A1 m a } type A1 m a = m a newtype T2 m a = T2 { unT2 :: A2 m a } type A2 m a = m a isoT1 = Iso T1 unT1 isoT2 = Iso T2 unT2 instance Monad m => Monad (T1 m) where return = derive_return isoT1 (>>=) = derive_bind isoT1 instance Monad m => Monad (T2 m) where return = derive_return isoT2 (>>=) = derive_bind isoT2 ---------------------------------------- Now I'm wondering if the derive_* functions can be overloaded using something like this. Note that the following doesn't typecheck: ---------------------------------------- {-# LANGUAGE MultiParamTypeClasses #-} {-# LANGUAGE RankNTypes #-} {-# LANGUAGE FunctionalDependencies #-} {-# LANGUAGE FlexibleInstances #-} ---------------------------------------- class Iso m n | m -> n, n -> m where close :: forall a. m a -> n a open :: forall a. n a -> m a deriveReturn :: (Monad m, Monad n, Iso m n) => a -> n a deriveReturn = close . return deriveBind :: (Monad m, Iso m n) => n a -> (a -> n b) -> n b deriveBind m k = close $ open m >>= open . k ---------------------------------------- newtype T1 m a = T1 { unT1 :: A1 m a } type A1 m a = m a instance Iso m (T1 m) where close = T1 open = unT1 instance Monad m => Monad (T1 m) where return = deriveReturn (>>=) = deriveBind ---------------------------------------- regards, Bas

Now I'm wondering if the derive_* functions can be overloaded using something like this. Note that the following doesn't typecheck:
----------------------------------------
{-# LANGUAGE MultiParamTypeClasses #-} {-# LANGUAGE RankNTypes #-} {-# LANGUAGE FunctionalDependencies #-} {-# LANGUAGE FlexibleInstances #-}
----------------------------------------
class Iso m n | m -> n, n -> m where close :: forall a. m a -> n a open :: forall a. n a -> m a
deriveReturn :: (Monad m, Monad n, Iso m n) => a -> n a deriveReturn = close . return
deriveBind :: (Monad m, Iso m n) => n a -> (a -> n b) -> n b deriveBind m k = close $ open m >>= open . k
----------------------------------------
newtype T1 m a = T1 { unT1 :: A1 m a } type A1 m a = m a
instance Iso m (T1 m) where close = T1 open = unT1
instance Monad m => Monad (T1 m) where return = deriveReturn (>>=) = deriveBind
----------------------------------------
Hi, I changed a line, It type checks. But I can't explain why your version does not type check. --- iso_orig.hs 2009-04-10 17:56:12.000000000 +0900 +++ iso.hs 2009-04-10 17:56:36.000000000 +0900 @@ -5,7 +5,7 @@ ---------------------------------------- -class Iso m n | m -> n, n -> m where +class Iso m n | n -> m where close :: forall a. m a -> n a open :: forall a. n a -> m a Thanks, Hashimoto

On Fri, Apr 10, 2009 at 11:15 AM, Yusaku Hashimoto
Hi, I changed a line, It type checks. But I can't explain why your version does not type check.
Thanks, I can't explain it either because I don't completely understand functional dependencies. So I rewrote it using type families which I find much easier to understand: ---------------------------------------- {-# LANGUAGE RankNTypes #-} {-# LANGUAGE TypeFamilies #-} {-# LANGUAGE FlexibleContexts #-} module Iso where class Iso m where type Inner m :: * -> * close :: forall a. Inner m a -> m a open :: forall a. m a -> Inner m a deriveReturn :: (Monad (Inner m), Iso m) => a -> m a deriveReturn = close . return deriveBind :: (Monad (Inner m), Iso m) => m a -> (a -> m b) -> m b deriveBind m k = close $ open m >>= open . k ---------------------------------------- newtype T1 m a = T1 { unT1 :: A1 m a } type A1 m a = m a instance Iso (T1 m) where type Inner (T1 m) = m close = T1 open = unT1 instance Monad m => Monad (T1 m) where return = deriveReturn (>>=) = deriveBind ---------------------------------------- You can also get a Monad instance "for free" if you aren't afraid of UndecidableInstances: ---------------------------------------- {-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE UndecidableInstances #-} instance (Monad (Inner m), Iso m) => Monad m where return = deriveReturn (>>=) = deriveBind ---------------------------------------- This seems useful. Does this exists somewhere on hackage? regards, Bas

On 2009/04/10, at 20:32, Bas van Dijk wrote:
So I rewrote it using type families which I find much easier to understand:
Cool. Type family version is easier to read and understand for me.
This seems useful. Does this exists somewhere on hackage?
I glanced at Monad category in package list, It seemed that There is no package like this. I hope you to upload your package! Thanks, Hashimoto

Hi,
On Fri, Apr 10, 2009 at 1:28 AM, Bas van Dijk
Now I'm wondering if the derive_* functions can be overloaded using something like this. Note that the following doesn't typecheck:
----------------------------------------
{-# LANGUAGE MultiParamTypeClasses #-} {-# LANGUAGE RankNTypes #-} {-# LANGUAGE FunctionalDependencies #-} {-# LANGUAGE FlexibleInstances #-}
----------------------------------------
class Iso m n | m -> n, n -> m where close :: forall a. m a -> n a open :: forall a. n a -> m a
If the intention is to capture the idea of an isomorphism between monads, then the functional dependencies on the class are not correct. For example, they assert that a monad can be isomorphic to at most one other monad, which is not true. For example, you can have two different monads that ar implemented in the same way under the hood: newtype T1 a = T1 { unT1 :: MyMonad a } newtype T2 a = T2 { unT2 :: MyMonad a } instance Iso MyMonad T1 where ... instance Iso MyMonad T2 where ... This violates the first functional dependency that you wrote. On the other hand, for the task at hand, we know that if we know the "derived" monad, then we will always know its implementation exactly. So the following concept might be more appropriate: class DerivedM new old | new -> old where close :: old a -> new a open :: new a -> old a Now it certainly makes sense to define the following instances: instance DerivedM T1 MyMonad where ... instance DerivedM T2 MyMonad where ... Note that this is essentially what Yusaku did by removing the one functional dependency (although the arguments of DerivedM are in the opposite order from the arguments of Iso). This is also exactly what you did when you rewrote the example to use type families. I kind of like this idea because it removes the need to use the rank-2 type extension, so I might try to implement it in monadLib. Thanks! -Iavor PS: You said that you find type families easier to understand then functional dependencies. While I can certainly believe that, I would encourage you to try to understand the concept of a functional dependency (which in actuality is not that complicated at all). It is a single concept that is useful in many situations, even ones that go beyond Haskell programming (e.g., database design). It will also help you understand much better the multitude of related Haskell extensions (associated type synonyms, associated data types, type families).
participants (3)
-
Bas van Dijk
-
Iavor Diatchki
-
Yusaku Hashimoto