DEV Community

Cover image for A new definition of Behavior
Mike Solomon
Mike Solomon

Posted on • Updated on

A new definition of Behavior

In 1997, Conal Elliott and Paul Hudak published their seminal Functional Reactive Animation (Fran) paper that, over the span of 25 years, has given rise to a host of libraries and frameworks that take their ideas as a point of departure. The paper defines two related types:

The key ideas in Fran are its notions of behaviors and events. Behavoirs are time-varying, reactive values, while events are sets of arbitrarily complex conditions, carrying possibly rich information. Most traiditional values can be treated as behaviors, and when images are thus treated, they become animations.

The genius of Fran is that it allows us to reason about time-dependent values compositionally. As the authors state, "Behaviors are built up from other behaviors, static (non-time-varying) values, and events, via a collection of constructors (combinators)."

In this article, I will argue that, while Elliott and Hudak provide a good definition for Behavior, the type they wind up using is too restrictive. I will then argue that the type that Phil Freeman uses in his purescript-behaviors library — one of the most-used implementations of Elliott and Hudak's ideas — is too conceptually broad. Lastly, I will present a definition that I believe is a good compromise between the two, adequately encapsulating how we intuitively expect behaviors to behave.

Pure Behaviors

Elliott and Hudak define Behavior as follows:

newtype Behavior a = Time -> Tuple a (Behavior a)
Enter fullscreen mode Exit fullscreen mode

Where Time is some semantic domain that could represent (for example) clock time in an animation, simulated time in a test, or no time at all.

The issue with this definition is that it does not allow for measuring effectful phenomena. For example, white noise is a valid function of time but is not possible to encode as a Behavior in Fran due to the side effects of randomness. A similar problem arises with animations based on event busses or network calls, like a player's health bar in a multiplayer game.

Behaviors in PureScript

Phil Freeman, when building his purescript-behavior library, encountered this issue and solved it in a rather ingenious manner.

He starts from a definition similar to that of Elliott and Hudak's Fran:

-- | A `Behavior` acts like a continuous function of time.
-- |
-- | We can construct a sample a `Behavior` from some `Event`, combine `Behavior`s
-- | using `Applicative`, and sample a final `Behavior` on some other `Event`.
Enter fullscreen mode Exit fullscreen mode

Like Fran, Behaviors are functions of time, they can be composed using combinators, and they are reactive, meaning they fit into a logic of events. However, the type he chooses for behavior is radically different.

-- | If you give me an emitter, I'll give you a way
-- | to turn on a stream of values to the emitter
-- | and then to turn it off again
type Event a = (a -> Effect Unit) -> Effect (Effect Unit)
-- | If you give me an emitter of `a -> b`, I'll return an
-- | emitter of `b`.
type Behavior a = forall b. Event (a -> b) -> Event b
Enter fullscreen mode Exit fullscreen mode

In the Fran paper, a Behavior only has time as an input, and does not have a computational context in which it can execute arbitrary side effects as a function of time. In Freeman's definition, arbitrary side effects are baked into the type. Let's examine how.

A Behavior is a function of an Event which, remembering the earlier definition from Fran, emits discrete values at arbitrary times. So rather than being a function of time, it is a function of something (an Event) that will have temporality.

As a motivating example, consider a white-noise behavior: the kind that is not possible using the Fran definition. Suppose that a term random :: Effect Number produces a random value between 0.0 and 1.0 every time it is bound in a monadic context. We then can have:

randomBehavior :: Behavior Number
randomBehavior e = \k -> do
  e \f -> random >>= k <<< f
  pure $ pure unit
Enter fullscreen mode Exit fullscreen mode

What this is saying is: every time the event e emits a function a -> b, we get a random number via random and emit it using the event's emitter k of type b -> Effect Unit. As per the definition of Behavior, we do not know what type b is, nor do we care: all we can do is dutifully pass it along to the next stage of the computation. Another way to think of it is that we use an event to sample a behavior whenever the event emits. In fact, Freeman's sample function, which integrates behaviors into a reactive event-driven system compositionally, is simply:

sample :: forall a b. Behavior a -> Event (a -> b) -> Event b
sample b e = b e
Enter fullscreen mode Exit fullscreen mode

By defining behaviors this way, we achieve the stated goal of Fran: "time-varying, reactive values." They are time varying because they inherit the temporality of an event, and they are reactive because they can execute arbitrary side effects to come up with a value.

An overly-broad definition

While Freeman's definition of Behavior remedies the crucial issue of arbitrary side effects that was present in the original formulation, it casts its net so wide that it allows for behaviors unbecoming of a Behavior. Consider the following three perfectly valid behaviors:

emptyBehavior   a. Behavior a
emptyBehavior _ _ = pure (pure unit)

erraticBehavior  Behavior Int
erraticBehavior e = \k  do
  _  e \f  do
    r  random
    launchAff_ do
      delay (Milliseconds (r * 10_000.0))
      liftEffect $ k (f 42)
  pure (pure unit)

