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

Bas van Dijk v.dijk.bas at gmail.com
Fri Apr 10 04:28:56 EDT 2009


On Fri, Apr 10, 2009 at 5:19 AM, Iavor Diatchki
<iavor.diatchki at gmail.com> wrote:
> 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


More information about the Haskell-Cafe mailing list