Extensible Effects: an alternative to Monad Transformers

 
We describe Cartwright and Felleisen's modular and compositional approach to effects, discuss extensions and present its implementations in Haskell. The principal ideas, in the words of Cartwright and Felleisen, are: We extend the approach with effect encapsulation and types. The result is a flexible effect handling framework, which subsumes monad transformers and overcomes their limitations. Thanks to the Freer monad construction and the representation of the continuation as an efficient sequence structure, extensible effects have good performance even for relatively short monad stacks, and algorithmically better performance than monad transformers for longer stacks.

When designing a program we should start thinking what effect we want to achieve rather than which monad transformer to use. Instead of jumping straight to StateT and so on, we ought to identify what transformation on the world and its resources we wish to effect. Written formally, this transformation often takes the form of an effect handler. Our framework is designed around such handlers, encouraging custom effects for program fragments and their composition.


 

Introduction

We design and implement a library that solves the long-standing problem of combining effects without imposing restrictions on their interactions (such as static ordering). Effects arise from interactions between a client and an effect handler (interpreter); interactions may vary throughout the program and dynamically adapt to execution conditions. Existing code that relies on monad transformers may be used with our library with minor changes, gaining efficiency over long monad stacks. In addition, our library has greater expressiveness, allowing for practical idioms that are inefficient, or greatly cumbersome with monad transformers.

Our alternative to a monad transformer stack is the single monad, for the coroutine-like communication of a client with its handler. Its type reflects possible requests, i.e., possible effects of a computation. To support arbitrary effects and their combinations, requests are values of an extensible union type, which allows adding and, notably, subtracting summands. Extending and, upon handling, shrinking of the union of possible requests is reflected in its type, yielding a type-and-effect system for Haskell. The library is lightweight, generalizing the extensible exception handling to other effects and accurately tracking them in types.

In the follow-up paper, we present a rational reconstruction of the above extensible effects, as the confluence of efforts to make effectful computations compose. Free monads and then extensible effects emerge from the straightforward term representation of an effectful computation, as more and more boilerplate is abstracted away. The generalization process further leads to freer monads, constructed without the Functor constraint. The continuation exposed in freer monads can then be represented as an efficient type-aligned data structure. The end result is the algorithmically efficient extensible effects library, which is not only more comprehensible but also faster than earlier implementations.

As an illustration of the new library, we show three surprisingly simple applications: non-determinism with committed choice (LogicT), catching IO exceptions in the presence of other effects, and the semi-automatic management of file handles and other resources through monadic regions.

We extensively use and promote the new sort of `laziness', which underlies the left Kan extension: instead of performing an operation, keep its operands and pretend it is done.

The ambition is for Eff to be the only monad in Haskell. Rather than defining new monads programmers will be defining new effects, that is, effect interpreters.

Joint work with Amr Sabry, Cameron Swords, and Hiromi Ishii.

Version
The current version is December 2015
References
more.pdf [291K]
Freer Monads, More Extensible Effects
The paper published in the Proceedings of the 2015 ACM SIGPLAN symposium on Haskell, pp. 94-105. Vancouver, BC, Canada. September 3-4, 2015 doi:10.1145/2804302.2804319
The talk at the Haskell Symposium 2015 on September 4, 2015 concentrated on the first, pedagogical part of the paper: deriving and understanding the monad for extensible effects. The presentation was recorded and should be available from YouTube.

exteff.pdf [286K]
Extensible Effects: An Alternative to Monad Transformers
The paper published in the Proceedings of the 2013 ACM SIGPLAN symposium on Haskell, pp. 59-70. Boston, MA, USA. September 23-24, 2013 doi:10.1145/2503778.2503791

talk.pdf [231K]
The annotated slides of the talk presented at the Haskell Symposium 2013 on September 23, 2013 in Boston

Eff1.hs [39K]
OpenUnion51.hs [5K]
FTCQueue1.hs [2K]
The complete, self-contained implementation of extensible effects
The file Eff1.hs (importing an implementation of open unions) defines and implements the API for extensible effects: an EFF monad as an extensible effect. It also implements the standard monadic effects such as exception, state, and non-determinism. The file contains many examples and test code. The December 2015 version introduces several specialization RULEs and inlining directives, which notably improve the performance.

Defining a new class for each effect, such as MonadState, is possible but not needed at all. With monad transformers, a class per effect is meant to hide the ordering of transformer layers in a monad transformer stack. Effect libraries abstract over the implementation details out of the box. Crutches -- extra classes -- become unnecessary.

We also illustrate, for pedagogical purposes, an implementation of the State effect as a combination of the existing but differently interpreted Reader and Writer effects. Truly the meaning of an effect is its interpretation.

EffDynCatch.hs [5K]
Catching of dynamic and asynchronous exceptions in the presence of other effects -- the solution of the MonadCatchIO problem. This code accompanies Section 6 of the paper.

EffRegion.hs [11K]
EffRegionTest.hs [10K]
Monadic regions through extensible effects: the code accompanying Section 7 of the paper. The test code is essentially the same as that of the original Monad Regions implementation.

Benchmarks.hs [21K]
Bench_nondet.hs [13K]
A few micro-benchmarks

Eff.hs [30K]
The now obsolete code for the original (2013) implementation

Reader00.hs [3K]
Reader0.hs [4K]
The warm-up example: the single Reader effect as an interaction with an authority. This is the code for Sec 3.1 of the 2013 paper. Reader00.hs describes the single Reader Int effect; the other file generalizes to arbitrarily typed environment monad.

ExtMTL.hs [9K]
A variation of Eff.hs emulating monad transformer classes of MTL. The framework of extensible effects indeed can define the instances for MonadError, MonadReader, MonadState, etc. These instances require fewer annotations in the user code; on the other hand, they are less general, enforcing a single effect layer of a particular kind.

 

Limitations of Monad Transformers

Monad transformers are strictly less expressive than extensible effects.

Monad transformers have become an integral part of Haskell, with many tutorials. Rarely do the drawbacks of transformers get a mention. As a rare exception, Chapter 18 of `Real World Haskell' points out the overhead added by each monad transformer layer, an occasional need for the ungainly explicit lifting, and the difficulty of building monad transformer libraries: when adding a new transformer, one has to explicitly specify `lifting', its interaction with all other transformers. Alas, the biggest drawback of monad transformers is hardly mentioned at all.

