Ashley Yakeley writes:
> Are there any useful monads that are instances of both MonadCont and
> MonadFix? I can't make the two meet. Perhaps this is because
> continuations have no fixed point, or something. Very annoying.
If you have a recursive monad with first-class references (such as IO
or ST s), you can define a continuation monad on top of it with an
instance of MonadFix I enclose below. The instance seems to make
sense operationally, but as Levent Erk�k has pointed out, it doesn't
satisfy the left-shrinking axiom for recursive monads:
fixM (\x -> a >>= f x) == a >>= \y -> fixM (\x -> f x y)
This axiom comes from Levent's and John Launchbury's ICFP'00
paper, see
http://www.cse.ogi.edu/PacSoft/projects/rmb/
Moreover, I suspect that the instance breaks the axiom for callcc,
which shows how any evaluation context E can be pushed inside a
callcc:
E[callcc e] = callcc (\k' -> E[e (\z -> k' (E[z]))]
This is for callcc without monadic types, see Sabry's and Friedman's
paper on "Recursion is a Computational Effect", at
http://www.cs.indiana.edu/hyplan/sabry/papers/
/M
--
class Monad m => FixMonad m where
fixM :: (a -> m a) -> m a
class Monad m => Ref m r | m -> r where
newRef :: a -> m (r a)
readRef :: r a -> m a
writeRef :: r a -> a -> m ()
newtype C m a = C ((a -> m ()) -> m ())
deC (C m) = m
instance (FixMonad m, Ref m r) => FixMonad (C m) where
fixM m = C $ \k -> do
x <- newRef Nothing
a <- fixM $ \a -> do
deC (m a) $ \a -> do
ma <- readRef x
case ma of
Nothing -> do writeRef x (Just a)
Just _ -> k a
ma <- readRef x
case ma of
Just a -> return a
Nothing -> error "fixM"
k a
_______________________________________________
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe