[Haskell-cafe] How to define a common return and bind?

Iavor Diatchki iavor.diatchki at gmail.com
Thu Apr 9 23:19:06 EDT 2009


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-Derive.html).
 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 <v.dijk.bas at gmail.com> wrote:
> 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 at haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>


More information about the Haskell-Cafe mailing list