Forking and ContT (I)
Introduction
This is the first article in a series about continuations, forking, and monad transformers. Next article.
Motivation
When using
StateT
orReaderT
overIO
, we sometimes would like to fork and still remain in this “monadic context”, but alas:= flip evalStateT (0 :: Int) $ do main +1) modify ($ forkIO $ do liftIO <- get s -- ^ type error: we are in IO, -- no state to `get`. d'oh! print s ..
For StateT this makes a good deal of sense - what does “forking” mean for the state? But that leaves two questions: 1) What about ReaderT? For that, the semantics should be unproblematic; 2) What if we do not even want to continue the stateful computation in
main
? I.e. we want to “move” theStateT Int IO
instead of forking it.Is this possible without any hassle of manually tracking state/environment and passing it between threads?
Continuations are a well-known tool for turning your ordinary control flow into headache-inducing control rapids. They can be seen as the “goto” of functional programming. For some background knowledge, I can recommend the following sources:
- wikibooks.org on haskell/CPS[1] as general-purpose introduction; it contains this example of advanced control-flow-bending.
- wiki.haskell.org on delimited continuations[7] to explain the terms “delimited”/“undelimited”
- okmij.org collection of articles on continuations[5] for more in-depth topics and related research.
Considering just implementations in haskell, we can find the following monads:
newtype ContT r m a = ContT { runContT :: (a -> m r) -> m r }
from thetransformers
package;newtype CPS3 m a = CPS3 { unCPS3 :: (a -> m Void) -> m Void }
mentioned in [6];newtype Codensity m a = Codensity { runCodensity :: forall b. (a -> m b) -> m b }
e.g. in thekan-extensions
package.newtype LogicT m a = LogicT { unLogicT :: forall r. (a -> m r -> m r) -> m r -> m r }
from thelogict
package and the underlying paper [2].data FFree f a where Pure :: a -> FFree f a; Impure :: f x -> (x -> FFree f a) -> FFree f a
from the “Freer Monads, More Extensible Effects” paper [8]
This article will focus on the deterministic, undelimited, but forkable continuations, and for now we will stick with the simplest/most permissive definition 1).
Forking is in haskell represented by the primitive forkIO :: IO () -> IO ThreadId
operation. In the context of continuations however we can come up with more than one notion:
forkCont1 :: ContT () IO () -> ContT () IO () -- closest to forkIO
forkCont2 :: ContT () IO Bool -- more of a "classic" fork
moveToNewThread :: ContT () IO () -- call continuation in forkIO
= liftIO . void . forkIO . evalContT
forkCont1 = ContT $ \c -> void (forkIO $ c False) >> c True
forkCont2 = ContT $ \c -> void $ forkIO $ c () moveToNewThread
These are not new inventions, for example this thread on reddit [3] implements at least the first two (their implementation is different, but intended semantics are same).
Being essentially the equivalent of forkIO
, the first of these is not too interesting. Instead, we will have a closer look at moveToNewThread
.
The moveToNewThread
Primitive
moveToNewThread :: ContT () IO ()
= ContT $ \c -> void $ forkIO $ c () moveToNewThread
- It executes the continuation exactly once;
- In that sense, it does not fork; the thread does not “split” into two inside the
ContT () IO
monad; - However, from the perspective of the
evalContT
(orrun~
etc.) the operation returns immediately when amoveToNewThread
is encountered. And if weevalContT
from the main thread, we may have to be a bit careful thatmain
does not terminate before our continuation thread has finished. - The interaction with
resetT
is non-trivial. To not get lost, we will just pretendresetT
does not exist for the moment. - The interaction with any (asynchronous) exceptions is non-trivial. We will assume they don’t exist or are caught locally, for the time being.
To clarify, some equivalences
|
~ |
|
reminder: evalContT :: Monad m => ContT r m r -> m r
, i.e. the type of the whole expression must be IO ()
|
~ |
|
This last example shows a bit how moveToNewThread
“flattens” the notation of moving an execution to a different thread (similarly to how e.g. EitherT
flattens a series of actions that return Either
s).
Below are some use-cases for this expressiveness. However, there is at least one more curious property to this, having to do with transformer stacks and lifting. For this, we look back to plain forkIO
and how it interacts with lift
(we will use StateT Int
as some simple, specific transformer):
forkIO :: IO () -> IO ThreadId
. forkIO :: MonadTrans t => IO () -> t IO ThreadId -- in general
lift . forkIO :: IO () -> StateT Int IO ThreadId -- specialized lift
Where the argument unfortunately still is IO ()
and not StateT Int IO ()
, so this does not work too well. For forkCont1
, the base monad is ContT () IO
, but the problem is essentially the same: forking “loses the state”. However:
forkCont2 :: MonadTrans t => t (ContT () IO) Bool
lift moveToNewThread :: MonadTrans t => t (ContT () IO) ()
lift-- or, specialized to our stack:
forkCont2 :: StateT Int (ContT () IO) Bool
lift moveToNewThread :: StateT Int (ContT () IO) () lift
Isn’t that neat? If the base of our stack is ContT () IO
, we can lift “forks” (and “moves”). This gives some expressiveness to transformer stacks I was not aware of previously. So while in general ContT
can easily become more confusing than useful, this expressiveness is sufficient motivation to consider this a bit more closely. So how does this behave?
|
~ |
|
Note how we have to manually carry over the intermediate state s'
to the forked thread when using forkIO
, while we only need one top-level evalStateT
with moveToNewThread
.
Applications, in ascending complexity:
First application: Blocking, but not
This is a straight-forward translation of using callbacks to cope with blocking operations: We can conditionally fork if we are about to block the current thread. For example, a new version of readMVar
:
readMVarMoving :: MVar a -> ContT () IO a
= liftIO (tryReadMVar mvar) >>= \case
readMVarMoving mvar Just a -> pure a -- phew, avoided blocking, and forking
Nothing -> moveToNewThread >> liftIO (readMVar mvar)
So while we still block, we don’t block the “initial” thread (the one calling evalContT
or similar). In an event processing loop, we might write something like
`forM_` \case
events ImportantEvent x -> evalContT $ do
<- readMVarMoving relevantResource
y <- lightweightProcess x y
z reply z
where the MVar
will never block this whole loop, and we only fork when it is necessary. However there is a downside: If we use readMVarMoving
multiple times, we create a new thread for each time we block. We could just fork once and then block without worrying about blocking the main loop. Which of these two approaches ultimately results in less forks globally depends on the rate at which the tryReadMVar
succeeds (i.e. on contention of our resources in general). Plus, threads are cheap in haskell, so the gains might be irrelevant either way.
I am not aware of any library that provides such versions of common blocking functions (yet).
Second application: Moving between Threads
We can create worker threads that evaluate continuations passed to them, e.g. using
contProcessor :: Chan (IO ()) -> IO ()
= forever . join . readChan
contProcessor
createContWorker :: IO (Chan (IO ()))
= do
createContWorker <- newChan
chan <- forkIO $ contProcessor chan
_ pure chan
moveToProcessor :: Chan (IO ()) -> ContT () IO ()
= ContT $ \c -> writeChan chan (c ()) moveToProcessor chan
So moveToProcessor
behaves like moveToNewThread
but instead of a fresh thread, in moves to a specific worker thread. This might come in handy if we have thread-specific resources (FFI stuff). We might also use this construct as a synchronization/critical section/resource ownership mechanism, although I have a hard time coming up with examples where this would have advantages over simpler approaches to locking resources. Maybe something with exception-handling around the resources that “belong” to this worker thread? But exception-handling deserves its own, large chapter (read: its own article).
Third Application: Moving with Transformer-Stacks
(some liftIO
s omitted)
$ flip evalStateT (0 :: Int) $ do
evalContT +1)
modify (>>= \x -> putStrLn ("from main thread: our current state is " ++ show x)
get +1)
modify ($ moveToNewThread
lift +1)
modify (>>= \x -> putStrLn ("from new thread: our current state is " ++ show x) get
will output
from main thread: our current state is 1
from new thread: our current state is 3
Fourth Application: Forking with Transformer-Stacks
We can also truly fork (can you guess how this behaves?) (liftIO
s omitted)
main :: IO ()
= evalContT $ flip evalStateT (0 :: Int) $ do
main >>= \case
lift forkCont2 False -> do
+ 1)
modify (1000000
threadDelay True -> do
+ 2)
modify (2000000
threadDelay >>= print get
yeah?
Solution: It prints 1 after 1 second and 2 after 2 seconds. I.e. the state indeed splits, somewhat in the fashion of non-determinism monads such as LogicT
. This may be undesired and become confusing quickly, so it might make sense to restrict the usage around this and either:
- Only use this around “harmless” stacks; e.g.
ReaderT
is fine; - Don’t use the “true forking” functions, but permit those that call the continuation exactly once (
moveToNewThread
,moveToProcessor
), which are still completely fine.
Fifth Application: Stateful Computations in Worker-Threads
This is essentially a combination of applications two and three. (liftIO
s omitted)
contProcessor :: Chan (IO ()) -> IO ()
createContWorker :: IO (Chan (IO ()))
moveToProcessor :: Chan (IO ()) -> ContT () IO ()
-- implemented as above
main :: IO ()
= do
main <- createContWorker
chan $ flip evalStateT (0 :: Int) $ do
evalContT +1)
modify (>>= \x -> putStrLn ("from main thread: our current state is " ++ show x)
get +1)
modify ($ moveToProcessor chan
lift +1)
modify (>>= \x -> putStrLn ("from worker thread: our current state is " ++ show x) get
from main thread: our current state is 1
from worker thread: our current state is 3
The interesting bit about this is that: The worker thread exposes and runs a plain ContT () IO ()
interface, but we still are able to pass it a stateful computation via lifting. And there is nothing stopping us from expanding on this some more:
- Can add multiple workers without problem
- Can return to some other thread (even the main thread, although that requires a new primitive)
- This does not only work for singly-transformed monads: Any transformers stack with the
ContT () IO
base qualifies (we might need a corresponding typeclass to allow effortless lifting, but that is trivial).
Generalizations and Conclusion
We can apply at least two generalizations. Firstly the typical “mtl” approach, using this class:
-- capture any monad stacks with a base of `ContT () IO`.
class MonadIO m => MonadContIO m where
liftContIO :: ContT () IO a -> m a
Secondly we can generalize over forkIO
. Together, we get:
forkCont2With :: MonadContIO m => (IO () -> IO ()) -> m Bool
= liftContIO $ ContT $ \c -> forker (c False) >> c True
forkCont2With forker moveContWith :: MonadContIO m => (IO () -> IO ()) -> m ()
= liftContIO $ ContT $ \c -> forker (c ()) moveContWith forker
Now moveToNewThread
can be implemented as moveContWith (void . forkIO)
.
To answer the motivation:
Summary
= flip evalStateT (0 :: Int) $ do main +1) modify ($ forkIO $ do liftIO <- get s -- ^ type error: we are in IO, -- no state to `get`. d'oh! print s ..
is fixed using
= do main $ flip (evalStateT (0 :: Int)) $ do evalContT +1) modify ( moveToNewThread<- get -- it compiles, so it must work! (TM of haskell hype industries) s $ print s liftIO ..
And:
forkCont2With
andmoveContWith
fork/move arbitrary monad stacks with theContT () IO
base.- Can fork state, for good or worse. That is, we accidentally got an answer to the “what does forking mean for state” question.
- We somewhat have to assume that we are working with undelimited continuations, i.e. mixing of fork/move and
callCC
/resetT
probably can become rather confusing (to be discussed).- Exceptions will blow up the current thread only. An
evalContT
wrapped in somecatch
will actually not catch an exception thrown after amoveToNewThread
(to be discussed).- The “host” of continuations (in the simplest case
forkIO
) requires only the power of running plainIO ()
, even when our “client” monad stack contains arbitrary transformers. The host is independent of those transformers (and is blissfully unaware of their internal state).- As a trivial consequence, a host can run a series of continuations that have different monads (stacks).
Outlook
(or should I say: To be Continued With:)
Arbitrary
ContT
values can do rather wonky stuff, like calling the continuation zero or more than one time. We discussed in the fourth application above that we might want to avoid those, but this would currently depend on “programmer discipline”, and generally in haskell we want our abstractions to do better than that.Even if we somehow hide/ban the
ContT
constructor, there are combinators likeresetT
andcallCC
that may be useful, but that also might not work once we combine it with any forking stuff. Using the “undelimited” CPS3 definition from [6] might give better results. We can also have a look atCodensity
, although this will become a short excursion.Exceptions in the
IO
part complicate matters further. Or: if we want try-catch/bracket/finally functionality, the ability to move to a new thread does not make things any easier. Neil Mitchel has one full blog post “Continuations and Exceptions” [4] already, and afaict this does not even involve any forking.How does this compare to other approaches to the “move transformer stacks” problem, like
monad-control
orunliftio
? This intersects a bit with the previous “exceptions” topic, but with the right base monad (something continuation-based but a bit more complex) you can get very close to the expressiveness of the coreunliftio
class. That, too, will require a full article.with
-functions pose an interesting application ofmonad-control
orunliftio
, i.e. the ability to pass effects through a IO-focused continuation gateway. This boils down to the following question: What constraint is sufficient to implement the following function:withLifted :: _ m => (forall r . (a -> IO r) -> IO r) -> (a -> m b) -> m b
with suitable semantics. See the “withLifted” addendum for details.
The next article in this series will introduce an implementation for withLifted
.
Addenda
forkSequential
moveToNewThread
and forkCont2
share certain functionality, so a natural question is if we can express one in terms of the other. In that direction, we define:
forkSequential :: ContT r IO Bool
= ContT $ \c -> c True >> c False forkSequential
and with that
forkCont2 :: ContT () IO Bool
= do
forkCont2 <- forkSequential
isChild
when isChild moveToNewThreadpure isChild
And we can also go from 2 to n:
forkSequentialN :: Int -> ContT () IO Int
= ContT $ forM_ [1 .. n] forkSequentialN n
What about the ContT transformer?
How does t (ContT () IO)
fare versus ContT () (t IO)
? The latter seems nicer in that it does not force us to switch the base of our transformer stack. Unfortunately, this does not work. Just consider how we would have to define our simplest forking function:
moveToNewThreadMIO :: MonadIO m => ContT () m ()
= ContT $ \c -> liftIO $ void $ forkIO $ _ $ c ()
moveToNewThreadMIO -- problem: ^ :: m () -> IO ()
Replacing m
with t IO
does not help:
moveToNewThreadMIO :: ? => ContT () (t IO) ()
= ContT $ \c -> liftIO $ void $ forkIO $ _ $ c ()
moveToNewThreadMIO -- i can't think of any constraints that would enable ^:: t IO () -> IO ()
withLifted
The riddle consists of the following signature:
withLifted :: MonadContIO m => (forall r . (a -> IO r) -> IO r) -> (a -> m b) -> m b
We are looking for an implementation so that
mockWith :: String -> (() -> IO a) -> IO a
= do
mockWith s c putStrLn $ "acquire " ++ s
<- c ()
x putStrLn $ "release " ++ s
pure x
main :: IO ()
= evalContT $ flip evalStateT (0 :: Int) $ do
main "a") $ \() -> do
withLifted (mockWith "b") $ \() -> do
withLifted (mockWith + 1)
modify (>>= liftIO . print get
prints
acquire a
acquire b
release b
release a
1
That is: We want to lift a “with-function” to an arbitrary transformer stack if the base monad is ContT () IO
. If you take into account that the “host” only needs to “speak IO”, and the challenge here is to pass a monad stack through an “IO gate”, this is an interesting but solvable riddle.
Hint: You don’t even need forkIO
, but you need an MVar
.
References
[1] https://en.wikibooks.org/wiki/Haskell/Continuation_passing_style
[2] Oleg Kiselyov, Chung-chieh Shan, Daniel P. Friedman, Amr Sabry, 2005. Backtracking, Interleaving, and Terminating Monad Transformers
[3] reddit thread “C-style fork with ContT”
https://old.reddit.com/r/haskell/comments/3h34ev/cstyle_fork_with_contt/
[4] Neil Mitchel, 2014, “Continuations and Exceptions”
https://neilmitchell.blogspot.co.uk/2014/08/continuations-and-exceptions.html
[5] http://okmij.org/ftp/continuations/index.html
[6] http://okmij.org/ftp/continuations/undelimited.html#proper-contM
[7] https://wiki.haskell.org/Library/CC-delcont
[8] Oleg Kiselyov, Hiromi Ishii, 2015, Freer Monads, More Extensible Effects