ANNOUNCE: GotoT-transformers version 1.0

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. On a more serious note, there are times when it can be useful to not only abort a computation in the middle, but to then transfer the flow of execution to another computation: do [...stuff...] when condition1 $ goto x [...more stuff...] when condition2 $ goto y [...more stuff...] when condition3 $ goto z Towards this end, I developed this package which provides a GotoT monad transformer and a "goto" function that takes a monadic computation and returns a monadic value that has the effect of transferring control to the new computation. Obviously this functionality can be abused, but when it is the natural fit I believe that it is much better to use it directly then to go through all sorts of contortions resulting in uglier code just to avoid it on principle. The best implementation I could think of was to use a "trampoline" approach. The GotoT monadic transformer is represented by a type which contains (wrapped inside the inner monad) either a pure value or a monadic computation. The runGotoT function operates by returning the value if it is pure, and evaluating the monadic computation and feeding the result back into itself otherwise. The "trampoline" term refers to the fact that the flow of execution bounces back to the runGotoT function as long as the computation keeps calling the "goto" function. I hope that the community not only finds this functionality useful, but also that does not kill me for committing the egregious act of bringing "goto" into the Haskell world. Cheers, Greg

Gregory Crosswhite schrieb:
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.
To be honest, when writing mutually depending functions that extensively rely on tail recursion optimization, this often looks a lot like GOTO already.

On 09/08/10 12:55, Henning Thielemann wrote:
Gregory Crosswhite schrieb:
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. To be honest, when writing mutually depending functions that extensively rely on tail recursion optimization, this often looks a lot like GOTO already.
True. I guess we should make sure that nobody tells Dijkstra about Haskell then. :-) Cheers, Greg

Gregory Crosswhite
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/

On 09/08/10 19:14, Ertugrul Soeylemez wrote:
Gregory Crosswhite
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

On Wed, Sep 8, 2010 at 9:43 PM, Gregory Crosswhite
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. :-)
Here's an implementation of GotoT with double-continuations: http://hpaste.org/fastcgi/hpaste.fcgi/view?id=29823 I also have a sketch of me trying to use a single-continuation, but I was defeated: http://hpaste.org/fastcgi/hpaste.fcgi/view?id=29824 The idea is that on 'goto', we throw away the passed down continuation in favor of an alternate return. The double-continuation approach is a bit overkill since we don't have the equivalent of 'catch', to add local scope to an alternate return. My single continuation approach has two type-check errors I haven't been able to understand yet, but hopefully you can see what I was going for. Antoine

Gregory Crosswhite
On 09/08/10 19:14, Ertugrul Soeylemez wrote:
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:
[...]
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!
It is, in fact, callCC. ;)
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. :-)
I don't think you need 'goto' to implement jumps in Haskell. Note that functions as well as computations are first class: myComp :: ContT () IO () myComp = do input <- inBase $ putStrLn "Print something (y/n)?" >> getLine unless ("y" `isPrefixOf` input) exit inBase $ putStrLn "Something." input <- inBase $ putStrLn "Print more (y/n)?" >> getLine unless ("y" `isPrefixOf` input) exit inBase $ putStrLn "More." where exit = do inBase $ putStrLn "Ok, I'm exiting." abort () You can interpret 'exit' as a label. Binding can be interpreted as a jump. Greets, Ertugrul -- nightmare = unsafePerformIO (getWrongWife >>= sex) http://ertes.de/

On Wed, Sep 8, 2010 at 11:54 PM, Ertugrul Soeylemez
Gregory Crosswhite
wrote: On 09/08/10 19:14, Ertugrul Soeylemez wrote:
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:
[...]
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!
It is, in fact, callCC. ;)
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. :-)
I don't think you need 'goto' to implement jumps in Haskell. Note that functions as well as computations are first class:
To recover from my overly complex previous post, here is a much simply goto based on existing monad transformers:
goto :: Monad m => ContT r m r -> ContT r m a goto (ContT m) = ContT $ \_ -> m return
Reading your post, Ertugrul, made something click for me Antoine

Antoine Latter
I don't think you need 'goto' to implement jumps in Haskell. Note that functions as well as computations are first class:
To recover from my overly complex previous post, here is a much simply goto based on existing monad transformers:
goto :: Monad m => ContT r m r -> ContT r m a goto (ContT m) = ContT $ \_ -> m return
Reading your post, Ertugrul, made something click for me
Yeah, that's a great functional CPS-based goto, which allows all kinds of spaghetti code. And it is in fact a real jump because of tail-call optimization. =) As a side note, the 'abort' function is implemented in a similar way. It ignores the continuation and jumps to an empty computation, that way it returns from the ContT computation. Greets, Ertugrul -- nightmare = unsafePerformIO (getWrongWife >>= sex) http://ertes.de/

To recover from my overly complex previous post, here is a much simply goto based on existing monad transformers:
goto :: Monad m => ContT r m r -> ContT r m a goto (ContT m) = ContT $ \_ -> m return
That doesn't actually work, though. Try running the following script: import Data.List import MonadLib goto :: Monad m => ContT r m r -> ContT r m a goto (ContT m) = ContT $ \_ -> m return myComp :: ContT () IO () myComp = do input <- inBase $ putStrLn "Print something (y/n)?" >> getLine unless ("y" `isPrefixOf` input) $ goto exit inBase $ putStrLn "Something." input <- inBase $ putStrLn "Print more (y/n)?" >> getLine unless ("y" `isPrefixOf` input) $ goto exit inBase $ putStrLn "More." where exit = do inBase $ putStrLn "Ok, I'm exiting." return () main :: IO () main = runContT return myComp

