How to make callCC more dynamic

Hi, all I thought the right type for ContT should be newtype ContT m a = ContT {runContT :: forall r. (a-> m r) -> m r} and other control operators shift :: Monad m => (forall r . (a-> ContT m r) -> ContT m r) -> ContT m a reset :: Monad m => ContT m a -> ContT m a callCC :: ((a-> (forall r . ContT m r)) -> ContT m a) -> ContT m a unfortunately, I can not make callCC type check, and don't know how to do it. I managed to make shift, reset type check reset :: Monad m => ContT m a -> ContT m a reset e = ContT $ \ k -> runContT e return >>= k shift :: Monad m => (forall r . (a-> ContT m r) -> ContT m r) -> ContT m a shift e = ContT $ \ (k :: a -> m r) -> runContT ((e $ \ v -> ContT $ \c -> k v >>= c) :: ContT m r) return but still, I cann't use shift, reset in recursive jumpings like this? newtype H r m = H (H r m -> ContT m r) unH (H x) = x test = flip runContT return $ reset $ do jump <- shift (\f -> f (H f)) lift . print $ "hello" unH jump jump Have anyone tried this before? Best, bob

On Wed, Aug 24, 2011 at 9:19 AM, bob zhang
Hi, all I thought the right type for ContT should be newtype ContT m a = ContT {runContT :: forall r. (a-> m r) -> m r} and other control operators shift :: Monad m => (forall r . (a-> ContT m r) -> ContT m r) -> ContT m a reset :: Monad m => ContT m a -> ContT m a callCC :: ((a-> (forall r . ContT m r)) -> ContT m a) -> ContT m a
unfortunately, I can not make callCC type check, and don't know how to do it. I managed to make shift, reset type check
Correct me if I'm wrong, but you're wanting to implement the delimited form of continuations? If so, you might take a look at this and the associated papers: http://hackage.haskell.org/package/CC-delcont Jason

Hi Jason, thanks for your reply.
I was curious that we could bring really continuations into haskell, the
traditional callCC brings a lot of unnecessary
type restrictions
On Wed, Aug 24, 2011 at 12:45 PM, Jason Dagit
On Wed, Aug 24, 2011 at 9:19 AM, bob zhang
wrote: Hi, all I thought the right type for ContT should be newtype ContT m a = ContT {runContT :: forall r. (a-> m r) -> m r} and other control operators shift :: Monad m => (forall r . (a-> ContT m r) -> ContT m r) -> ContT m a reset :: Monad m => ContT m a -> ContT m a callCC :: ((a-> (forall r . ContT m r)) -> ContT m a) -> ContT m a
unfortunately, I can not make callCC type check, and don't know how to do it. I managed to make shift, reset type check
Correct me if I'm wrong, but you're wanting to implement the delimited form of continuations?
If so, you might take a look at this and the associated papers: http://hackage.haskell.org/package/CC-delcont
Jason
-- Best, bob

bob zhang
I was curious that we could bring really continuations into haskell, the traditional callCC brings a lot of unnecessary type restrictions
That's where the misconception lies. The type parameter /is/ necessary for delimited continuations in Haskell. By the way, I don't see how these continuations would be in any way not "real" or how the type parameter places any "restrictions", unless of course you want dynamic typing. The only operations I can imagine, which really restrict the type parameter, are the operation of aborting the entire computation and manipulating the result of it: abort :: a -> ContT a m a mapContT :: (r -> r) -> ContT r m () You can have undelimited CPS without the type parameter, but then you won't get any CPS effects. As noted, you will just have an IdentityT-like monad transformer, which can at best improve the semantics of the underlying monad. Greets, Ertugrul -- nightmare = unsafePerformIO (getWrongWife >>= sex) http://ertes.de/

bob zhang
I thought the right type for ContT should be newtype ContT m a = ContT {runContT :: forall r. (a-> m r) -> m r}
No, that will effectively make it impossible to make use of CPS effects, hence turning your ContT into an IdentityT-like monad transformer, which can only change the semantics of the underlying monad. More concretely what you are implementing here is a codensity as you can find it in the monad-ran package by Edward K. Greets, Ertugrul -- nightmare = unsafePerformIO (getWrongWife >>= sex) http://ertes.de/
participants (3)
-
bob zhang
-
Ertugrul Soeylemez
-
Jason Dagit