Proposal: add replay function to Control.Monad.Cont.Class

I'd like to propose adding the following function (method?) to Control.Monad.Cont.Class, possibly with another name: replay :: MonadCont m => m (m a) replay = callCC $ pure . fix Using this in a do-notation block allows one to bind a name to the sub-block that starts immediately after. I reached for continuations to try to get this behavior for use with recursive flows without disrupting the reading of the main forward flow and found how to do it in https://jsdw.me/posts/haskell-cont-monad/ under the name "goto". While "goto" is as familiar as a name can be, I feel "replay" more accurately conveys, that you can only 'go back', by stating what actually is happening - that a sub-block we're currently evaluating is replayed from its beginning. As a motivating example, here's the same recursive IO flow written in 3 ways - one with replay, one with fix, and one with where clauses. {-# LANGUAGE LambdaCase #-} import Control.Monad.Cont.Class (MonadCont(callCC)) import Control.Monad.IO.Class (MonadIO, liftIO) import Control.Monad.Trans.Cont (evalContT) import Data.Function (fix) import Text.Read (readMaybe) replay :: MonadCont m => m (m a) replay = callCC $ pure . fix prompt :: MonadIO m => String -> m String prompt t = liftIO $ do putStrLn t putStr "> " getLine flowContT :: IO () flowContT = evalContT $ do liftIO $ putStrLn "Welcome to the totally not contrived game" numberPromptStep <- replay readMaybe <$> prompt "Pick a number" >>= \case Nothing -> liftIO (putStrLn "Not a number") *> numberPromptStep Just n -> liftIO $ putStrLn $ "You picked " <> show (n :: Int) exitPromptStep <- replay prompt "Stop? y/n" >>= \case "y" -> pure () "n" -> numberPromptStep _ -> liftIO (putStrLn "Invalid choice") *> exitPromptStep flowFix :: IO () flowFix = do putStrLn "Welcome to the totally not contrived game" fix $ \numberPromptStep -> do readMaybe <$> prompt "Pick a number" >>= \case Nothing -> liftIO (putStrLn "Not a number") *> numberPromptStep Just n -> liftIO $ putStrLn $ "You picked " <> show (n :: Int) fix $ \exitPromptStep -> do prompt "Stop? y/n" >>= \case "y" -> pure () "n" -> numberPromptStep _ -> liftIO (putStrLn "Invalid choice") *> exitPromptStep flowWhere :: IO () flowWhere = do putStrLn "Welcome to the totally not contrived game" numberPromptStep where numberPromptStep = do readMaybe <$> prompt "Pick a number" >>= \case Nothing -> liftIO (putStrLn "Not a number") *> numberPromptStep Just n -> do liftIO $ putStrLn $ "You picked " <> show (n :: Int) exitPromptStep exitPromptStep = do prompt "Stop? y/n" >>= \case "y" -> pure () "n" -> numberPromptStep _ -> liftIO (putStrLn "Invalid choice") *> exitPromptStep

On Sun, Mar 07, 2021 at 03:25:16AM +0000, Alexandre Esteves wrote:
replay :: MonadCont m => m (m a) replay = callCC $ pure . fix
Using this in a do-notation block allows one to bind a name to the sub-block that starts immediately after. I reached for continuations to try to get this behavior for use with recursive flows without disrupting the reading of the main forward flow and found how to do it in https://jsdw.me/posts/haskell-cont-monad/ under the name "goto".
While "goto" is as familiar as a name can be, I feel "replay" more accurately conveys, that you can only 'go back', by stating what actually is happening - that a sub-block we're currently evaluating is replayed from its beginning.
Looks like a "label" more than a "goto" to me. Would "label" be a good name?

I rather like label. +1 from me. On Sun, Mar 7, 2021 at 1:25 AM Tom Ellis < tom-lists-haskell-cafe-2017@jaguarpaw.co.uk> wrote:
replay :: MonadCont m => m (m a) replay = callCC $ pure . fix
Using this in a do-notation block allows one to bind a name to the sub-block that starts immediately after. I reached for continuations to try to get this behavior for use with recursive flows without disrupting the reading of the main forward flow and found how to do it in https://jsdw.me/posts/haskell-cont-monad/ under
On Sun, Mar 07, 2021 at 03:25:16AM +0000, Alexandre Esteves wrote: the
name "goto".
While "goto" is as familiar as a name can be, I feel "replay" more accurately conveys, that you can only 'go back', by stating what actually is happening - that a sub-block we're currently evaluating is replayed from its beginning.
Looks like a "label" more than a "goto" to me. Would "label" be a good name? _______________________________________________ Libraries mailing list Libraries@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries

Yeah
On Sun, Mar 7, 2021 at 12:16 PM Edward Kmett
I rather like label. +1 from me.
On Sun, Mar 7, 2021 at 1:25 AM Tom Ellis < tom-lists-haskell-cafe-2017@jaguarpaw.co.uk> wrote:
replay :: MonadCont m => m (m a) replay = callCC $ pure . fix
Using this in a do-notation block allows one to bind a name to the sub-block that starts immediately after. I reached for continuations to try to get this behavior for use with recursive flows without disrupting the reading of the main forward flow and found how to do it in https://jsdw.me/posts/haskell-cont-monad/ under
On Sun, Mar 07, 2021 at 03:25:16AM +0000, Alexandre Esteves wrote: the
name "goto".
While "goto" is as familiar as a name can be, I feel "replay" more accurately conveys, that you can only 'go back', by stating what actually is happening - that a sub-block we're currently evaluating is replayed from its beginning.
Looks like a "label" more than a "goto" to me. Would "label" be a good name? _______________________________________________ Libraries mailing list Libraries@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries
_______________________________________________ Libraries mailing list Libraries@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries

I kind of don't like it, because the continuation doesn't return anything
but itself. I'd prefer something that works more like the setjmp function
in C, taking a value and returning the value plus a function that lets it
return the new value:
setJump :: MonadCont m => a -> m (a -> m b, a)
setJump a = callCC $ \k -> let
go b = k (go, b)
in pure (go, a)
On Sun, Mar 7, 2021, 11:36 Carter Schonwald
Yeah
On Sun, Mar 7, 2021 at 12:16 PM Edward Kmett
wrote: I rather like label. +1 from me.
On Sun, Mar 7, 2021 at 1:25 AM Tom Ellis < tom-lists-haskell-cafe-2017@jaguarpaw.co.uk> wrote:
replay :: MonadCont m => m (m a) replay = callCC $ pure . fix
Using this in a do-notation block allows one to bind a name to the sub-block that starts immediately after. I reached for continuations to try to get this behavior for use with recursive flows without disrupting the reading of the main forward flow and found how to do it in https://jsdw.me/posts/haskell-cont-monad/ under
On Sun, Mar 07, 2021 at 03:25:16AM +0000, Alexandre Esteves wrote: the
name "goto".
While "goto" is as familiar as a name can be, I feel "replay" more accurately conveys, that you can only 'go back', by stating what actually is happening - that a sub-block we're currently evaluating is replayed from its beginning.
Looks like a "label" more than a "goto" to me. Would "label" be a good name? _______________________________________________ Libraries mailing list Libraries@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries
_______________________________________________ Libraries mailing list Libraries@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries
_______________________________________________ Libraries mailing list Libraries@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries

This does sound more useful!
What are some simple expressivity examples for the two?
On Sun, Mar 7, 2021 at 1:36 PM Zemyla
I kind of don't like it, because the continuation doesn't return anything but itself. I'd prefer something that works more like the setjmp function in C, taking a value and returning the value plus a function that lets it return the new value:
setJump :: MonadCont m => a -> m (a -> m b, a) setJump a = callCC $ \k -> let go b = k (go, b) in pure (go, a)
On Sun, Mar 7, 2021, 11:36 Carter Schonwald
wrote: Yeah
On Sun, Mar 7, 2021 at 12:16 PM Edward Kmett
wrote: I rather like label. +1 from me.
On Sun, Mar 7, 2021 at 1:25 AM Tom Ellis < tom-lists-haskell-cafe-2017@jaguarpaw.co.uk> wrote:
On Sun, Mar 07, 2021 at 03:25:16AM +0000, Alexandre Esteves wrote:
replay :: MonadCont m => m (m a) replay = callCC $ pure . fix
Using this in a do-notation block allows one to bind a name to the sub-block that starts immediately after. I reached for continuations to try to get this behavior for use with recursive flows without disrupting the reading of the main forward flow and found how to do it in https://jsdw.me/posts/haskell-cont-monad/ under the name "goto".
While "goto" is as familiar as a name can be, I feel "replay" more accurately conveys, that you can only 'go back', by stating what actually is happening - that a sub-block we're currently evaluating is replayed from its beginning.
Looks like a "label" more than a "goto" to me. Would "label" be a good name? _______________________________________________ Libraries mailing list Libraries@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries
_______________________________________________ Libraries mailing list Libraries@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries
_______________________________________________ Libraries mailing list Libraries@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries

