• Stars
    star
    157
  • Rank 237,511 (Top 5 %)
  • Language PureScript
  • License
    MIT License
  • Created over 7 years ago
  • Updated over 2 years ago

Reviews

There are no reviews yet. Be the first to send feedback to the community and the maintainers!

Repository Details

An extensible-effects implementation

purescript-run

Latest release Build status

An extensible-effects implementation for PureScript.

Install

spago install run

Documentation

Run is an implementation of extensible, algebraic effects for PureScript. This means we can write composable programs using normal PureScript data types, and then provide interpreters for those data types when we actually want to run them. Our effect descriptions naturally compose with others, so we don't need to write a large encompassing data type, or explicitly lift things through transformer stacks.

You should familiarize yourself with purescript-variant before using Run.

Free DSLs

The Free data type (found in Control.Monad.Free) gives us a means to take any Functor, and get a Monad instance out of it. This lets us turn fairly simple data types into a composable DSL. Here's an example that defines a DSL for string input and output:

data TalkF a
  = Speak String a
  | Listen (String -> a)

derive instance functorTalkF :: Functor TalkF

type Talk = Free TalkF

-- Boilerplate definitions for lifting our constructors
-- into the Free DSL.

speak :: String -> Talk Unit
speak str = liftF (Speak str unit)

listen :: Talk String
listen = liftF (Listen identity)

-- Now we can write programs using our DSL.

program :: Talk Unit
program = do
  speak $ "Hello, what is your name?"
  name <- listen
  speak $ "Nice to meet you, " <> name

Note that this doesn't do anything yet. All we've done is define a data type, and we can write a monadic program with it, but that program still only exists as simple data. In order for it to do something, we'd need to provide an interpreter which pattern matches on the data types:

main :: Effect Unit
main = foldFree go program
  where
  go :: TalkF ~> Effect
  go = case _ of
    -- Just log any speak statement
    Speak str next -> do
      Console.log str
      pure next
    -- Reply to anything with "I am Groot", but maybe
    -- we could also get input from a terminal.
    Listen reply -> do
      pure (reply "I am Groot")
Hello, what is your name?
Nice to meet you, I am Groot

Now say that we've written another orthogonal DSL:

type IsThereMore = Boolean
type Bill = Int

data DinnerF a
  = Eat Food (IsThereMore -> a)
  | CheckPlease (Bill -> a)

type Dinner = Free DinnerF

-- Insert boilerplate here

If we could somehow combine these two data types, we could have a lovely evening indeed. One option is to just define a new DSL which has the capabilities of both:

data LovelyEveningF a
  = Dining (DinnerF a)
  | Talking (TalkF a)

type LovelyEvening = Free LovelyEveningF

But now every time we want to use one DSL or another, we have to explicitly lift them into LovelyEvening using a natural transformation (~>).

liftDinner :: Dinner ~> LovelyEvening
liftDinner = hoistFree Dining

liftTalk :: Talk ~> LovelyEvening
liftTalk = hoistFree Talking

dinnerTime :: LovelyEvening Unit
dinnerTime = do
  liftTalk $ speak "I'm famished!"
  isThereMore <- liftDinner $ eat Pizza
  if isThereMore
    then dinnerTime
    else do
      bill <- liftDinner checkPlease
      liftTalk $ speak "Outrageous!"

We can create these sorts of sums in a general way with Coproduct (Either for Functors):

liftLeft :: forall f g. Free f ~> Free (Coproduct f g)
liftLeft = hoistFree left

liftRight :: forall f g. Free g ~> Free (Coproduct f g)
liftRight = hoistFree right

type LovelyEveningF = Coproduct TalkF DinnerF
type LovelyEvening = Free LovelyEveningF

dinnerTime :: LovelyEvening Unit
dinnerTime = do
  liftLeft $ speak "I'm famished!"
  isThereMore <- liftRight $ eat Pizza
  if isThereMore
    then dinnerTime
    else do
      bill <- liftRight checkPlease
      liftLeft $ speak "Outrageous!"

