[Haskell-cafe] Re: ANNOUNCE: GotoT-transformers version 1.0

Gregory Crosswhite gcross at phys.washington.edu
Wed Sep 8 22:43:23 EDT 2010


 On 09/08/10 19:14, Ertugrul Soeylemez wrote:
> Gregory Crosswhite <gcross at phys.washington.edu> wrote:
>
>>  People want to believe that Haskell is a better language than C, but
>> how could this possibly be true when Haskell lacks the very basic
>> "goto" feature???  If the world is going to take Haskell seriously,
>> then this serious blight needs to be addressed immediately!  Thus I
>> proud to present to you the "GotoT-transformers" package which
>> provides this missing functionality and so finally makes Haskell a
>> serious contender with C.
> Have you looked at ContT from monadLib?  It's not just a goto, but in
> fact a setjmp/longjmp, i.e. a goto with value.  I haven't used it for
> anything yet, but it might come in handy for some algorithms:
>
>   import Data.List
>   import MonadLib
>   import Text.Printf
>
>   myComp :: ContT (Maybe Int) IO (Maybe Int)
>   myComp = do
>     (i, beginning) <- labelCC 0
>     inBase $ printf "Current value: %i (type q to quit)\n" i
>     query <- inBase getLine
>     when ("q" `isPrefixOf` query) $ abort (Nothing :: Maybe Int)
>     when (i < 10) $ jump (i+1) beginning
>     return $ Just i
>
>   main :: IO ()
>   main = runContT return myComp >>=
>          printf "Final result: %s\n" . maybe "none" show
>
>
> Greets,
> Ertugrul
>
>

Whoa, that's cool!  I glanced at monadLib but I didn't realize that it
let you create labels that you could return to like that.  :-)  (I know
of callCC, but that isn't quite the same as this.)  Thanks for the pointer!

The limitation with continuation-based approaches to goto, though, is
that you can only jump back to points that you've seen before.  The
reason why I don't use a continuation-based approach in GotoT is because
I wanted the user (i.e., me, and maybe one or two other people if I'm
lucky :-) ) to be able to jump to an arbitrary point outside the
calculation that has never been visited before, rather than returning a
previously visited point of the same calculation.

Of course, if someone can prove to me that I am wrong and that GotoT
semantics can be implemented with continuations, then I would welcome
this information.  :-)

Cheers,
Greg



More information about the Haskell-Cafe mailing list