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

Pepe Iborra mnislaih at gmail.com
Mon Feb 26 10:46:51 EST 2007


David Roundy <droundy <at> darcs.net> writes:
> 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.



Did anyone with knowledge of Associated Types pursue this solution? 
It doesn't work with GHC head, and I can't really do anything about that.
Mostly curiosity. 

Thanks
pepe


----------------------------------------------------------------
Everything from here on is to convince GMane that, even if my message 
contains more quoted text than fresh text, it is a legitimate message and it 
should be ok to post it. 



More information about the Haskell-Cafe mailing list