Okay, where that unpost button when I need it... :-) So, I hadn't noticed that the script that I copied and pasted didn't even compile because I was pressing "up enter" at the console to run it, but had forgotten that I was now working with a script with a new name and so all I was doing was running a different script over and over again! Doh. :-) Anyway, okay, I see your point now. The following script *does* work. import Data.List import Control.Monad import Control.Monad.IO.Class import Control.Monad.Trans.Cont goto :: Monad m => ContT r m r -> ContT r m a goto (ContT m) = ContT $ \_ -> m return myComp :: ContT () IO () myComp = do input <- liftIO $ putStrLn "Print something (y/n)?" >> getLine unless ("y" `isPrefixOf` input) $ goto exit liftIO $ putStrLn "Something." input <- liftIO $ putStrLn "Print more (y/n)?" >> getLine unless ("y" `isPrefixOf` input) $ goto exit liftIO $ putStrLn "More." where exit = do liftIO $ putStrLn "Ok, I'm exiting." return () main :: IO () main = runContT myComp return *HOWEVER*, if we replace main with main = runContT myComp (const $ putStrLn "I can't wait to print this string!") Then the program will be eternally disappointed because it will never actually get to print that string at the end. On 9/11/10 6:16 PM, Gregory Crosswhite wrote:
To recover from my overly complex previous post, here is a much simply goto based on existing monad transformers:
goto :: Monad m => ContT r m r -> ContT r m a goto (ContT m) = ContT $ \_ -> m return
That doesn't actually work, though. Try running the following script:
import Data.List
import MonadLib
goto :: Monad m => ContT r m r -> ContT r m a goto (ContT m) = ContT $ \_ -> m return
myComp :: ContT () IO () myComp = do input <- inBase $ putStrLn "Print something (y/n)?" >> getLine unless ("y" `isPrefixOf` input) $ goto exit inBase $ putStrLn "Something."
input <- inBase $ putStrLn "Print more (y/n)?" >> getLine unless ("y" `isPrefixOf` input) $ goto exit inBase $ putStrLn "More."
where exit = do inBase $ putStrLn "Ok, I'm exiting." return ()
main :: IO () main = runContT return myComp
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Gregory Crosswhite
Okay, where that unpost button when I need it... :-)
So, I hadn't noticed that the script that I copied and pasted didn't even compile because I was pressing "up enter" at the console to run it, but had forgotten that I was now working with a script with a new name and so all I was doing was running a different script over and over again! Doh. :-)
Happens. =)
Anyway, okay, I see your point now. The following script *does* work.
import Data.List
import Control.Monad import Control.Monad.IO.Class import Control.Monad.Trans.Cont
goto :: Monad m => ContT r m r -> ContT r m a goto (ContT m) = ContT $ \_ -> m return
myComp :: ContT () IO () myComp = do input <- liftIO $ putStrLn "Print something (y/n)?" >> getLine unless ("y" `isPrefixOf` input) $ goto exit liftIO $ putStrLn "Something."
input <- liftIO $ putStrLn "Print more (y/n)?" >> getLine unless ("y" `isPrefixOf` input) $ goto exit liftIO $ putStrLn "More."
where exit = do liftIO $ putStrLn "Ok, I'm exiting." return ()
main :: IO () main = runContT myComp return
*HOWEVER*, if we replace main with
main = runContT myComp (const $ putStrLn "I can't wait to print this string!")
Then the program will be eternally disappointed because it will never actually get to print that string at the end.
It should print the string, if the computation isn't aborted, i.e. if the last continuation, which you specify as an argument to runContT is reached. Greets, Ertugrul -- nightmare = unsafePerformIO (getWrongWife >>= sex) http://ertes.de/

On 9/11/10 10:36 PM, Ertugrul Soeylemez wrote:
It should print the string, if the computation isn't aborted, i.e. if the last continuation, which you specify as an argument to runContT is reached.
Greets, Ertugrul
That's true, it just seems to me like at that point the spirit of the continuation monad is being violated since the final continuation is never actually called. That isn't necessarily a big deal, but it is the kind of behavior that could bite someone if they weren't aware or forgot about it. Cheers, Greg

On Sun, Sep 12, 2010 at 1:19 AM, Gregory Crosswhite
That's true, it just seems to me like at that point the spirit of the continuation monad is being violated since the final continuation is never actually called. That isn't necessarily a big deal, but it is the kind of behavior that could bite someone if they weren't aware or forgot about it.
I guess you could newtype ConT to make GotoT, and then provide your own runner with `return` as the continuation, and then that detail doesn't escape. Or provide the `goto` combinator in the same module as a ContT runner which auto-passes a vacuous final continuation. Antoine
participants (4)
-
Antoine Latter
-
Ertugrul Soeylemez
-
Gregory Crosswhite
-
Henning Thielemann