Why not both?
On Sun, Mar 7, 2021, 1:36 PM Zemyla
I kind of don't like it, because the continuation doesn't return anything but itself. I'd prefer something that works more like the setjmp function in C, taking a value and returning the value plus a function that lets it return the new value:
setJump :: MonadCont m => a -> m (a -> m b, a) setJump a = callCC $ \k -> let go b = k (go, b) in pure (go, a)
On Sun, Mar 7, 2021, 11:36 Carter Schonwald
wrote: Yeah
On Sun, Mar 7, 2021 at 12:16 PM Edward Kmett
wrote: I rather like label. +1 from me.
On Sun, Mar 7, 2021 at 1:25 AM Tom Ellis < tom-lists-haskell-cafe-2017@jaguarpaw.co.uk> wrote:
On Sun, Mar 07, 2021 at 03:25:16AM +0000, Alexandre Esteves wrote:
replay :: MonadCont m => m (m a) replay = callCC $ pure . fix
Using this in a do-notation block allows one to bind a name to the sub-block that starts immediately after. I reached for continuations to try to get this behavior for use with recursive flows without disrupting the reading of the main forward flow and found how to do it in https://jsdw.me/posts/haskell-cont-monad/ under the name "goto".
While "goto" is as familiar as a name can be, I feel "replay" more accurately conveys, that you can only 'go back', by stating what actually is happening - that a sub-block we're currently evaluating is replayed from its beginning.
Looks like a "label" more than a "goto" to me. Would "label" be a good name? _______________________________________________ Libraries mailing list Libraries@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries
_______________________________________________ Libraries mailing list Libraries@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries
_______________________________________________ Libraries mailing list Libraries@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries
_______________________________________________ Libraries mailing list Libraries@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries

Agreed that 'label' is a better name than goto/replay.
It didn't even hit me until I saw setJump that `m (m a)` doesn't allow
representing recursive functions with arguments, so `a -> m(a -> m b, a)`
does seem much more expressive to me
Starting with my original examples, introducing the recursive binding when
there are arguments would look like
`(numberPromptStep, (x,y)) <- setJump (x0, y0)`
`fix $ \numberPromptStep x y -> do`
`numberPromptStep x y = do`
It is slightly annoying that the later 2 can simply add an argument while
setJump requires using the uncurried version but I don't see a way around
that since >>= itself works that way
`m (m a)` is essentially the 0-tuple version of `a -> m(a -> m b, a)` which
makes me wonder if it's even worth having. Sure, it's convenient not to
have these unit/() around, but maybe the same argument (heh) could be made
for 2-argument and 3-argument versions.
do
numberPromptStep <- setJump
(..)
numberPromptStep
do
(numberPromptStep, x, y) <- setJump2 x0 y0
(..)
numberPromptStep x' y'
Given that, I think `a -> m (a -> m b, a)` is the important one be it
called label or setJump and maybe there can be a specialized 0-tuple
version (e.g. label_ / setJump_) offering the `m (m a)` special case. I
don't feel strongly about it though, since unlike `for_` it wouldn't
actually relax constraints, only have a simpler signature.
On Sun, Mar 7, 2021 at 7:33 PM David Feuer
Why not both?
On Sun, Mar 7, 2021, 1:36 PM Zemyla
wrote: I kind of don't like it, because the continuation doesn't return anything but itself. I'd prefer something that works more like the setjmp function in C, taking a value and returning the value plus a function that lets it return the new value:
setJump :: MonadCont m => a -> m (a -> m b, a) setJump a = callCC $ \k -> let go b = k (go, b) in pure (go, a)
On Sun, Mar 7, 2021, 11:36 Carter Schonwald
wrote: Yeah
On Sun, Mar 7, 2021 at 12:16 PM Edward Kmett
wrote: I rather like label. +1 from me.
On Sun, Mar 7, 2021 at 1:25 AM Tom Ellis < tom-lists-haskell-cafe-2017@jaguarpaw.co.uk> wrote:
On Sun, Mar 07, 2021 at 03:25:16AM +0000, Alexandre Esteves wrote:
replay :: MonadCont m => m (m a) replay = callCC $ pure . fix
Using this in a do-notation block allows one to bind a name to the sub-block that starts immediately after. I reached for continuations to try to get this behavior for use with recursive flows without disrupting the reading of the main forward flow and found how to do it in https://jsdw.me/posts/haskell-cont-monad/ under the name "goto".
While "goto" is as familiar as a name can be, I feel "replay" more accurately conveys, that you can only 'go back', by stating what actually is happening - that a sub-block we're currently evaluating is replayed from its beginning.
Looks like a "label" more than a "goto" to me. Would "label" be a good name? _______________________________________________ Libraries mailing list Libraries@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries
_______________________________________________ Libraries mailing list Libraries@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries
_______________________________________________ Libraries mailing list Libraries@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries
_______________________________________________ Libraries mailing list Libraries@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries
_______________________________________________ Libraries mailing list Libraries@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries
participants (6)
-
Alexandre Esteves
-
Carter Schonwald
-
David Feuer
-
Edward Kmett
-
Tom Ellis
-
Zemyla