doubleBehavior :: Behavior Int
doubleBehavior e = \k  do
  _  pure $ e \f  k (f 42) *> k (f 42)
  pure (pure unit)
Enter fullscreen mode Exit fullscreen mode

In emptyBehavior, the Behavior does not react to the event at all: it simply swallows it and nothing is emitted when a subscription occurs.

In erraticBehavior, the Behavior reacts to values with a random delay. This means that their original temporality will be lost, and events may even be delivered out of order.

Lastly, in doubleBehavior, while the temporality of the events is preserved, for every one value in, there are two values out.

None of these examples are problematic per se, and they may lead to programs that are desirable in some cases. However, they all stretch the definition of Behavior beyond what most folks would be intuitively comfortable with. The last one, doubleBehavior, is not a function at all as there are multiple outputs for a single input, so it's hard to reconcile this with Freeman's definition of a Behavior as something that "acts like a continuous function of time." So it is our task to determine which, if any, of the above Behaviors should be admissible and to refine the type so that it excludes the problematic ones.

A better Behavior

Let's look at a different definition of behavior that, I believe, is closer to achieving the stated goal of a reactive function of continuous time.

type Behavior a = Effect (Tuple (Effect Unit) (Effect a))
Enter fullscreen mode Exit fullscreen mode

In this section, I'll explore what the definition means and how it can be used in tandem with events to activate arbitrary side effects. I'll then revisit the litmus test above and show how my new definition accepts emptyBehavior while excluding erraticBehavior and doubleBehavior, which I feel is an appropriate dividing line. Lastly, I'll argue that Behavior, when defined this way, is a valid Monad whereas it is problematic as a monad in both Fran's and Freeman's definitions.

Unpacking the new type

The new Behavior type, like Event, has a way to turn something on (the outer effect) and then to turn something off (the inner Effect Unit). Let's compare the types side-by-side to see this:

-- |           emitter               ON.     OFF
type Event a = (a -> Effect Unit) -> Effect (Effect Unit)
-- |              ON             OFF           behavior
type Behavior a = Effect (Tuple (Effect Unit) (Effect a))
Enter fullscreen mode Exit fullscreen mode

That is, when we first thunk a Behavior using this new definition, we turn on an arbitrary side effect (like for example a polling mechanism via HTTP requests) and when we thunk the inner Effect Unit, we turn off the mechanism. For behaviors without setup and teardown, this will be a no-op.

The crucial thing to grok about this new definition of Behavior and perhaps its most counterintuitive aspect is that nowhere is there any representation of time. In the Fran definition of Behavior, time is baked into the definition, and in Freeman's definition, a Behavior is built off of an event, which is a carrier of time. Here, though, time is completely absent. Why?

The key idea that underpins this definition is that all programs exist in time. Meaning that the passage of time does not need to be baked into a definition of Behavior because a Behavior will necessarily be used in a program that has its own temporality. Or, more precisely, the type of Behavior need only share the temporality of the execution context of its program, which in the case of PureScript is Effect. Thus, instead of Time being the carrier of time à la Fran or Event (a -> b) being the carrier of time à la Freeman, here, time is dictated by the program.

To see this play out, let's revisit randomBehavior above and then sample it on an event.

randomBehavior :: Behavior Number
randomBehavior = pure (Tuple (pure unit) random)
Enter fullscreen mode Exit fullscreen mode

The definition, now much simpler, provides a random number generator without any notion of temporality - it is a thin wrapper around random.

Now, let's examine how it is sampled by an Event.

sample :: forall a b. Behavior a -> Event (a -> b) -> Event b
sample ea eAb k = do
  Tuple ua ba <- ea
  u <- eAb \f -> ba >>= k <<< f
  pure do
    ua
    u
Enter fullscreen mode Exit fullscreen mode

Here, sampling does more work than the previous definition of sample, but the outcome is the same. Every time the event emits a function of type a -> b, the Effect a (called ba above) is consulted to yield an a to which the function is applied & then passed to the emitter k.

Here, the functionality of sample is identical to the old definition from purescript-behavior. It just does more work. It's in this function that we link the temporality of an event to a behavior instead of in the definition of a Behavior. Or, in other words, the program decides the temporality of behaviors (in this case by marrying them to event), but the behavior does not decide its own temporality, as it does in the Freeman example (recall ie how erraticBehavior behaved). So, we never have to worry about a rogue behavior emitting too many events. Rather, we can have a small and well-tested surface area of functions, like sample, that work with Behaviors and are guaranteed to have a certain temporal profile.

Drawing the line in the sand

Previously, I mentioned that this new example of behavior admits emptyBehavior while disallowing erraticBehavior and doubleBehavior. We've already seen how doubleBehavior is not possible within the definition of Behavior. erraticBehavior is the same: because the type of Behavior contains an Effect a, which is synchronous, there is no way to significantly alter the temporality of the program, which would require Aff or another asynchronous context.