This has saved us from having to define a new composite data type, but we still have to manually lift everywhere. And what about if we want to add more things to it? We'd need to use more and more Coproducts, which quickly gets very tedious. What if we could instead use an extensible sum type?

Variant lets us encode polymorphic sum types using the row machinery in PureScript. If we look at its big brother VariantF (found in Data.Functor.Variant), we see that it gives us the same capability over Functors and works like an extensible Coproduct.

type TALK r = (talk :: TalkF | r)

_talk = Proxy :: Proxy "talk"

speak :: forall r. String -> Free (VariantF (TALK + r)) Unit
speak str = liftF (inj _talk (Speak str unit))

listen :: forall r. Free (VariantF (TALK + r)) String
listen = liftF (inj _talk (Listen identity))

---

type DINNER r = (dinner :: DinnerF | r)

_dinner = Proxy :: Proxy "dinner"

eat :: forall r. Food -> Free (VariantF (DINNER + r)) IsThereMore
eat food = liftF (inj _dinner (Eat food identity))

checkPlease :: forall r. Free (VariantF (DINNER + r)) Bill
checkPlease = liftF (inj _dinner (CheckPlease identity))

Now our DSLs can be used together without any extra lifting.

type LovelyEvening r = (DINNER + TALK + r)

dinnerTime :: forall r. Free (VariantF (LovelyEvening + r)) Unit
dinnerTime = do
  speak "I'm famished!"
  isThereMore <- eat Pizza
  if isThereMore
    then dinnerTime
    else do
      bill <- checkPlease
      speak "Outrageous!"

This pattern is exactly the Run data type:

newtype Run r a = Run (Free (VariantF r) a)

In fact, this library is just a combinator zoo for writing interpreters.

Writing Interpreters

Lets review our simple TalkF effect and example, now lifted into Run instead of Free:

data TalkF a
  = Speak String a
  | Listen (String -> a)

type TALK r = (talk :: TalkF | r)

_talk = Proxy :: Proxy "talk"

speak :: forall r. String -> Run (TALK + r) Unit
speak str = Run.lift _talk (Speak str unit)

listen :: forall r. Run (TALK + r) String
listen = Run.lift _talk (Listen identity)

program :: forall r. Run (TALK + r) Unit
program = do
  speak $ "Hello, what is your name?"
  name <- listen
  speak $ "Nice to meet you, " <> name

Our original Free based interpreter used foldFree, and we can do the same thing with Run using interpret or interpretRec. The only difference is that interpretRec uses a MonadRec constraint to ensure stack-safety. If your base Monad is stack-safe then you don't need it and should just use interpret.

Since we need to handle a VariantF, we need to use the combinators from purescript-variant, which are re-exported by purescript-run.

handleTalk :: TalkF ~> Effect
handleTalk = case _ of
  Speak str next -> do
    Console.log str
    pure next
  Listen reply -> do
    pure (reply "I am Groot")

main = program # interpret (case_ # on _talk handleTalk)

Here we've used case_, which is the combinator for exhaustive pattern matching. If we use case_, that means we have to provide a handler for every effect. In this case we only have one effect, so it does the job.

Note: An alternative to on chaining is to use onMatch (or match for exhaustive matching) which uses record sugar. This has really nice syntax, but inference around polymorphic members inside of the record can be finicky, so you might need more annotations (or eta expansion) than if you had used on.

Let's try adding back in our other effect for a lovely evening:

type DINNER r = (dinner :: DinnerF | r)

_dinner :: Proxy :: Proxy "dinner"

eat :: forall r. Food -> Run (DINNER + r) IsThereMore
eat food = Run.lift _dinner (Eat food identity)

checkPlease :: forall r. Run (DINNER + r) Bill
checkPlease = Run.lift _dinner (CheckPlease identity)

type LovelyEvening r = (TALK + DINNER + r)

dinnerTime :: forall r. Run (LovelyEvening + r) Unit
dinnerTime = do
  speak "I'm famished!"
  isThereMore <- eat Pizza
  if isThereMore
    then dinnerTime
    else do
      bill <- checkPlease
      speak "Outrageous!"

