Deku logo

Functional reactive programming

Filtering

How to make events less eventful.

If you’re implementing any sort of client-side search bar or content-picker, filtering is a must. This section will show you how to filter events.


Filter

Event implements Filterable, meaning that you can use the same functions you use to filter arrays and lists on events.

Filtering an event

You can filter an event using filter from the Filterable typeclass.

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

import Prelude
import Deku.Toplevel (runInBody)

import Data.Filterable (filter)
import Data.Tuple.Nested ((/\))
import Deku.Control (text, text_)
import Deku.DOM as D
import Deku.DOM.Attributes as DA
import Deku.DOM.Listeners as DL
import Deku.Do as Deku
import Deku.Hooks (useState)
import Deku.Toplevel (runInBody)
import Effect (Effect)
import ExampleAssitant (ExampleSignature)
import Deku.Toplevel (runInBody)

main :: Effect Unit
main = void $ runInBody Deku.do
  setNumber /\ number <- useState 50.0
  D.div_
    [ D.input [ DA.xtypeRange, DL.numberOn_ DL.input setNumber ] []
    , D.div_
        [ text_ "Latest less than 50: "
        , text (filter (_ < 50.0) number <#> show)
        ]
    , D.div_
        [ text_ "Latest greater than 50: "
        , text (filter (_ > 50.0) number <#> show)
        ]
    ]
Latest less than 50:
Latest greater than 50:

The other members of Filterable, namely filterMap, partition, partitionMap, are available as well and do what you think they'd do!

A slight of hand

Woah woah woah, you've been turning events into polls using functions like sham and dredge and we've put up with it, but now you’re not even pretending anymore. You're calling filter on an Poll in the example above and you’re passing it off as an event? What gives?

Ok, ok, guilty as charged. The thing is, Polls are Events in the sense that Poll implements all of the typeclasses that Event does. Ecclesiastical scholars of functional theology often call this Eventpolular transubstantiation.

The important thing to know is that events and polls can almost always be used interchangeably in polymorphic functions. So when you build intuition for how one works, it works that way for the other and vice versa. I write more about this here.

Performance considerations

If you use the same filter multiple times, it creates a new subscription for each filter. Consider coupling filter with useMemoized to make things faster if needed.


Compact

Events are compactable as well, which is extremely useful for sketching out systems that occassionally fail before developing robust error handling. The compact function for Event is defined as filterMap identity.

Compacting events

Here's an example of using compact to “turn off” one slider in our application. We can think of the right slider as representing errors, and we write a higher-order function to turn it off via compact.

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

import Prelude
import Deku.Toplevel (runInBody)

import Control.Alt ((<|>))
import Data.Filterable (compact)
import Data.Maybe (Maybe(..))
import Data.Tuple.Nested ((/\))
import Deku.DOM.Attributes as DA
import Deku.Control (text, text_)
import Deku.DOM as D
import Deku.Do as Deku
import Deku.Hooks (useState)
import Deku.DOM.Listeners as DL
import Deku.Toplevel (runInBody)
import Effect (Effect)
import ExampleAssitant (ExampleSignature)
import FRP.Poll (Poll)
import Deku.Toplevel (runInBody)

main :: Effect Unit
main = void $ runInBody Deku.do
  setLeft /\ left <- useState 50.0
  setRight /\ right <- useState 50.0
  let
    eventMaker
      :: forall b c
       . (Poll b -> Poll c)
      -> (Poll Number -> Poll b)
      -> (Poll Number -> Poll b)
      -> Poll c
    eventMaker f l r = f (l left <|> r right)
  D.div_
    [ D.input [ DA.klass_ "mr-2", DA.xtypeRange, DL.numberOn_ DL.input setLeft ]
        []
    , D.input [ DA.xtypeRange, DL.numberOn_ DL.input setRight ] []
    , D.div_
        [ text_ "Responds to both channels: "
        , text (eventMaker identity identity identity <#> show)
        ]
    , D.div_
        [ text_ "Only responds to the left channel: "
        , text
            ( eventMaker compact (map Just) (const (pure Nothing))
                <#> show
            )
        ]
    ]
Responds to both channels: 50.0
Only responds to the left channel: 50.0

Why events cannot wither

The Witherable typeclass from PureScript's filterable package is an amazing class that allows you to accumulate an arbitrary effect every time something is partitioned.

class (Filterable t, Traversable t) <= Witherable t where
  wilt :: forall m a l r. Applicative m =>
    (a -> m (Either l r)) -> t a -> m { left :: t l, right :: t r }

  wither :: forall m a b. Applicative m =>
    (a -> m (Maybe b)) -> t a -> m (t b)

This is very useful for doing things like logging when performing a partition. Types that are Filterable, Compactable, and Witherable achieve the holy trifecta of filtering, which confers unto them a special glow that makes them more pleasant to work with. Unfortunately, for events, this simply isn't possible 😞

There is no way to take an effect applied to each event emission and hoist it to a higher context. If that were the case, we would need to time travel to all future events, retrieve their effects, time travel back, and incorporate them into the enclosing applicative. While the PureScript core team is ardently working on time travel as a stepping stone to dependent types, they haven't figured it out yet, so events cannot wither. But do not let this deter you from using them!