My situation is fairly similar to Gabor's, and, like him, I was able to make do with an equality superclass.  However, instead of combining two classes, I found that I needed to add a third.

My concept here is to create two monads which share much of their functionality, but not all of it.  Specifically, one of them is "high" and one is "low".  Values of type "Low" encapsulate computations in the low monad, and values of type "High" encapsulate values in the high monad.  Both low and high monads can *create* Low and High values and *execute* Low values, but only the high monad can *execute* High values.

So, what I'd like to write is:

data High a

data Low a

class (Monad m, MonadLow (LowM m), MonadHigh (HighM m)) => MonadLow m where
  execLow :: Low a -> m a
  type LowM m :: * -> *
  mkLow :: LowM m a -> m (Low a)
  type HighM m :: * -> *
  mkHigh :: HighM m a -> m (High a)

class MonadLow m => MonadHigh m where
  execHigh :: High a -> m a

data L a

data H a

instance Monad L

instance MonadLow L where
    type LowM L = L
    type HighM L = H

instance Monad H

instance MonadLow H where
    type LowM H = L
    type HighM H = H

instance MonadHigh H

Of course, this has a superclass cycle.  Instead, I can write:

...
class Monad m => MonadLow m where
...
class (MonadHigh m, MonadLow (LowM m), HighM m ~ m, HighM (LowM m) ~ m, LowM (LowM m) ~ LowM m) => MonadHigh' m where {}

Then I can use MonadHigh' wherever I might have instead used MonadHigh, and achieve roughly the result I was looking for.  However, it doesn't seem like a very clean definition to me.

That being said, I haven't found any problem with using the MonadHigh' approach, although I've just recently started investigating it.


Ryan


2011/7/22 Dan Doel <dan.doel@gmail.com>
2011/7/22 Gábor Lehel <illissius@gmail.com>:
> Yeah, this is pretty much what I ended up doing. As I said, I don't
> think I lose anything in expressiveness by going the MPTC route, I
> just think the two separate but linked classes way reads better. So
> it's just a "would be nice" thing. Do recursive equality superclasses
> make sense / would they be within the realm of the possible to
> implement?

Those equality superclasses are not recursive in the same way, as far
as I can tell. The specifications for classes require that there is no
chain:

   C ... => D ... => E ... => ... => C ...

However, your example just had (~) as a context for C, but C is not
required by (~). And the families involved make no reference to C,
either. A fully desugared version looks like:

   type family Frozen a :: *
   type family Thawed a :: *

   class (..., Thawed (Frozen t) ~ t) => Mutable t where ...

I think this will be handled if you use a version where equality
superclasses are allowed.

-- Dan

_______________________________________________
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users