We could interpret both of these effects together in one go by providing multiple handlers, but oftentimes we only want to handle them in isolation. That is, we want to interpret one effect in terms of other effects at our convenience. We can't use case_ then, because case_ must always handle all effects. Instead we can use send for unmatched cases.

-- This now interprets it back into `Run` but with the `EFFECT` effect.
handleTalk :: forall r. TalkF ~> Run (EFFECT + r)
handleTalk = case _ of
  Speak str next -> do
    -- `liftEffect` lifts native `Effect` effects into `Run`.
    liftEffect $ Console.log str
    pure next
  Listen reply -> do
    pure (reply "I am Groot")

runTalk
  :: forall r
   . Run (EFFECT + TALK + r)
  ~> Run (EFFECT + r)
runTalk = interpret (on _talk handleTalk send)

program2 :: forall r. Run (EFFECT + DINNER + r) Unit
program2 = dinnerTime # runTalk

We've interpreted the TALK effect in terms of the native Effect type, and so it's no longer part of our set of Run effects. Instead, it has been replaced by EFFECT. DINNER has yet to be interpreted, and we can choose to do that at a later time.

In fact, let's go ahead and do that, but we will interpret it in a completely pure manner. We will need an internal accumulator for our interpreter, which we can do with runAccumPure.

type Tally = { stock :: Int, bill :: Bill }

-- We have internal state, which is our running tally of the bill.
handleDinner :: forall a. Tally -> DinnerF a -> Tuple Tally a
handleDinner tally = case _ of
  Eat _ reply
    -- If we have food, bill the customer
    | tally.stock > 0 ->
        let tally' = { stock: tally.stock - 1, bill: tally.bill + 1 }
        in Tuple tally' (reply true)
    | otherwise ->
        Tuple tally (reply false)
  -- Reply with the bill
  CheckPlease reply ->
    Tuple tally (reply tally.bill)

-- We eliminate the `DINNER` effect altogether, yielding the result
-- together with the final bill.
runDinnerPure :: forall r a. Tally -> Run (DINNER + r) a -> Run r (Tuple Bill a)
runDinnerPure = runAccumPure
  (\tally -> on _dinner (Loop <<< handleDinner tally) Done)
  (\tally a -> Tuple tally.bill a)

program3 :: forall r. Run (EFFECT + r) (Tuple Bill Unit)
program3 = program2 # runDinnerPure { stock: 10, bill: 0 }

Since both runPure and runAccumPure fully interpret their result without running through some other Monad or Run effect, we need to preserve stack safety using the Step data type from Control.Monad.Rec.Class. This is why you see the Loop and Done constructors. Loop is used in the case of a match, and Done is used in the default case.

Looking at the type of program3, all we have left are raw Effect effects. Since Effect and Aff are the most likely target for effectful programs, there are a few combinators for extracting them.

program4 :: Effect (Tuple Bill Unit)
program4 = runBaseEffect program3

Additionally there are also combinators for writing interpreters via continuation passing (runCont, runAccumCont). This is useful if you want to just use Effect callbacks as your base instead of something like Aff.

data LogF a = Log String a

derive instance functorLogF :: Functor LogF

type LOG r = (log :: LogF | r)

_log = Proxy :: Proxy "log"

log :: forall r. String -> Run (LOG + r) Unit
log str = Run.lift _log (Log str unit)

---

data SleepF a = Sleep Int a

derive instance functorSleepF :: Functor SleepF

type SLEEP r = (sleep :: SleepF | r)

_sleep = Proxy :: Proxy "sleep"

sleep :: forall r. Int -> Run (SLEEP + r) Unit
sleep ms = Run.lift _sleep (Sleep ms unit)

---

program :: forall r. Run (SLEEP + LOG + r) Unit
program = do
  log "I guess I'll wait..."
  sleep 3000
  log "I can't wait any longer!"

program2 :: Effect Unit
program2 = program # runCont go done
  where
  go = match
    { log: \(Log str cb) -> Console.log str *> cb
    , sleep: \(Sleep ms cb) -> void $ setTimeout ms cb
    }

  done _ = do
    Console.log "Done!"

