Delimited Continuations: Optimise tail-resumptive operations
Summary
When implemented in terms of delimited continuation primops, the operations of many effects such as Reader
and State
turn out to be tail-resumptive.
An effect operation is tail-resumptive if it is implemented as control# tag (\k -> k e)
, where k
does not occur in e
.
Rough example, assuming the delim control primops have been wrapped for IO
(main point is the impl of ask
):
data Reader r a = MkReader (PromptTag# a) (IORef r)
newtype Eff a = MkEff (IO a) deriving ...
withReader :: r -> (Reader r a -> Eff r) -> Eff r
withReader r f = MkEff $ do
tag <- newPromptTag
io_ref <- newIORef r
prompt tag (case f (MkReader tag io_ref) of MkEff m -> m)
ask :: Reader r a -> Eff r
ask (MkReader tag io_ref) = MkEff $ readIORef ref >>= \v -> control0 tag (\k -> k v)
Do note that the impl of the effect operation ask
is tail-resumptive.
Any such tail-resumptive effect operation can be optimised such that the control0#
is cancelled away, and with it a costly copying of the stack (%):
prompt# tag (E[control# tag (\k -> k e))
-->
prompt# tag (E[pure e])
For the implementation of ask, we equivalently get
ask :: Reader r a -> Eff r
ask (MkReader tag io_ref) = MkEff $ readIORef ref >>= \v -> pure v
It's easy to see that this is far more efficient.
(This is important when writing custom effect operations, to be interpreted by e.g. effectful
's interpret
.)
I suggest we implement the rewrite rule (%) above in the Simplifier. The tail-call test should be pretty cheap; just check that k
occurs at most once on each branch, and in tail position.