MonadCont done right
Jump to navigation
Jump to search
The Cont class MonadCont [1] defined in the monad template library [2] could be improved if you are willing to use rank two polymorphism [3].
Notice the change in the signature of callCC
. This allows one to use the passed continuation in different situations inside a callCC
block. However, you will have to provide an explicit signature for the function you are calling callCC
with.
Possible implementation
newtype Cont r a = Cont { runCont :: ((a -> r) -> r) } -- r is the final result type of the whole computation
class (Monad m) => MonadCont m where
callCC :: ((a -> (forall b. m b)) -> m a) -> m a
instance Monad (Cont r) where
return a = Cont (\k -> k a) -- i.e. return a = \k -> k a
(Cont c) >>= f = Cont (\k -> c (\a -> runCont (f a) k)) -- i.e. c >>= f = \k -> c (\a -> f a k)
instance MonadCont (Cont r) where
callCC f = Cont (\k -> runCont (f (\a -> Cont (\_ -> k a))) k)
Alternative implementation
This implementation has the advantage that it provides a polymorphic version of callCC
for all instances of MonadCont from Control.Monad.Cont
. I also added shift
and reset
functions for using ComposableContinuations.
{-# OPTIONS -fglasgow-exts -fno-warn-unused-binds -cpp #-}
module ContExts (
callCC',
shift, reset, shiftT, resetT,
) where
import Control.Monad.Cont
-- Cont' m a is the type of a continuation expecting an a within the
-- continuation monad Cont m
type Cont' m a = forall r. a -> m r
callCC' :: forall a m. MonadCont m => (Cont' m a -> m a) -> m a
#if __GLASGOW_HASKELL__ > 602
callCC' f = callCC f' where
#else
callCC' (f :: ((a -> (forall b. m b)) -> m a) ) = callCC f' where
#endif
f' :: (a -> m (EmptyMonad m)) -> m a
f' g = f g' where
g' :: a -> m b
g' = (=<<) runEmptyMonad . g
-- ghc doesn't allow something like m (forall c. m c)
newtype EmptyMonad m = EmptyMonad { runEmptyMonad :: forall c. m c }
-- shift/reset for the Cont monad
shift :: ((a -> Cont s r) -> Cont r r) -> Cont r a
shift e = Cont $ \k -> e (return . k) `runCont` id
reset :: Cont a a -> Cont r a
reset e = return $ e `runCont` id
-- shiftT/resetT for the ContT monad transformer
shiftT :: Monad m => ((a -> ContT r m s) -> ContT s m s) -> ContT s m a
shiftT e = ContT $ \k -> e (lift . k) `runContT` return
resetT :: Monad m => ContT a m a -> ContT r m a
resetT e = lift $ e `runContT` return
All of this is presumably meant to be under the MIT license, since it wants to be in the library. --SamB 22:44, 30 October 2006 (UTC)