Deku logo

Functional reactive programming

Events

The original FRP type. Always imitated, never duplicated.*

* Haha, get it? Because it's referentially transparent, you can't duplicate anEvent. Oh man that's lame…

If you've been following these docs from the beginning, you've been working with events for several pages already. Every time you used a state hook, you created a Poll as well as a pusher to that Poll.

Deku.do
  pusher /\ event <- useState 42

As we’ll see later, the Poll type is defined in terms of events. You have to understand the Tao of Event before you understand the Te of Poll.

In this section, we’ll look at the Event type constructor and study its strengths and limitations. Armed with that knowledge, you’ll be able to create truly reactive sites for the ages!


Definition

Before we start working with the Event type constructor, let's delve into the canonical definition of Event.

The type constructor and contract

Event is a type constructor that takes a type and returns a type. For example, you can have Event Int, Event String, or Event Unit amongst others. There are several different implementations of Event in PureScript, but the “average” definition is similar to the original definition of Event from the seminal 1997 paper Functional reactive animation by Paul Hudak and Conal Elliott. It's also similar to the definition used in the various Rx frameworks.

type Event a = (a -> Effect Unit) -> Effect (Effect Unit)

Let's unpack what this type is telling us, or its contract. The type is saying:

If you provide me with a way to report values of type a, I’ll provide you with a way to tell me to start and then stop reporting these values.

The “reporter” is the argument to the function of type (a -> Effect Unit). You can think of this as a walkie-talkie or self-addressed stamped envelope. It's what the producer of values uses to “send the values back” to the consumer.

The notion of “sending values back” may sound counter-intuitive, especially if you’re used to seeing patterns in functional programming where values of interest are outputs of functions and not inputs. Yet our value of type a is not the output of any function: it is only an input. More specifically, it is the input into an opaque computational context with type Effect Unit. This Effect Unit often represents a unit of work in a program during which actions like updating a DOM or printing to a console occur.

Going back to the definition of our contract for Event, the right-hand side of the function is of typeEffect (Effect Unit). The two effects represent starting and stopping the emission of events to the callback. When I left-bind on Effect (Effect Unit), I’ll get back an Effect Unit that's called an unsubscriber and events will start flowing to the callback (a -> Effect Unit). Then, when I left-bind (or discard) the unsubscriber of type Effect Unit, the event is asked to stop emitting new values to the (a -> Effect Unit) callback.

Whether the unsubscriber actually stops the flow of events is implementation specific. For example, on unsubscribe, an event may choose to emit several “clean up” instructions before stopping entirely. But in general, the unsubscribe function should turn off the faucet in a reasonable timeframe.

Subscription and unsubscription effects

To get a better sense of how these subscription and unsubscription effects work in practice, let's create a small PureScript program that uses an event to update the DOM. The program uses the raw DOM API without any frameworks. In doing so, we’ll see how the event contract plays out step by step.

View on GithubVITE_START=HandRolledEvent pnpm example
module Examples.HandRolledEvent where

import Deku.Toplevel (runInBody)
import Prelude
import Deku.Toplevel (runInBody)

import Control.Monad.Error.Class (throwError)
import Data.Maybe (maybe)
import Effect (Effect)
import Effect.Exception (error)
import Effect.Random (random)
import Effect.Ref (new, read, write)
import Effect.Timer (clearInterval, setInterval)
import ExampleAssitant (ExampleSignature)
import Web.DOM.Document (createElement, createTextNode)
import Web.DOM.Element (setAttribute, toEventTarget, toNode)
import Web.DOM.Node (appendChild, setTextContent)
import Web.DOM.Text as TN
import Web.Event.Event (EventType(..))
import Web.Event.EventTarget (addEventListener, eventListener)
import Web.HTML (window)
import Web.HTML.HTMLDocument (body, toDocument)
import Web.HTML.HTMLElement as HTMLElement
import Web.HTML.Window (document)
import Deku.Toplevel (runInBody)

type Event a = (a -> Effect Unit) -> Effect (Effect Unit)

main :: Effect Unit
main = do
  bod <- window >>= document >>= body >>= maybe
    (throwError $ error "Could not find body")
    pure
  doc <- window >>= document <#> toDocument
  anchor <- createElement "a" doc
  setAttribute "class" "cursor-pointer" anchor
  setTextContent "Turn on event" (toNode anchor)
  txt <- createTextNode " " doc
  div <- createElement "div" doc
  setAttribute "style" "hidden" div
  appendChild (toNode anchor) (HTMLElement.toNode bod)
  appendChild (TN.toNode txt) (HTMLElement.toNode bod)
  appendChild (toNode div) (HTMLElement.toNode bod)
  onOff <- new false
  unsubscribe <- new (pure unit)
  let
    (event :: Event Number) = \callback -> do
      random >>= callback
      i <- setInterval 400 do
        random >>= callback
      pure do
        clearInterval i
  el <- eventListener \_ -> do
    read onOff >>= case _ of
      false -> do
        u <- event \v -> setTextContent (show v) (toNode div)
        write u unsubscribe
        write true onOff
        setTextContent "Turn off event" (toNode anchor)
      true -> do
        u <- read unsubscribe
        u
        write false onOff
        setTextContent "Turn on event" (toNode anchor)
  addEventListener (EventType "click") el true
    (toEventTarget anchor)
  pure (pure unit)
