
Hi David, I don't think you need functional dependencies or associated type synonyms to get your example to work. In the past, I have used the abstraction that you are describing (I call it an "indexed monad" and it has a nice categorical definition). Here is how you can define it:
class IxMonad m where (>>>=) :: m i j a -> (a -> m j k b) -> m i k b ret :: a -> m i i a
Next, you wanted to define an instances that captured the fact that any monad is trivially an indexed monad. Here is how you can do this:
newtype FromMonad m i j a = M { unM :: m a }
instance Monad m => IxMonad (FromMonad m) where ret x = M (return x) M m >>>= f = M (m >>= (unM . f))
We use a newtype to prevent this instance overlapping with other instances. And just for fun we can define another indexed monad: state that supports "strong updates" (i.e., the type of the state can change as you compute):
newtype State i j a = S { unS :: i -> (a,j) }
instance IxMonad State where ret x = S (\s -> (x,s)) S m >>>= f = S (\s1 -> let (a,s2) = m s1 in unS (f a) s2)
Here are some operations to access and modify the state:
get :: State s s s get = S (\s -> (s,s))
set :: s1 -> State s2 s1 s2 set s1 = S (\s2 -> (s2,s1))
Notice that swapping "s1" and "s2" results in a type error. Nice. Also by choosing different operations one can enforce other properties. Now lets try it out:
test = set True >>>= \x -> set 'a' >>>= \y -> ret (x,y)
And it is all Haskell 98! Another interesting example of
an indexed monad is the continuation monad (I noticed that
from Wadler's "Composable Continuations" paper).
I hope this helps!
-Iavor
On 12/17/06, David Roundy
Here's a sketch of an idea as a solution to my dilemma, which unfortunately requires associated types. Any suggestions how it might be translatable into functional dependencies? (I should say, I've not got a HEAD ghc, and am just going by memory on my indexed types syntax.)
class Witness w where type M w a b (>>=) :: M w a b x -> (x -> M w b c y) -> M w a c y (>>) :: M w a b x -> M w b c y -> M w a c y f >> g = f >>= const g return :: x -> M w a a x fail :: String -> M w a b x
instance Monad m => Witness m where M m a b = m (>>=) = Prelude.(>>=) (>>) = Prelude.(>>) return = Prelude.return fail = Prelude.fail
with these definitions it seems that any existing monad will continue to work as it always had, but I can now add new special sorts of monadish objects, such as
data RepositoryMonad a b x = RM ... instance Witness RepositoryMonad where M RepositoryMonad x y = RepositoryMonad x y ...
which would allow me to create a monad in which the actions are limited according to witness types, such as
applyPatchToWorking :: Patch a b -> RepositoryMonad (rec,a) (rec,b) () -- David Roundy http://www.darcs.net _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe