[Haskell-cafe] AT solution: rebinding >>= for restricted monads

David Roundy droundy at darcs.net
Tue Dec 19 11:58:51 EST 2006


On Tue, Dec 19, 2006 at 10:08:12AM -0500, Jacques Carette wrote:
> David Roundy wrote:
> >The trouble is that your solution doesn't allow you to use do-notation with
> >the IxMonad.  And if you did allow yourself to use do-notation by rebinding
> >(>>=), etc, then you wouldn't be able to use ordinary monads with
> >do-notation in the same module.  That's what makes things tricky, since an
> >IxMonad is different-kinded from Monad, so you can't make a monad an
> >instance of IxMonad.
> >  
> Seems to me that this screams for camlp4.  Oops, wrong language ;-)
> 
> But seriously, this kind of thing seems to arise often enough that 
> having a standard method for doing "syntax extensions" for Haskell seems 
> like a good idea.

Rebinding the do notation is at least reasonably clean, it's just that we
don't want to lose the ability to mix with ordinary monads.  I'm not sure
that syntax extensions are very often a good idea...

> And as far as making Monad instances for IxMonad, this is where partial 
> application at the class level would come in rather handy.  Seems to be 
> that (at least) IxMonad m () () should be a Monad.

Indeed, that's true, but it's hard to go the other way around, but it is
possible (I believe) to go the other way around with associated types.  My
latest attemp (which won't compile with the HEAD ghc that I just compiled,
probably because I haven't figured out the synatax for guards with indexed
types is:

class WitnessMonad m where
    type W m :: * -> * -> *
    (>>=) :: (WitnessMonad m', WitnessMonad m'',
              w a b = W m', w b c = W m'', w a c = W m)
          => m' x -> (x -> m'' y) -> m y
    (>>) :: (WitnessMonad m', WitnessMonad m'',
              w a b = W m', w b c = W m'', w a c = W m)
          => m' x -> m'' y -> m y
    f >> g = f >>= const g
    return :: w a a = W m x => -> m x
    fail :: String -> m x

data Witness a b

instance Monad m => WitnessMonad m where
    W m = Witness () ()
    (>>=) = Prelude.(>>=)
    (>>) = Prelude.(>>)
    return = Prelude.return
    fail = Prelude.fail

which I think is quite pretty.  It allows the Monadlike object to have kind
* -> *, while still allowing us to hide extra witness types inside and pull
them out using the W function.
-- 
David Roundy
http://www.darcs.net


More information about the Haskell-Cafe mailing list