Re: [Haskell-cafe] How to make callCC more dynamic

2011-08-27 Thread oleg

 ContT {runContT :: forall r1 . (forall r2 . a- m r2) - m r1}
 callCC can be defined, however, you can not run it, and reset couldn't
 type check

Indeed you cannot. As the articles
http://okmij.org/ftp/continuations/undelimited.html

explain, the answer of _undelimited_ continuation is not available
to the program itself. You really cannot write runUndelimitedCont --
just as you cannot write runIO. Once you in the monad of undelimited
continuations, you cannot get out of it -- just you cannot get out of
IO. Since reset is the composition of runCont and return, reset is not
expressible either.

The article above explains that in detail (see the CPS2 attempt). The
article also shows how to cheat.

This exercise points out that undelimited continuations are really not
useful. In fact, I don't know of any practical application of them.
I'm deeply puzzled why people insist on using callCC given how useless
it is by itself (without other effects such as mutation). If one uses
callCC and runCont, one deals with _delimited_ continuation. Why not
to use shift then, which has a bit more convenient interface.

Do you have a specific code that you want to write using ContT? It
is generally more productive to discuss a concrete example.





___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] How to make callCC more dynamic

2011-08-26 Thread bob zhang
Thank you, there is also a nice link here :-)
http://stackoverflow.com/questions/7178919/how-to-make-callcc-more-dynamic
and for this type,
ContT {runContT :: forall r1 . (forall r2 . a- m r2) - m r1}
callCC can be defined, however, you can not run it, and reset couldn't
type check
于 11-8-25 上午1:53, o...@okmij.org 写道:
 bob zhang wrote:
 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.
 Precisely that problem was discussed in  
   http://okmij.org/ftp/continuations/undelimited.html#proper-contM

 Your ContT is CPS1 in the above article. The article shows why you
 cannot write callCC with the above type of ContT. The article talks
 about other types. BTW, if you faithfully defined the monad for
 undelimited control than shift/reset cannot be expressed. Undelimited
 continuations are strictly less expressible than delimited ones. The
 above page gives the pointers to the papers with the proof.




___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] How to make callCC more dynamic

2011-08-25 Thread Ertugrul Soeylemez
bob zhang bobzhang1...@gmail.com wrote:

   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/



___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] How to make callCC more dynamic

2011-08-24 Thread 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

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

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] How to make callCC more dynamic

2011-08-24 Thread Jason Dagit
On Wed, Aug 24, 2011 at 9:19 AM, bob zhang bobzhang1...@gmail.com 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

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] How to make callCC more dynamic

2011-08-24 Thread Ertugrul Soeylemez
bob zhang bobzhang1...@gmail.com wrote:

 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/



___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] How to make callCC more dynamic

2011-08-24 Thread bob zhang
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 dag...@gmail.com wrote:

 On Wed, Aug 24, 2011 at 9:19 AM, bob zhang bobzhang1...@gmail.com 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
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] How to make callCC more dynamic

2011-08-24 Thread oleg

bob zhang wrote:
 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.

Precisely that problem was discussed in  
http://okmij.org/ftp/continuations/undelimited.html#proper-contM

Your ContT is CPS1 in the above article. The article shows why you
cannot write callCC with the above type of ContT. The article talks
about other types. BTW, if you faithfully defined the monad for
undelimited control than shift/reset cannot be expressed. Undelimited
continuations are strictly less expressible than delimited ones. The
above page gives the pointers to the papers with the proof.



___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe