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

Iavor Diatchki iavor.diatchki at gmail.com
Sat Apr 11 11:12:37 EDT 2009


Hi,

On Fri, Apr 10, 2009 at 1:28 AM, Bas van Dijk <v.dijk.bas at gmail.com> wrote:

> 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).


More information about the Haskell-Cafe mailing list