Let’s look at routing in Halogen. We will start by implementing a router ourselves to show that just because we are using Halogen it doesn’t mean we can’t use the Html api as well.
We need an app that informs us of the best variety of potato depending on how we want to cook them. A vital quality of life tool.
Setup
First setup the project as per here.
We alse want to install the web-html and web-events packages to give us access to the Html api. So in the command line cd to the project directory and:
> spago install web-html web-events
Installation complete.
The router
Lets start by creating the router functionality. Create a new file in src
called Router.purs
. Add the following imports :
module Router where
import Prelude
import Data.Maybe (Maybe(..))
import Effect (Effect)
import Web.Event.EventTarget as EventTarget
import Web.HTML (window)
import Web.HTML.Event.HashChangeEvent.EventTypes as ET
import Web.HTML.Location as Location
import Web.HTML.Window as Window
We want a simple type to represent our routes :
data Route = Roast | Chips | Salad
getRoute
Then lets create a function that will take the hash from the location url. The hash is the part of the url that follows the #
- for example https://somenonexistentdomain.com/apage/#hereisthehash
. Changing the hash of the url in the browser will not cause a page reload, but the change will be stored in the browsers history. It is ideal to use for routing with single page applications.
If it is a matching Url it will return the Route
, otherwise it returns Nothing
.
getRoute :: Effect (Maybe Route)
getRoute = do
hash <- window >>= Window.location >>= Location.hash
pure $ case hash of
"#roast" -> Just Roast
"#chips" -> Just Chips
"#salad" -> Just Salad
_ -> Nothing
Note that this is running in the Effect monad. Just about everything with the Html api runs in this monad since you can create side effects all over the place!
The first line retrieves the hash from the location from the window.
hash <- window >>= Window.location >>= Location.hash
Each function is running in the Effect
monad, so we can’t get the actual value directly - we have to stay in Effect
. We could rewrite this as:
window' <- window
location <- Window.location window'
hash <- Location.hash location
But that is a bit long winded, so we can take advantage of bind as per here.
Next we match on the hash string to get our Route. Obviously this is a bit naff for anthing more than the most simple of routes, but it will do for now.
router
Our router will work by listening to the HashChange event of the browser. The router
function hooks into this event :
router :: (Route -> Effect Unit) -> Effect Unit
router cb = do
listener <- EventTarget.eventListener $ const matchRoute
window' <- window
EventTarget.addEventListener ET.hashchange listener false $ Window.toEventTarget window'
where
matchRoute = do
route <- getRoute
case route of
Just route' -> cb route'
Nothing -> pure unit
The parameter passed to the function has type Route -> Effect Unit
. This is the callback that will be invoked when the route changes. Note it also runs in Effect.
First let us setup the callback that will be invoked by the event.
listener <- EventTarget.eventListener $ const matchRoute
eventListener
takes a callback function and returns an EventListener
- all within Effect
. The callback function we are passing is const matchRoute
. We don’t need the event parameter so we ignore it using const
.
where
matchRoute = do
route <- getRoute
case route of
Just route' -> cb route'
Nothing -> pure unit
This function will get the route and if it is a valid route it will invoke the main callback with the route as a parameter. Otherwise it does nothing.
Now we set up the listener:
window' <- window
EventTarget.addEventListener ET.hashchange listener false $ Window.toEventTarget window'
We neet to pull the window out of Effect
into the window' variable. Then we call addEventListener to set up the HashChangeEvent. The browser will now call matchRoute
whenever there is a hashchange
event.
Pages
Each page is a separate Halogen component. The details aren’t particularly important, but you can pull down the code from here.
Parent
Now lets setup the parent component that will handle showing each page according to the route. A lot of this should be familiar from the last time.
Create a new file under src, Parent.purs
. Add the following imports:
module Parent where
import Prelude
import Children as Children
import Data.Maybe (Maybe(..))
import Data.Symbol (SProxy(..))
import Halogen as H
import Halogen.HTML as HH
import Halogen.HTML.Properties as HP
import Router as R
We are going to need to create our child slots, one for each page:
type ChildSlots = ( roast :: Children.Slot Unit
, chips :: Children.Slot Unit
, salad :: Children.Slot Unit
)
_roast :: SProxy "roast"
_roast = SProxy
_chips :: SProxy "chips"
_chips = SProxy
_salad :: SProxy "salad"
_salad = SProxy
Our State contains the current route :
type State = { currentRoute :: R.Route }
This component will get notifications about the current route and route changes from the parent, in this case that is going to be the main
function. So we need to set up our Query
and Input
types to receive the routes.
data Query a = ChangeRoute R.Route a
type Input = R.Route
Setup the page component:
page :: forall m. H.Component HH.HTML Query Input Void m
page = H.mkComponent { initialState
, render
, eval : H.mkEval $ H.defaultEval
{ handleQuery = handleQuery }
}
Our initialState
function requires that we are passed the initial route to display.
initialState :: Input -> State
initialState route = { currentRoute : route }
The Query sends us a new route to display. We modify our state to hold this new route.
handleQuery :: forall m a. Query a -> H.HalogenM State Void ChildSlots Void m (Maybe a)
handleQuery (ChangeRoute route k) = do
H.modify_ _{ currentRoute = route }
pure $ Just k
Now we move on to the rendering. First lets render the menu :
renderMenu :: forall m . H.ComponentHTML Void ChildSlots m
renderMenu = HH.div_ [ HH.a [ HP.href "#roast" ]
[ HH.text "Roast" ]
, HH.text " | "
, HH.a [ HP.href "#chips" ]
[ HH.text "Chips" ]
, HH.text " | "
, HH.a [ HP.href "#salad" ]
[ HH.text "Salad" ]
]
Then we render the current route :
renderPane :: forall m . State -> H.ComponentHTML Void ChildSlots m
renderPane state =
HH.div_ [ case state.currentRoute of
R.Roast -> HH.slot _roast unit Children.roast unit absurd
R.Chips -> HH.slot _chips unit Children.chips unit absurd
R.Salad -> HH.slot _salad unit Children.salad unit absurd
]
We render a different slot based on what our current route is.
Finally we render the whole app, the menu followed by the current page:
render :: forall m . State -> H.ComponentHTML Void ChildSlots m
render state =
HH.div_ [ renderMenu
, renderPane state
]
main
The main
function is where we will create our component and link it to our router event listener. In src/Main.purs
set the following imports :
import Data.Maybe as Maybe
import Effect (Effect)
import Effect.Aff (launchAff_)
import Halogen as H
import Halogen.Aff as HA
import Halogen.VDom.Driver (runUI)
import Parent as Parent
import Router as R
Then change the main
to the following :
main :: Effect Unit
main = HA.runHalogenAff do
body <- HA.awaitBody
current <- H.liftEffect $ Maybe.fromMaybe R.Roast <$> R.getRoute
io <- runUI Parent.page current body
let
changeRoute route = launchAff_ $
io.query $
H.tell $
Parent.ChangeRoute route
H.liftEffect $ R.router changeRoute
Lines of interest:
current <- H.liftEffect $ Maybe.fromMaybe R.Roast <$> R.getRoute
We need to call R.getRoute
to get the current route so we know which page to display initially. This may just return Nothing, so we use Maybe.fromMaybe
to default to the R.Roast
route if needed. We are using <$> here since R.getRoute
returns an Effect (Maybe Route)
and we want it to be an Effect Route
. Using <$>
allows us to do the work (call fromMaybe
) from within Effect
.
Finally, R.getRoute
returns the route in the Effect monad. But Halogen runs in the Aff monad (an asynchronous layer over Effect). To move from the Effect
monad into Aff
we need to call H.liftEffect
.
Next we call runUI
to kick off the whole halogen process. This time we capture the return of runUI
. This is a reference to our parent component. We will use this to send it ChangeRoute
messages.
We setup the callback function to pass into our router:
let
changeRoute route = launchAff_ $
io.query $
H.tell $
Parent.ChangeRoute route
The io
variable we recieved from runUI
has a query
function property that we can use to send queries to the component. We need to make our query a tell query (one that doesn’t require any result) using H.tell
. Our message is Parent.ChangeRoute
.
io.query
is being run in the Aff
monad, but the router expects the callback to be run in the Effect
monad. launchAff_
will do this for us.
Finally, we call our router and pass the changeRoute
callback to it :
H.liftEffect $ R.router changeRoute
Again, we need to move from Effect
to Aff
with H.liftEffect
.
Finally
That covers some very simple routing. Next I’ll look into using the routing library that handles much more complex cases.
You can find sample code here.