Monad transformers have an inherent limitation: they enforce the static ordering of effect layers and hence statically fixed effect interactions. There are practically significant computations that require interleaving of effects. `Delimited Dynamic Binding' (ICFP 2006) was first to bring up this point. The `Extensible Effects' paper expanded that discussion on new examples. Section 5 describes simple and common programming patterns that are particularly problematic with monad transformers because the static ordering of effect layers is not flexible.

References
transf.hs [10K]
Two examples of limited expressivity of monad transformers: the complete code for Sec 5 of the paper

Bryan O'Sullivan, Don Stewart, and John Goerzen: Real World Haskell
Chapter 18. Monad transformers
<http://book.realworldhaskell.org/read/monad-transformers.html#id6594>

 

Open Unions

Extensible effects, as well as extensible interpreters (Liang et al. `Monad Transformers and Modular Interpreters' and later Swierstra's `Data types à la carte') all rely on typed open unions, or open type-indexed coproducts. Open unions, by the name of polymorphic variants, are part of OCaml and proved to be a popular feature. One of their uses is again extensible interpreters. It may be high time Haskell supported typed open unions on par with OCaml. We describe the desired interface, its actual and possible implementations, and the overall design space. We use extensible effects as a running example, in part to justify a rarely considered but often crucial function of orthogonal decomposition.

An early compelling case for open unions are extensible exceptions, which have been part of Haskell for many years (Simon Marlow, Haskell Workshop 2006). To permit throwing exceptions of arbitrarily many types, the thrown exception value is an open union (see SomeException in Control.Exception). Raising an exception puts -- injects -- a particular exception value into the open union. When we handle an exception, we project: check if the thrown exception is of a particular desired type. (Extensible effects operate in the same manner; supporting, in addition, the resumption of an `exception'.) Thus, at its core, an open union should let us inject a value of any type into the union and to project a type from the union, that is, to find find out if the union value was previously injected with a particular specific type. These operations are familiar from OOP as downcast and upcast.

The open-union type of exceptions, SomeException (or the similar exn in ML), gives no indication of possible summands -- that is, which particular exception types may be in the union. Therefore, neither Haskell nor ML can ensure that a program handles all exceptions that could be raised during its execution.

To do better, the type of an open union should be annotated with the set of possible summands. The injection function will add the type of the injected value to the union type, unless it was there already. As always with types, the type of the open union is an approximation for the type of the value therein. Consider the simplest union Either Int Bool: at run time, the union value is either a single Int or a single Bool. The union type is an approximation: we cannot generally determine at compile-time the specific type of the value stored in the union. We are sure however that this type is not a String and hence attempting to project a String value from an Either Int Bool union is a compile-time error. Such type-annotated union is called a type-indexed co-product.

The familiar data type (Either a b) is the simplest example of typed unions, but it is not extensible. The constructors Left and Right are injections, and the projections are realized via pattern-matching:

    prj1:: Either a b -> Maybe a
    prj1 (Left x) = Just x
    prj1 _        = Nothing
The type checker does not let us inject a value of a type other than a and b into Either a b, hence restricting injection to values that participate in the union. We can only project at types a and b -- Either a b is a union of exactly two types, and thus not extensible. Furthermore, it is not abstract: we must know the exact structure of the union in order to choose the proper injection, Left or Right. The type Either Int Bool is different from Either Bool Int, although they are morally the same union.

Heeding the drawbacks of Either, we arrive at the following interface for open unions:

    data Union (r :: [*]) -- abstract
   
    type family Member (t :: *) (r :: [*]) :: Constraint
   
    inj :: Member t r => t -> Union r
    prj :: Member t r => Union r -> Maybe t
    decomp :: Union (t ': r) -> Either (Union r) t

The union type Union r is tagged with r, which is meant to be a set of summands. For the lack of type-level sets, it is realized as a type-level list, of the kind [*]. The injection inj and the projection prj ensure that the type t to inject or project must be a member of the set r, as determined by the type-level function Member t r. The function decomp performs the orthogonal decomposition. It checks to see if the union value given as the argument is a value of type t. If so, the value is returned as Right t. Otherwise, we learn that the received union value does not in fact contain the value of type t. We return the union, adjusting its type so that it no longer has t. The function decomp thus decomposes the open union into two orthogonal ``spaces:'' one with the type t and the other without. The decomposition operation, which shrinks the type of open unions, is the crucial distinction of our interface from the previous designs (Liang et al. 1995, Swierstra 2008, polymorphic variants of OCaml). It is this decomposition operation, used to `subtract' handled exceptions/effects, that insures that all effects are handled. The constraint Member t r may be seen as the interface between inj and prj on one hand and decomp on the other hand: for each injection or projection at type t there shall be a decomp operation for the type t.

This basic interface of open unions has several variations and implementations. One is OpenUnion1, presented in the Haskell 2013 extensible-effects paper. It is essentially the one described in Appendix C of the full HList paper, published in 2004. In the version for extensible-effects, the summands of the open union have the kind * -> * rather than *. This implementation uses Dynamic as the open union. Therefore, all operations take constant time -- like polymorphic variants of OCaml and unlike open unions used by Liang et al. 1995 and Swierstra 2008.

One may notice a bit of asymmetry in the above interface. The functions inj and prj treat the open union index r truly as a set of types. The operations assert that the type t to inject or project is a member of the set, without prescribing where exactly t is to occur in the concrete representation of r. On the other hand, decomp specifies that the type t must be at the head of the list that represents the set of summand types. It is unsatisfactory, although has not presented a problem so far for extensible effects. If the problem does arise, it may be cured with an easily-defined conversion function of the type conv :: SameSet r r' => Union r -> Union r', akin to an annotation. The other solutions to the problem (based on constraint kinds, for example) are much more heavier-weight, requiring many more annotations. Perhaps implicit parameters may help:

    e1 = if ?x then ?y else (0::Int)
    -- inferred:  e1 :: (?x::Bool, ?y::Int) => Int
   
    f :: ((?x::Bool) => r) -> r             -- explicit signature required
    f x = let ?x = True in x
   
    t1 = f e1
    -- inferred:  t1 :: (?y::Int) => Int
The inferred type of t1 no longer contains the ?x::Bool constraint, which thus has been subtracted. The type of the `subtraction function' f, the handler, only mentions the removed constraint, saying nothing of other constraints or if there are other constraints. Binding an implicit parameter builds the dictionary and makes the constraint go away. One could wish the same for proper constraints.

One may notice that the open union interface, specifically, the function decomp, does not check for duplicates in the set of summands r. This check is trivially to add -- in fact, the HList implementation of type-indexed co-products did have such a check and so implemented true rather than disjoint unions. In case of extensible effects, the duplicates are harmless, letting us nest effect handlers of the same type. The dynamically closest handler wins -- which seems appropriate: think of reset in delimited control. There is even a test case for nested handlers in Eff.hs.

The implementation OpenUnion1 was received with significant controversy, often derailing discussions of extensible effects, which work with any open union implementation. Although OpenUnion1 provides constant-time operations, it relies on Dynamic, which requires the Typeable constraint all throughout extensible-effects. Although, with few exceptions, it is a minor annoyance, it is the annoyance still. The OverlappingInstances extension used by OpenUnion1 was also objected to, although without much reason since the extension does not leak from the open union implementation to the rest of the code. To address the concerns, OpenUnion41 was developed. It has the same interface as OpenUnion1 but uses neither Typeable nor OverlappingInstances. It relies on GADTs and closed type families. Alas, its operations in the worst case take time proportional to the number of summands in the union. The recent OpenUnion5 implementation brought back the constant-time union operations. It realizes ``strong sums'': existentials over a finite type universe that do not hide the type of the containing value.

We have thus seen the design space for typed open unions and a few sample implementations. Hopefully more experience will help choose an optimal implementation and introduce it into Haskell.

References
OpenUnion5.hs [4K]
OpenUnion51.hs [5K]
The latest implementation of open unions, with constant-time operations but without Typeable. It relies on the fact that the type parameter r, the list of possible summand types, is actually a type universe. An integer index in that list serves well as a value-level representation for the indexed type. Whereas OpenUnion5 relies on closed type families, OpenUnion51 uses overlapping instances. The latter can resolve even for unground types, but closed type families are subject to a strict apartness condition.

OpenUnion41.hs [4K]
Another implementation of open unions, with neither Typeable nor overlapping instances. We pay for the lack of Typeable with non-constant--time injections and projections. However, the more frequent decomposition takes short constant time. This implementation has exactly the same interface as the others, and can be used in any extensible-effects code as the drop-in replacement for more controversial implementations like OpenUnion1.

OpenUnion1.hs [3K]
The code for open unions used in the paper. It is close to the implementation in the HList paper. It relies on Typeable, and emulates closed type families using the overlapping instances extension that is limited to that module.

OpenUnion2.hs [3K]
The version of open union without any overlapping instances, directly using closed type families.

OpenUnion3.hs [3K]
Another, somewhat dual implementation, relying on universals rather than existentials

TList.hs [2K]
The old implementation of open unions, without overlapping instances or Typeable

 

Parameterized extensible effects and session types

Parameterized monad goes beyond monads in letting us represent type-state. An effect executed by a computation may change the set of effects it may be allowed to do afterwards. We describe how to `add' and `subtract' such type-state effects -- which first appeared straightforward, then impossible and finally doable. Parameterized monad is often used to implement session types. We point out that extensible type-state effects are themselves a form of session types -- in particular, session types for internal choice.

The type of a value determines the set of operations on it. The set may be further restricted by the computation state: e.g., although an open file handle and a closed file handle have the same type, the sets of meaningful operations on them greatly differ. Type-state is the refinement of the notion of type to characterize such restriction. Session types, in the news lately, are one manifestation of the type-state. Whereas monads represent stateful computations, type-state calls for a parameterized monad, as a poor programmer's substructural type system. Tracking type-state seems to require quite advanced type (and effect) systems, in particular, modal or substructural type systems. None of these advanced type systems are available in mainstream Haskell.

Monad transformers -- and recently, algebraic, extensible and other `effects' -- let us combine in the same program independently developed monadic computations, each with their own side-effects. The effects may need to interact in a controlled fashion. The similar combining of parameterized monads has not been addressed so far. The problem is not straightforward, as we shall see from several failed attempts. We eventually present the solution, along the lines of extensible effects. The inferred types curiously look like session types.

For clarity, this abstract uses a rather specific example: two mutable cells. The generalizations, to other effects and to truly open unions, and optimizations are all doable and have been already described. We elide them to demonstrate the problem and the solution in the purest, barest form.

It may seem that the approaches to combine monadic computations should straightforwardly extend to type-state (parameterized monads). That turns out not to be the case. In the hindsight, the stumbling block is easy to see. Consider two differently effectful expressions m1 and m2, which we wish to combine in the same program. It is most revealing to look at the following combination:

    m12 = if test then m1 else m2
where test :: Bool is some decision procedure. Clearly m12 performs what is called in process calculi an internal choice. An effect may be regarded as an interaction (communication) with the context. The expression m12 may hence interact as m1 or as m2, based on an internal decision.

The type of an expression should describe what interactions it may (potentially) make. The type of m12 should therefore represent the union of effects of m1 and m2. In the framework of extensible effects, m1 has the type Eff r1 a and m2 has the type Eff r2 a; then m12 has essentially the type Eff (union r1 r2) a. No wonder the implementation of open unions is the crucial part of any extensible-effect library.

Eff r a is an ordinary monad and r may be considered a degenerate session type: A computation m :: Eff [Read Int, Write String] Bool, for example, tells that m, if terminates, produces a boolean and can make Read Int or Write String requests -- an indeterminate number of times and in any order. Type-state reins in: a type-state computation may require that, e.g., any Write String request be preceded by a Read Int request. Ordinary monads cannot express such computations, but parameterized monads can: m1 :: EffP [Read Int] [Write String] Bool says that computation m1 may make a Read Int request. If it really does that, it may then, afterwards, make a Write String request (or yield a value). Suppose m2 has the type EffP [Writer String] [Read Int] Bool -- it may make a Write String request and after that, Read Int.

If we then combine m1 and m2 into m12 as in our running example, what is the type of m12? It should be something like EffP [Read Int, Write String] ?? Bool -- telling that the computation may do either Read Int or Write String. But what is the type state afterwards? It should be Write String if m12 actually made the first choice, or Read Int otherwise. It seems we need dependent sums! This is the unexpected predicament in what at first seemed to be a straightforward generalization of extensible effect to parameterized monads.

Version
The current version is September 2016
References
param-eff.pdf [158K]
The extended abstract published in the Proceedings of the 1st International Workshop on Type-Driven Development (TyDe 2016), pp. 41-42. Nara, Japan. September 18, 2016 doi:10.1145/2976022.2976034

ParamEff1.hs [12K]
The accompanying complete source code

 

Generic crossover, with extensible effects

We present generic crossover -- the interchange of segments between two algebraic data structures. Our surgery library, of cutting a structure at an arbitrary place and grafting new branches, supports many kinds of crossover, e.g., from three parents. The library shows off extensible effects: of defining a new effect (SYB-aware coroutines) and combining it with two standard effects, state and non-determinism.

In genetics, crossover is the interchange of segments between two chromosomes of the same `type' (or, homologous). Genetic algorithms borrow this term to mean the interchange of segments between two structures representing sets of optimization parameters. These data structures are called chromosomes as well, and the parameters, or features, are also called genes. Here is an example with two chromosomes that are lists of integers (which we write in the explicit (::) and [] notation).

    1  ::  2 ::  3  :: []
    10 :: 20 :: []
First we cut each list in two pieces
    1  ::  2 ::  _      and    3 :: []
    10 ::  _            and   20 :: []
where _ represents the hole, which is left at the place of a cut-off branch. Then we swap the branches, grafting the cut-off branch from one list into the hole of the other.
    1  ::  2 ::  20 :: []
    10 ::  3 :: []
The second example
    1  ::  _ ::  3  :: []   and    2
    _ :: 20 :: []           and   10
cuts the leaves: 2 from the first list and the leaf 10 from the second one. The interchange gives
    1  :: 10 ::  3 :: []
    2  :: 20 :: []
Not all cuts produce swappable branches: e.g., the leaf 1 of the first list is not interchangeable with the branch 3::[] of the second because they have incompatible types. What we have just shown is a so-called cut-and splice crossover. Other variations (with the same cut point for both chromosomes, with two cut points, etc.) can also be easily written with our library.

Our code implements the above surgery, of cutting and grafting. First, we write the generic traversal with branch replacement, using the Scrap-your-boilerplate generic programming library (SYB). Next, we differentiate the traversal obtaining the procedure to cut a branch at an arbitrary point. Finally, we add grafting of the swapped branches cut off two data structures, obtaining the crossover. Although the branches must match in type, the types of the whole structures may differ. We need effects: the coroutine effect for differentiating the traversal, and non-determinism for choosing a cut location. We also need state to keep track of the number of cuts made to a structure.

The most interesting part is the traversal and its differentiation. The traversal function of the signature below receives a data structure, and a function that can examine a branch and possibly replace it.

    newtype Updates = Updates Int  -- update count
    traverse :: Member (State Updates) r =>
          (forall a. (Data a) => a -> Eff r a) ->
          (forall a. (Data a) => a -> Eff r a)

In the latter case, that function should increment the update count, shared among the traversals of all branches. The traversal is terminated when the count exceeds a threshold. The traverse itself is a wrapper over SYB's gfoldl, counting updates to branches.

    traverse f = check_done $ \x -> f x >>= check_done traverse_children
     where
     threshold = 1
     check_done go x = get >>= \case
       Updates n | n >= threshold -> return x
       _                          -> go x
     traverse_children = gfoldl traverse_child return
     traverse_child builda x = liftM2 ($) builda (traverse f x)

To differentiate the traversal -- to suspend it at each encountered branch -- we need a coroutine effect. The branches may have different types: for example, the traversal of an integer list comes across branches of the type Int and [Int]. Therefore, a custom coroutine effect is needed, abstracting the type of a branch and ensuring it supports the Data interface.

    data YieldD v = forall a. Data a => YieldD a (Maybe a -> v)
    yieldD :: (Data a, Member (State Updates) r, Member YieldD r) =>
              a -> Eff r a
    yieldD x = send (inj . YieldD x) >>= \case
                Nothing -> return x
                Just x  -> modify (\ (Updates n) -> Updates (n+1)) >> return x
The request YieldD sends to its effect handler a value and waits to be resumed with a possibly new value, which becomes the result of yieldD x after incrementing the update count. If the suspension was resumed with no new value, yieldD x just returns x. The request YieldD is easily turned into the description of a structure with a cut branch. A structure of the type a with a hole of the type b is represented as a function Maybe b -> (Eff r (Cut r a)), that waits for a value to fill the hole with and then produces a new Cut:
    data Cut r a = CDone a | Cut (YieldD (Eff r (Cut r a)))

To differentiate traverse we merely apply it to yieldD, obtaining

    traverse_diff :: Data a => a -> Eff r (Cut r (a,Updates))

The next step, cutting a data structure at a random point, is also easy, by non-deterministically choosing one cut point among the many encountered during the whole traversal.

    random_walk :: (Member Choose r, Data a) => a -> Eff r (Cut r (a,Updates))
    random_walk a = traverse_diff a >>= check
      where
        check y@CDone{}            = return y
        check y@(Cut (YieldD x k)) = return y `mplus` (k Nothing >>= check)

Finally, crossover swaps the branches between two data structures cut at non-deterministically chosen points, provided the branches have the suitable type.

    crossover :: (Member Choose r, Data a, Data b) => a -> b -> Eff r (a,b)
    crossover x y = do
      tx <- random_walk x  
      ty <- random_walk y
      case (tx,ty) of
        (Cut (YieldD x kx), Cut (YieldD y ky)) | Just x' <- cast x, Just y' <- cast y -> do
          (xnew,_) <- zip_up =<< kx (Just y')
          (ynew,_) <- zip_up =<< ky (Just x')
          return (xnew,ynew)
        _ -> mzero

As an example, crossing over [1,2,3] with Just 10 produces three possible results: ([10,2,3],Just 1), ([1,10,3],Just 2) and ([1,2,10],Just 3). There are 18 possible ways to crossover [1,2,3] and [10,20], including the two cases described earlier. The code has more examples, including crossover between two trees.

We have presented the library for generic crossover between two arbitrary algebraic data structures. The library is a showcase for extensible effects, demonstrating how easy it is to define a custom effect for a given problem and use it alongside standard effects. We are spared annoying lifting, so typical of monad transformers. Raising and handling of effects is as simple as using side-effectful operations in ML or other impure languages. Unlike ML however, the effects of a function are seen in its type, and the type checker watches that all effects are handled in the end.

Version
The current version is July 2014
References
Crossover.hs [6K]
The source code of the library with many crossover examples

 

Lazy state

It has been claimed that lazy state, backward state and similar effects critically relying on laziness are out of reach of extensible effects -- or free-like monads in general. As it turns out, lazy state is subtle and not quite within the grasp of the familiar monad transformer library (MTL) either. We then demonstrate that extensible effects are not only capable of representing lazy- and backward-state computations, they also go beyond.

Lazy state is best understood on the delightfully puzzling example designed by Albert Y.C. Lai and popularized by Edward Kmett. In MTL, it is written thusly:

    lzs = do
      lzs
      modify ((1::Int):)
One may wonder what could possibly come out of this left recursion. In a strict language, surely nothing: lzs loops. To see what we can get in Haskell, let's look at the type: lzs :: Monad m => StateT [Int] m (). It is a computation over the integer-list state. Let s be the final state of lzs. The computation starts by calling itself; upon return the state will be s, by assumption; the state is then modified by prepending 1. We hence obtain the equation s = 1:s whose solution, in Haskell, is the infinite sequence of ones. To check
    *Main> take 5 . snd $ runState lzs undefined
    [1,1,1,1,1]
lzs indeed ended in the state that is [1,1,..].

MTL, as extensible effects, has been motivated by the desire to compose and extend effectful computations. From its inferred type lzs :: Monad m => StateT [Int] m (), lzs is indeed extensible: it is a state computation on top of an arbitrary effectful m. Let's take it to be the Error monad. Although lzs itself throws no exceptions, it may be used as a part of a larger program that does.

    lzseRun :: Either String ((), [Int])
    lzseRun = runIdentity $ runErrorT $ runStateT lzs undefined
Alas, lzseRun goes into the infinite loop. Again, lzs, taken as it was, does not make any use of the underlying Error monad. Yet that monad drastically changed the lzs behavior. (We shall see that extensible effects can do better.)

We learned two lessons from this experiment. First, trying to be too clever with laziness invariably comes to bite back. As much as looking at the program a wrong way may send it into the infinite loop. Second, lazy state is not easily extensible, by nature. It is not a good counter-example to extensible effects, which emphasize easy extensibility.

Still, the challenge remains: Can we write something like lzs, an on-demand stateful computation, with extensible effects? At first blush, the answer is no. First, the state effect provided by the Eff library is intentionally strict, to stem space leaks. There is the other reason, left as an exercise to the reader. (Solving it will make the explanation below more understandable.)

If we contemplate the lazy state more, we realize how crucial it is to delay the recursive invocation of lzs until its state is demanded. The modify operation in lzs obtains the current state but does not demand its value. That is why lzs does not diverge. To write lzs with extensible effects, we have to make the implicit delay explicit. We have seen the subtlety and the fragility of the lazy state; being explicit seems to be a good idea. We hence arrive at the following declaration of the lazy state effect:

    data LazyState s v where
      LGet  :: LazyState s s
      LPut  :: s -> LazyState s ()
      Delay :: Eff '[LazyState s] a  -> LazyState s a
The LGet and LPut operations need no further explanations; we could have reused the State effect already in the Eff library, if not for the fact that it is strict. Delay is the effect to delay a given stateful computation until its result or state are demanded. The familiar operations on state are defined in terms of sending the effect requests:
    lget      = send LGet
    lput      = send . LPut
    lmodify f = do {s <- lget; lput (f s)}
    
    onDemand :: Member (LazyState s) r => Eff '[LazyState s] v -> Eff r v
    onDemand = send . Delay
The argument of onDemand is an ``effect-closed'' computation, with the sole LazyState. This closedness is inherent in lazy state, as we have seen -- and is easy to understand once we get to the LazyState handler. However, onDemand e itself may be used with arbitrary other effects as we show later.

The handler for LazyState is almost conventional: the LGet request is replied with the current state s and LPut s takes s to be the new state. (Recall, in the Eff library, handle_relay_s is the `deep' handler.)

    runStateLazy :: s -> Eff (LazyState s ': r) a -> Eff r (a,s)
    runStateLazy s = handle_relay_s s (\s x -> return (x,s))
                       (\s req k -> case req of
                           LGet    -> k s s -- reply with s and continue in the state s
                           LPut s  -> k s ()
                           Delay m -> let ~(x,s1) = run $ runStateLazy s m
                                      in k s1 x)
The interesting bit is the handling of Delay -- by running the argument computation m and continuing with its outcome. In a non-strict language, however, runStateLazy s m is not actually performed unless its state s1 or the result x are demanded. This is exactly what we want from the lazy state. It also becomes clear why we need to statically know all the effects of the delayed computation: we should be able to run them all.

That was the whole implementation. Edward Kmett's example looks as follows and produces the expected result:

    lex3 = do
      onDemand lex3
      lmodify ((1::Int):)
    
    ex3Run = let (x,s) = run $ runStateLazy (undefined::[Int]) lex3
             in (x,take 5 s)
    -- ((),[1,1,1,1,1])

There is more: the lazy state computation can be combined in the same program with computations that actually do other effects, like throwing exceptions:

    lex31 :: Member (LazyState [Int]) r => Eff r ()
    lex31 = do
      onDemand (lex31 :: Eff '[LazyState [Int]] ())
      lmodify ((1::Int):)
    
    lex5 = do
      lex31
      x <- lget
      throwError ((take 5 x)::[Int])
    
    ex5Run :: Either [Int] a
    ex5Run = fst . run . runStateLazy (undefined::[Int]) . runError $ lex5
    -- Left [1,1,1,1,1]
    
    ex51Run :: Either [Int] (a,[Int])
    ex51Run = run . runError . runStateLazy (undefined::[Int]) $ lex5
    -- Left [1,1,1,1,1]
Unlike the lzseRun earlier, both ex5Run and ex51Run terminate, with the result shown in the comments. Although lex31 does not throw exceptions, it can be used with any other effect beside LazyState, as its signature shows. It can indeed, regardless of the order LazyState and the other effects are handled. There is a slight sleigh of hand, in writing the signature for lex31 and providing the type annotation on the recursive call. The reader is encouraged to guess its significance.

The backward state, in comparison, is trivial: the run-on-the-mill laziness with no delay tricks. To remind, in the ordinary (forward) state computation, get returns what has been most recently put. With the backward state, get returns what will be  put next. Yes, it is backwards. An example should make it clear:

    st = do
      x <- lget
      lput (1::Int)
      lput (1::Int)
      y <- lget
      lput (2::Int)
      lput (3::Int)
      z <- lget
      lput (4::Int)
      return (x,y,z)
To run it as usual, `forwards', we supply the initial state, say, 0, and obtain the result and the final state, from the last put:
    stF :: ((Int,Int,Int),Int)
    stF = run $ runStateLazy (0::Int) st
    -- ((0,1,3),4)
We used the previously described runStateLazy. The very same st can be run backwards, giving the result and the state from the first put:
    stB :: ((Int,Int,Int),Int)
    stB = runStateBack st
    -- ((1,2,4),1)
Each get gets the value from the following put.

We can play infinite games by modifying the state we have not yet obtained:

    ones :: [Int]
    ones = snd $ runStateBack $ do
      s <- lget
      lput ((1::Int):s)
      
    take 5 ones
    -- [1,1,1,1,1]
As the final exercise, the reader is encouraged to similarly represent the storyline of ``Primer''.

The implementation of runStateBack is unremarkable. Like all laziness tricks, it is best understood through Attribute Grammars. The overall state is represented with two attributes: the inherited getAttr and the synthesized putAttr. The get operation just takes what is in getAttr. All the action is happens at the put s node of the expression tree:

    this.getAttr = child.putAttr
    this.putAttr = s
At the root node, putAttr becomes getAttr, tying the knot. The accompanying source code implements this algorithm in the standard way: the inherited attribute as the argument (i.e., the `environment') and the synthesized as the result of the handler. The code shows another implementation, exploring Haskell's laziness to make putAttr also technically inherited, to accumulate the sequence of updates. This implementation is compatible with deep handlers, and lets us play with different notions of `backwardness'.

In conclusion, we have implemented the effect of delaying an effectful computation until its main- or side-results are needed. We have demonstrated the lazy state as well as Attribute-Grammar--like computations with extensible effects. Our implementation makes the crucial delay points explicit. Furthermore, although the delayed computation is not effect-extensible, the overall computation is.

Version
The current version is July 2015, March 2016
References
LazyState.hs [5K]
The accompanying source code with more examples, using the Eff1 library

Edward Kmett: Comment on the r/haskell thread ``Are extensible effects a complete replacement for mtl?''
June 2015.

 

A bit of history

Perhaps a bit of history may help drawing comparisons with related work. Cartwright and Felleisen's paper that put forward extensible denotational language specifications and hence an alternative to monad transformers was presented in April 1994 -- some 8 months ahead of Liang et al. paper on monad transformers. Very unfortunately Cartwright and Felleisen's paper did not receive the attention it deserved and was largely forgotten. I became aware of it in 2004 and found it remarkably inspiring. The translation into Haskell, with the crucial distinction (the authority no longer being central but distributed) was posted on this web site around 2006. A version of extensible effects close to the one described in the Haskell Symposium paper was written in February 2012 and was shown around privately.
References
Extensible interpreters -- an alternative to monad transformers
The early implementation of extensible effects, in a form close to the exposition in the Cartwright and Felleisen's 1994 paper.

Nondet.hs [3K]
Exceptions.hs [2K]
Extensible.hs [12K]
TList.hs [2K]
The first modern implementation of extensible effects (February 2012). The first two files are the warm-up examples, leading to the full implementation.

 

Extensible interpreters -- an alternative to monad transformers

Cartwright and Felleisen have described a technique for composing interpreters that is an alternative to monad transformers. One particular advantage of their technique (hereafter, EDLS) is that the order of composing interpreters, where it is irrelevant, does not have to be specified at all. In fact, unlike monad transformers, we do not have to commit to a single, statically determined order of sub-interpreters. More importantly, object programs are written in the `direct' rather than the monadic (that is, barely hidden continuation-passing) style. Continuation-passing style has many known usability and performance problems. Cartwright and Felleisen's approach also has a theoretical advantage of providing so-called `stable denotations' for expressions (please see their paper for the precise definition). The abstract and page 2 of EDLS paper are particularly insightful.

Cartwright and Felleisen's paper appeared just a bit prior to Liang, Hudak and Jones' ``Monad Transformers and Modular interpreters'' that introduced monad transformers. In fact, the monad transformers paper mentions Cartwright and Felleisen's direct approach in footnote 1. Perhaps because Cartwright and Felleisen demonstrate their approach in an obscure dialect of Scheme, their work did not receive nearly as much attention as it vastly deserves.

We implement the enhanced EDLS in Haskell and add delimited control. To be precise, we implement the Base interpreter (whose sole operations are Loop and Error) and the following extensions: CBV lambda-calculus, Arithmetic, Storage, Control. The extensions can be added to the Base interpreter in any order and in any combination.

Our implementation has the following advantages over EDLS:

Our main departure from EDLS is is the removal of the `central authority'. There is no semantic `admin' function. Rather, admin is part of the source language and can be used at any place in the code. The `central authority' of EDLS must be an extensible function, requiring meta-language facilities to implement (such as quite non-standard Scheme modules). We do not have central authority. Rather, we have bureaucracy: each specific effect handler interprets its own effects as it can, throwing the rest `upstairs' for higher-level bureaucrats to deal with. Extensibility arises automatically.

We take the meaning of a program to be the union of Values and (unfulfilled) Actions. If the meaning of the program is a (non-bottom) value, the program is terminating. If the meaning of the program is an Action -- the program finished with an error, such as an action to access a non-existing storage cell, or shift without reset, or a user-raised error.

EDLS says, at the very top of p. 3, that the handle in the effect message ``is roughly a conventional continuation.'' Because the admin of EDLS is `outside' of the program (at the point of infinity, so to speak), its continuation indeed appears undelimited. By making our `admin' part of the source language, we recognize the handle in the effect message for what it is: a delimited continuation.

Version
The current version is 1.5, January 2006
References
Robert Cartwright, Matthias Felleisen: Extensible Denotational Language Specifications
Symposium on Theoretical Aspects of Computer Software, 1994. LNCS 789, pp. 244-272.
<http://citeseerx.ist.psu.edu/viewdoc/summary?doi=10.1.1.25.5941>

ExtensibleDS.hs [17K]
The complete code in Haskell98 (plus pattern guards), including several examples

This code is not written in idiomatic Haskell and does not take advantage of types at all. The ubiquitous projections from the universal domain tantamount to ``dynamic typing.'' The code is intentionally written to be close to the EDLS paper, emphasizing denotational semantics, whose domains are untyped. One can certainly do better, for example, employ user-defined datatypes for tagged values, avoiding the ugly string-tagged values.

Having an Effect: The modern reconstruction of EDLS