Turn on event

First, let's zoom in on the hand-rolled event that's doing the updating

let
  (event :: Event Number) = \callback -> do
    random >>= callback
    i <- setInterval 400 do
      random >>= callback
    pure do
      clearInterval i

Let's convince ourselves that this event fulfills the contract (a -> Effect Unit) -> Effect (Effect Unit). The argument callback is our (a -> Effect Unit), so let's verify that it has that type. Indeed it does, as it binds to random. Next, let's see if the return type is Effect (Effect Unit). Indeed it is, as the return type is a thunk that clears the interval, which seems like a sensible unsubscribe action.

So now that we've validated that our event conforms to the contract of Event the next step is looking at what subscription and unsubscription look like. We subscribe like so:

u <- event \v -> setTextContent (show v) (toNode div)
write u unsubscribe

We pass the event a subscriber that takes a float and writes it to a div. This is our callback! It's challenging to follow the control flow because it is not linear, but read through the code block again and convince yourself that this function is the callback in the defintion of Event and therefore is the function that receives the output of random.

Next up is our unsubscribe.

u <- read unsubscribe
u

We read a reference to the unsubscribe function we set when we subscribed to the listener and thunk it. Again, convince yourself that this unsubscribe function is none other than:

pure do
  clearInterval i

Which is why our random number emitting stops emitting when we ask it to. Pretty neat, huh?

You may be wondering: Why have such a backwards control flow just to update stuff in the DOM? Good question! The reason is because, as we’ll learn in the following sections, Event can now act as a killer abstraction for which we will define all sorts of typeclass instances and functions to supercharge our application writing while benefiting from the fast performance of this example.


Interactive events

In the previous section, we saw an example of a Stand-alone event, or an event that managed its own input and unsubscription. This is quite uncommon at the end of the day - the far more common scenario is one where there is a pusher and an event. This type of event is called an Interactive event, the subject of this section.

The create effect

Similar to State hooks from Deku, we can create a pusher and an event with the create effect. It has the following signature:

create
  :: forall a
  . ST Global
    { event :: Event a
    , push :: a -> Effect Unit
    }

Let's write a small program using create. Our program will use the created event to write a message to the console. When clicking on Run program below, make sure to open up the console to see the result!

main = do
  { push, event } <- liftST create
  u <- liftST $ subscribe event log
  push "fee"
  push "fi"
  push "fo"
  liftST u
  push "fum" 

Note how, when you run the program, the word “fum” does not print to the console. This is because the unsubscriber is called before “fum” is pushed to the event.

In Deku, the state hooks are literally just calling create under the hood and passing those down into a DSL representing the DOM. And we have the guile to call those two lines of code a framework… 😤

Lifetime and garbage collection

Interactive events' pushers are created in an Effect context and have the same longevity as a Ref. That is, their lifetime is completely managed by JavaScript garbage collection instead of PureScript. In most cases, modern JavaScript engines are smart enough to clean these when they are no longer needed, but as a precaution, you should have an eye on where you dispatch both pushers and events to make sure too many of them are not accidentally stashed in long-living objects.

Performance notes

The performance of events created using create scales linearly with the number of times the event is subscribed to. Any one unsubscribe has logarithmic performance.


Stand-alone events

The event based on setInterval that we saw earlier on this page is an example of a Stand-alone event. These events do not have a pusher associated with them because all of the pushing happens within the event. They also manage their own unsubscribe effects.

The makeEvent function

To make a stand-alone effect, use the makeEvent function. This function has a pretty frightening signature, so it's not for the feint of heart.

makeEvent
  :: forall a
   . ((forall b. Event b -> (b -> EventfulProgram a) -> ST Global (ST Global Unit)) -> ST Global (ST Global Unit))
  -> Event a

This is similar-ish to the definition of Event above, except that EventfulProgram is a subset of Effect that lets you do a few things, like operations in the ST monad, without triggering additional side effects. As we’ll see in the Effect systems section, this is done so that we can push all side effects to the boundaries of our program.

In theory, you should never have to use this low-level function. If you do, then chances are you’re reading the source code, at which point these docs are but a memory. We miss you, come back 🥲

Idempotency

In the examples we've seen so fars, the unsubscribe effect has only been used to stop loops. However, there is nothing that prevents you from running an unsubscribe effect multiple times.

We've done our best to make sure that unsubscribe is idempotent, meaning that you can run it as many times as you want without wreaking havoc on your program. That said, it's still a good idea to be mindful of how you use it. For example, unsubscribe can have O(log(n)) performance in some cases, which can slow down your program if it's called over and over accidentally. So keep it simple!

Previous
Effects