I often see polling solutions in the wild. Usually we use it in SPAs when we can not / or don't want to use a Websocket connection to update the frontend model of the SPA over time. Polling has for sure it's place when developing a web application and I am not going to argue for one or another.
In this article we will look how polling can be implemented in PureScript Halogen. Halogen itself follows a strict architecture where components are the central idea. If you don't know Halogen yet but are familiar with React in combination of Redux or reducers, this should ring a bell.
We will start with a simple application that will do nothing special - except logging to console as soon as the App is mounted in the DOM:
module Example.Basic.Main where
import Prelude
import Effect (Effect)
import Example.Polling as Polling
import Halogen.Aff as HA
import Halogen.VDom.Driver (runUI)
main :: Effect Unit
= HA.runHalogenAff do
main <- HA.awaitBody
body runUI Polling.component unit body
module Example.Polling (component) where
import Prelude
import Halogen as H
import Halogen.HTML as HH
import Halogen.HTML.Events as HE
import Halogen.HTML.Properties as HP
type State = { }
data Action =
Initialize
| LogToConsole
component :: forall q i o m. H.Component q i o m
=
component
H.mkComponent
{ initialState
, render: H.mkEval $ H.defaultEval { handleAction = handleAction }
, eval
}
initialState :: forall i. i -> State
= { }
initialState _
render :: forall m. State -> H.ComponentHTML Action () m
=
render state "Render something"
HH.text
handleAction :: forall o m. Action -> H.HalogenM State Action () o m Unit
= case _ of
handleAction Initialize -> do
pure unit
LogToConsole -> do
"This is a log entry" traceM
Looking at the code you will find a LogToConsole action. We would like that this action is performed periodically. One way - the obvious one - is to use the delay function from the Effect.Aff module. We can execute the logging, wait 300ms and then re-all the action again:
module Example.Polling (component) where
import Prelude
import Halogen as H
import Halogen.HTML as HH
import Halogen.HTML.Events as HE
import Halogen.HTML.Properties as HP
import Effect.Aff (delay)
type State = { }
data Action =
Initialize
| LogToConsole
| ScheduleLogging
component :: forall q i o m. H.Component q i o m
=
component
H.mkComponent
{ initialState
, render: H.mkEval $ H.defaultEval { handleAction = handleAction }
, eval
}
initialState :: forall i. i -> State
= { }
initialState _
render :: forall m. State -> H.ComponentHTML Action () m
=
render state "Render something"
HH.text
handleAction :: forall o m. Action -> H.HalogenM State Action () o m Unit
= case _ of
handleAction Initialize -> do
ScheduleLogging
handleAction
LogToConsole -> do
"This is a log entry"
traceM
ScheduleLogging -> do
$ H.fork $ handleAction LogToConsole
void <- H.liftEffect $ delay 300
_ ScheduleLogging handleAction
While this solution is straight forward, it is not really reusable, hence bound to only this component. As well we need to work with an extra action for each delay we would like to implement. (And this can grow quite fast. Imagine effects of modals that slide up as a small box and then move to a side. Those would require different actions in a certain flow).
This solution is more or less what we know from the setTimeout method from JavaScript. It is heavily overused since it is simple.
Halogen gives us the possibility to work with a Publisher/Subscriber pattern. And one way to do periodical actions is to create a publisher which creates an event every 300ms and bind a subscriber to it to react to this event. We will do both in the same setup. As well, let's open this function to any Number of milliseconds, not only 300 ms from our example:
import Halogen.Subscription as HS
timer :: forall m a. MonadAff m => Number -> a -> m (HS.Emitter a)
= do
timer delayValue val <- H.liftEffect HS.create
{ emitter, listener } <- H.liftAff $ Aff.forkAff $ forever do
_ $ Milliseconds delayValue
Aff.delay $ HS.notify listener val
H.liftEffect pure emitter
The HS module gives us the possibility to create an emitter / listener combination. Then we can again make use a delay with the given delayValue. When the delay time passes whe can notify our listener.
This is repeated endlessly. The result of this function is an HS.Emitter which we can use to subscribe our component to.
Let's use this in our example code. We can remove the action now and schedule our logging directly when we Init the component:
module Example.Polling (component) where
import Prelude
import Halogen as H
import Halogen.HTML as HH
import Halogen.HTML.Events as HE
import Halogen.HTML.Properties as HP
type State = { }
data Action =
Initialize
| LogToConsole
component :: forall q i o m. H.Component q i o m
=
component
H.mkComponent
{ initialState
, render: H.mkEval $ H.defaultEval { handleAction = handleAction }
, eval
}
initialState :: forall i. i -> State
= { }
initialState _
render :: forall m. State -> H.ComponentHTML Action () m
=
render state "Render something"
HH.text
handleAction :: forall o m. Action -> H.HalogenM State Action () o m Unit
= case _ of
handleAction Initialize -> do
<- H.subscribe =<< timer 300.0 LogToConsole
_ pure unit
LogToConsole -> do
"This is a log entry" traceM
Ah, much cleaner, no?
Thank you for reading this far! Let’s connect. You can @ me on X (@debilofant) with comments, or feel free to follow. Please like/share this article so that it reaches others as well.