Continuations and Effects, part 1 ROUGH DRAFT
Or, to be continued…
1 Intro
This article serves as the background for a future article about effects and effect systems.
I can’t promise that I didn’t let some of this article influence me and anyway it’s a fun read.
1.1 This is an executable essay
This post is written in literate Haskell, which means that (the source for) this essay is a valid Haskell program you can run yourself:
- If you don’t have Haskell installed, easily do so with ghcup
- Download the source for this essay as
effects.lhs
- Compile the program with
ghc -o effects effects.lhs
!- Or open an interactive session with
ghci
and loadeffects.lhs
into it.
- Or open an interactive session with
It also means enduring this annoying boilerplate. We enable a few GHC-specific language extensions and import a few packages from the standard base
library.
{-# LANGUAGE PolyKinds, RankNTypes #-}
module Main where
import Data.Kind (Type)
import Control.Monad (forM)
Okay now for the good stuff.
2 Effects, effectively
I’ll start by posing a question.
The following function loads a state variable of type Int
into a variable n
, saves a new value (n + 1)
, and then finally halts and returns with no value (the ()
type):
state_example_intro :: CPSState Int ()
= do
state_example_intro <- cps_load
n + 1) cps_save (n
If I run this function 100 times, I will get back the value ()
every one of those 100 times. The question is: what will the state value be?
Take this second program:
try_example :: Int -> CPSExcept String Double
=
try_example n if 0 == n
then cps_throw "cannot divide by 0"
else return ( 1.0 / (fromIntegral n) )
absurd_exception_demo :: IO Double
= do
absurd_exception_demo <- forM [0, 1, 2] $ \n -> (try_example n) `catch` (\msg -> do
ns putStrLn $ "error: " ++ msg
return 0)
return (sum ns)
The function try_example
returns a Double
-precision floating point number unless you give it an argument of 0
. In that case it produces an error String
which is printed to the console by catch
. The computation recovers (in this case with an arbitrary result value) and continues.
How is this computation able to return a different type entirely in the event of an error, and how is the error routed to catch
?
2.1 The cause: Effects
- Effect
- An observable behavior or outcome of a program execution besides returning a result value.
If that sounds extremely broad that’s because it is. The most obvious effect for Haskell programmers is IO
(“input/output”), the ability to send and receive data to and from “the outside world” - every single Haskell program begins with a function main :: IO ()
, because without effects you cannot even interact with the program.
Both the CPSState
and CPSExcept
types represent computations with side effects (or just effects), and not too far below the surface you’ll find that they have quite a lot in common.
2.2 Don’t “monads” have something to do with this?
Yes, and I encourage programmers to read Moggi’s work on representing side effects as monads, but we actually won’t be doing another monad tutorial today. Effect systems basically have one monad whose internal workings you can ignore if you are simply designing effect-laden software.
And now we will visit that particular monad type, CPS
.
3 CPS
The concept of continuations is used extensively in programming language theory and semantics; they are abstract representations of the program’s current execution state as well as the future of the work to be done.
Most programming languages don’t expose continuations directly to the programmer (after all, does what I just describe sound like it would be terribly straightforward to even use?); rather, other control flow operators are defined in terms of continuations.
Haskell is “most” languages in this regard, but never fear, because we can use continuation passing style (CPS). In CPS, every function explicitly requires one final argument (its continuation) which it will use as its return
keyword by passing to it the value being returned. Eg,
my_func arg1 arg2 = do
x <- foo arg1
y <- bar x arg2
return y
is rewritten as
my_func arg1 arg2 ret = do
x <- foo arg1
y <- bar x arg2
ret y
Now, programming like this explicitly would be annoying …
3.1 The CPS
monad
… but this is Haskell!
newtype CPS (result :: k) (m :: k -> Type) (answer :: Type) = CPS
(#) :: (answer -> m result) -> m result } {
This reads as: a term of type CPS result m answer
is
- a function in possession of some
answer
value expecting a - continuation which takes
answer
values tom result
values, which then - returns that very same
m result
by applying the continuation to theanswer
.
3.2 Why do we care about CPS?
It so-happens that CPS
is a Monad
(and hence an Applicative
and a Functor
) And as we all know, Haskell rewards monads with readable syntax, so these typeclass instances do serve a purpose.
:
instance Functor (CPS r m) where
fmap f (CPS c) = CPS (\k -> c (k . f))
instance Applicative (CPS r m) where
pure v = CPS (\k -> k v)
<*> v = CPS (\k -> f # \g -> v # (k . g))
f *> k = m >>= \_ -> k
m
instance Monad (CPS r m) where
return = pure
>>= k = _join (fmap k m) where
m _join :: CPS r m (CPS r m a) -> CPS r m a
CPS cc) = CPS (\k -> cc (\ (CPS c) -> c k)) _join (
Note that the continuation evaluates to the type m result
- it must be some kind of type constructor wrapped around the actual result value. Part of the reason for this is that the mediating type m
affects properties and capabilities of CPS
.
For example, when m ~ IO
,
sixteen :: CPS Int IO Int
= do
sixteen <- shift $ \k -> lift $ do
s putStrLn ("Calling (k 4) ...")
<- k 4
eight putStrLn ("Calling (k eight) ...")
-- *this* is the return value
k eight $ putStrLn ("k called with " ++ show s)
lift return (s * 2) -- this is *not* the return value
seventeen :: IO ()
= do
seventeen <- reset sixteen
_16 putStrLn . show $ _16 + 1
-- some helpers which we will talk more about next article :)
lift :: Monad m => m a -> CPS r m a
= CPS (v >>=)
lift v
reset :: Monad m => CPS r m r -> m r
CPS cc) = cc return
reset (
shift :: Monad m => ((a -> m r) -> CPS r m r) -> CPS r m a
= CPS (\k -> reset (e k)) shift e
The function sixteen
uses the delimited continuation operators shift
and reset
in order to manipulate the flow of control; they will play an important role in the next article so I snuck them in here.
lift
takes advantage of the way we split the CPS
result type into m
and result
in order to augment the type m
(which or may not be a Monad
) with the ability to manipulate control flow. Here, I chose IO
so that the example would be compelling.
4 Defining effects with CPS
FINALLY I can arrive at the point of all this. At the beginning of the article we showcased two effects: mutable local state and exception handling.
The examples are worth experimenting with as we will be examining them further in the next article. Nevertheless, we have everything we need right here to model effects with continuations.
4.1 State
4.1.1 Type definition
type CPSState s a = forall r. CPS r ((->) s) a
The type ((->) s)
is the type of “functions with an argument s
.” In the Haskell community this type is often referred to as Reader s
or Env s
(for all types s
, of course). Reader
is a monad providing read-access to a dynamic value, so CPS r ((->) s)
is CPS
but with the “extra effect” of being able to access a hidden s
.
The consequence of this choice, ultimately, is that continuations now have a second argument, the state value in question.
4.1.2 Operators
cps_load :: CPSState s s
= CPS (\k s -> k s s) cps_load
The first operation we define is loading a local state value. Note that our CPS
continuation has a second parameter now. We fulfill this loading operation by passing the state value to the continuation itself as its first argument.
cps_save :: s -> CPSState s ()
= CPS (\k _ -> k () s) cps_save s
To save is the reverse of loading a value. The operation does not return any meaningful value; internally, it ignores the state value it will be overwriting, and will instead pass along a new value of its own.
4.1.3 Running stateful functions
The final ingredient is the function to kick-start effect handling and also define what happens when you “return” in a stateful function.
run_cps_state :: CPSState s a -> s -> (s, a)
CPS m) = m (flip (,)) run_cps_state (
This pairs the state with the final answer
. When we run this (excerpt from GHCI):
*Main> run_cps_state state_example_intro 0
(1,())
4.2 Exceptions
Fundamentally the idea behind exceptions is that we can return Either
an answer
or some err
or value, to be handled by a different code path.
4.2.1 Type definition
type CPSExcept err a = forall r. CPS r (Either err) a
4.2.2 Operations
cps_throw :: err -> CPSExcept err a
= CPS (\ _ -> Left m) cps_throw m
4.2.3 Running exceptions
run_cps_except :: CPSExcept err a -> Either err a
CPS m) = m Right
run_cps_except (
-- this is a little friendlier and idiomatic.
catch :: Monad m => CPSExcept err a -> (err -> m a) -> m a
catch fn hndl = case run_cps_except fn of
Left err -> hndl err
Right val -> return val
And now, in GHCI, we can begin using our DIY exception system:
*Main> absurd_exception_demo
error: cannot divide by 0
1.5
5 Recap; I already used the “to be continued” joke
The purpose of this post is not to be a comprehensive treatment of continuations or effects, as that would be impossible, but rather to get the gist of some powerful ideas across succinctly to inspire you, dear reader.
We covered what effects are, why we might want to account for them, and then constructed them in terms of continuations. In the next article we will build on these ideas to build an effect system.
By writing this article in literate Haskell I can ensure that the examples compile and behave appropriately and that nothing crucial is missing, so I hope you have fun experimenting with it.
= do
main
seventeen>>= putStrLn . show
absurd_exception_demo putStrLn . show $ run_cps_state state_example_intro 0