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

Ertugrul Soeylemez es at ertes.de
Wed Sep 8 22:14:32 EDT 2010


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


-- 
nightmare = unsafePerformIO (getWrongWife >>= sex)
http://ertes.de/




More information about the Haskell-Cafe mailing list