Of course, this abstraction hides the inconvenient truth that all computations have some temporal cost, which means that for temporal entity A like an event or a program, sampling behavior B will necessarily alter its temporality because of the time the sampling takes. Thankfully, programs are often able to get around this by having an alternative denotational semantics of time than clock time. For example, in the browser, there is the event loop, and we often consider that two things happen at the same time if they occur during the same iteration of this loop. So while this new definition of behavior may be nominally erratic in that it has a computational cost like any computation, it is denotationally sound, as within the semantics of the event loop it does not modify the temporality of the program.

That leaves us with emptyBehavior, which still exists. Here's an example:

emptyBehavior :: forall a. Behavior a
emptyBehavior =
  pure (Tuple (pure unit) (throwException $ error "ha"))
Enter fullscreen mode Exit fullscreen mode

Revisiting the sample function above, this will radically change the outputted event: it will transform an emitting event into radio silence. So why do we accept this? The answer is that no definition of behavior can protect us from programs that do nothing, even Fran's. Using Elliott and Hudak's definition, we can create a behavior that is equally problematic:

emptyBehavior :: forall a. Behavior a
emptyBehavior x = emptyBehavior x
Enter fullscreen mode Exit fullscreen mode

We simply cannot guard against this category of errors using conventional type systems. Instead, we need to rely on well-written and well-tested programs to provide us with these guarantees.

Behaviors as monads

In both Fran's and Freeman's definition of a Behavior, behavior is an applicative while not being a monad. This makes sense conceptually and also implementationally.

Conceptually, behaviors are intended to monitor several independent phenomena and blend them into a single computation. A monad is not needed here because the behaviors do not depend on each other.

Definitionally, a monad would be difficult because of the continuity of Behavior. Let's first see this in the case of Fran.

instance Monad Behavior where
  bind ma f t = let a = fst (ma t) in f a t
Enter fullscreen mode Exit fullscreen mode

While this would satisfy the monadic laws, it is hardly satisfying: it throws out everything but the first value of ma in order to create the mb. Traditionally, comonadic structures like Behavior as defined by Fran can only be meaningful monadic if we can somehow take into account subsequent values of the comonad. In the case, for example, of newtype Cofree f a = Cofree (Tuple a (f (Cofree f a))), whose type is quite similar to Behavior, its monad definition is:

instance bindCofree :: Alternative f => Bind (Cofree f) where
  bind fa f = loop fa
    where
    loop fa' =
      let fh = f (head fa')
      in mkCofree (head fh) ((tail fh) <|> (loop <$> tail fa'))
Enter fullscreen mode Exit fullscreen mode

This works because of the alternative - f, implementing alternative, allows for the fa to keep producing values. However, we trade one problem for another - by recursively alting over f, subsequent values run the risk of becoming huge if for example f is an array: it will take into account all of the recursive branching of ma and all of the recursive branching of mb for each a.

The same problem exists for Freeman's Behavior because Event, which is part of his definition, also branches (I've written more about this here). For each a emitted by an event, a monad spin off a new event, which leads to an explosion of emissions at a certain point.

In the case of Behavior as defined in this article, this problem does not exist because there is no branching. Every ma engenders one and only one value with respect to the Behavior - it only generates multiple values if a program asks it to (remembering that, in my definition, temporality is dictated by the program, not the type). Let's see that in action:

instance Bind Behavior where
  bind (Behavior ea) f = Behavior do
    uu <- new (pure unit)
    Tuple ua aa <- ea
    pure $ Tuple (ua *> join (read uu)) do
      a <- aa
      let Behavior eb = f a
      Tuple ub b <- eb
      join (read uu)
      write ub uu
      b
Enter fullscreen mode Exit fullscreen mode

Yay! Behavior finally has its monad instance. However, even if we can do this, do we want to? Does it mean anything? Sure it does! One example is authentication. If ma is Behavior AuthenticationStatus and f is AuthenticationStatus -> Behavior BankAccount, we absolutely want to have monadic behaviors. At any given time, the beahvior of a bank account will change depending on who's looking.

Conclusion

In this article, I present two historical definitions of Behavior: one from Fran in 1997, and one from purescript-behavior in 2014. Both definitions seek to accomplish the same goal but do so through very different implementations. My argument is that the initial implementation did not capture enough of what the authors wanted out of a behavior, whereas Freeman's definition captured too much. I believe that the definition presented in this article lies at an acceptable spot between the two. It does so by abandoning the one thing that Fran and Freeman have in common: time. Instead, if one operates from the premise that Behavior a type does not need to have temporality built into it because programs, as represented by Effect a, are inherently temporal objects, one can use a much simpler definition of Behavior that avoids several shortcomings of its predecessors.

Top comments (0)