Feasibility of native RTS support for continuations?

Simon Marlow marlowsd at gmail.com
Thu Feb 6 08:33:55 UTC 2020


On Sun, 2 Feb 2020 at 04:26, Alexis King <lexi.lambda at gmail.com> wrote:

> I took a stab at implementing this today, using the “continuation is a
> stack” implementation strategy I described in my previous email. I
> haven’t tried very hard to break it yet, but this tiny test program
> works:
>
>     {-# LANGUAGE BangPatterns, BlockArguments, MagicHash,
>                  ScopedTypeVariables, UnboxedTuples #-}
>
>     import GHC.Prim
>     import GHC.Types
>
>     data Continuation a b = Continuation# (Continuation# RealWorld a b)
>
>     reset :: IO a -> IO a
>     reset (IO m) = IO (reset# m)
>
>     shift :: (Continuation a b -> IO b) -> IO a
>     shift f = IO (shift# \k -> let !(IO m) = f (Continuation# k) in m)
>
>     applyContinuation :: Continuation a b -> a -> IO b
>     applyContinuation (Continuation# k) a = IO (applyContinuation# k a)
>
>     main :: IO ()
>     main = do
>       ns <- reset do
>         n <- shift \(k :: Continuation Integer [Integer]) -> do
>           a <- applyContinuation k 2
>           b <- applyContinuation k 3
>           pure (a ++ b)
>         pure [n]
>       print ns
>
> The output of this program is [2, 3], as expected.
>

That's impressive!


>
> My implementation doesn’t share any code with raiseAsync. Currently, it
> isn’t very clever:
>
>     * reset# pushes a RET_SMALL frame with a well-known info pointer,
>       &stg_reset_frame_info.
>
>     * shift# walks the stack and copies it up to the nearest reset
>       frame. If the stack consists of several chunks, it only copies the
>       chunk that contains the reset frame, and it just repurposes the
>       other chunks as the continuation (since the stack is unwinding
>       anyway).
>
>     * applyContinuation# copies the captured stack and updates the
>       UNDERFLOW frames as needed to point to the current stack.
>
>     * I haven’t implemented it yet, but it would be straightforward to
>       implement an applyContinuationOneShot# operation that works like
>       applyContinuation#, but doesn’t actually copy anything and just
>       updates the UNDERFLOW frames in the captured stack itself.
>
> This seems to work in my very simple examples, but there are also things
> I know it doesn’t handle properly:
>
>     * It doesn’t make any attempt to handle modifications to the
>       interrupt masking state properly. The right thing to do here is
>       probably to look for mask/unmask frames on the stack during
>       unwinding and to stash that information somewhere.
>
>     * It doesn’t do anything special for UPDATE_FRAMEs, so if there’s an
>       UPDATE_FRAME that owns a blackhole on the stack, things will go
>       quite wrong.
>
>       I haven’t been worrying about this because I don’t think there
>       should ever be any update frames between shift# and reset#. In the
>       case of raiseAsync, the location of the “prompt” is well-defined:
>       it’s the update frame. But shift# captures up to an explicit
>       prompt, so using shift# when there’s an update frame on the stack
>       can surely only lead to nonsense... right?
>
>     * It doesn’t do anything special for STM frames, so trying to
>       capture a continuation through those will be similarly broken.
>

Yes, these are all the things that make raiseAsync tricky! You can either
copy what raiseAsync does (but be warned, it has taken a lot of iteration
to get right) or try to use raiseAsync and/or modify it to do what you want.

Cheers
Simon



> There are also probably bugs I don’t know about — I haven’t exercised
> the implementation very hard yet — but I’ll keep playing with it. If
> anyone is at all interested, I’ve pushed the code to a branch here:
>
>
> https://gitlab.haskell.org/lexi.lambda/ghc/compare/master...first-class-continuations
>
> My thanks again to everyone’s help!
>
> Alexis
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/ghc-devs/attachments/20200206/d62b28b1/attachment.html>


More information about the ghc-devs mailing list