In this case, the functor component of our effects now has the Effect continuation (or callback) embedded in it, and we just invoke it to run the rest of the program.

Stack-safety

Since the most common target for PureScript is JavaScript, stack-safety can be a concern. Generally, evaluating synchronous Monadic programs is not stack safe unless your particular Monad of choice is designed around it. You should use interpretRec, runRec, and runAccumRec if you want to guarantee stack safety in all cases, but this does come with some overhead.

Since Run itself is stack-safe, it's OK to use interpret, run, and runAccum when interpreting an effect in terms of other Run effects. Aff is also designed to be stack safe. Effect, however, is not stack safe, and you should use the *Rec variations. It's not possible to guarantee stack-safety when using the *Cont interpreters.

More Repositories

1

matches.js

Powerful pattern matching for Javascript
JavaScript
774
star
2

sparkler

Native pattern matching for JavaScript
JavaScript
696
star
3

adt.js

Algebraic data types for Javascript
JavaScript
220
star
4

purescript-spork

Elm-like for PureScript
PureScript
157
star
5

purescript-variant

Polymorphic variants for PureScript
PureScript
132
star
6

adt-simple

Algebraic data types for JavaScript using Sweet.js macros
JavaScript
94
star
7

purescript-tidy

A syntax tidy-upper for PureScript.
PureScript
91
star
8

purescript-psa

Error/Warning reporting frontend for the PureScript compiler
PureScript
88
star
9

purescript-routing-duplex

Unified parsing and printing for routes in PureScript
PureScript
86
star
10

lambda-chop

Sweet.js macros for lambdas with currying, bound functions, and placeholders.
JavaScript
83
star
11

purescript-checked-exceptions

Extensible checked exceptions with polymorphic variants
PureScript
80
star
12

example-functional-compiler

PureScript
59
star
13

purescript-heterogeneous

Maps and folds for heterogeneous data types.
PureScript
54
star
14

purescript-language-cst-parser

PureScript CST Parser written in PureScript
PureScript
49
star
15

tailrec.js

Dead simple auto-trampolining for Javascript
JavaScript
47
star
16

purescript-typelevel-eval

Higher order functional programming in PureScript's type system
PureScript
43
star
17

purescript-cst

A concrete-syntax tree and parser for the PureScript language
Haskell
40
star
18

purescript-convertable-options

Highly-overloaded APIs for PureScript
PureScript
35
star
19

purescript-call-by-name

Syntactically light-weight call-by-name arguments in PureScript. No guarantees. Completely gratuitous.
PureScript
30
star
20

purescript-dodo-printer

An adequate printer.
PureScript
30
star
21

purescript-tidy-codegen

Convenient codegen for PureScript
PureScript
28
star
22

grunt-sweet.js

Grunt task for Sweet.js
JavaScript
27
star
23

purescript-argparse-basic

A no frills CLI argument parser for PureScript.
PureScript
20
star
24

purescript-optimizer

Haskell
20
star
25

purescript-node-workerbees

Convenient multi-threading on Node with PureScript.
PureScript
17
star
26

purescript-run-streaming

Streaming effects for PureScript
PureScript
15
star
27

polykinds

Experimental polykinds implementation
Haskell
14
star
28

purescript-node-glob-basic

A very basic glob library for PureScript.
PureScript
11
star
29

derelicte

An AltJS lang implemented entirely with Sweet.js macros
JavaScript
9
star
30

purescript-free-semigroupoid

Free semigroupoids for PureScript
PureScript
9
star
31

jsScrollbar

A highly customizable javascript scrollbar
JavaScript
9
star
32

purescript-higher-order

PureScript
8
star
33

talks

PureScript
8
star
34

purescript-halogen-connect-experiment

PureScript
5
star
35

purescript-halogen-startapp

PureScript
5
star
36

backbone.ext

Extensions for Backbone.js
JavaScript
3
star
37

purescript-psa-utils

Utility library for purescript-psa
PureScript
2
star