In the last post we covered writing a child component. Now let’s code up a parent component that will create and contain these components as well as coordinate the communication between them.
Create a new file under src
called Parent.purs
. Stick the following in the header:
module Parent where
import Prelude
import Child as Child
import Data.Array ((..))
import Data.Const (Const)
import Data.Maybe (Maybe(..))
import Data.Symbol (SProxy(..))
import Data.Traversable (traverse_)
import Halogen as H
import Halogen.Aff as HA
import Halogen.HTML as HH
Types
First we define some types.
type ChildSlots = ( child :: Child.Slot Int )
_child :: SProxy "child"
_child= SProxy
ChildSlots
represents storage for our child components.
If you recall we defined the type for Child.Slot
as type Slot = H.Slot Query Message
representing the Query
and Message
types used to communicate with the component. H.Slot
needs to take three type variables. Here we add the third. Our component can have more than one child component inserted, and we need to use some way to identify which child we are referring to. In this case we use an Int
and we will be creating three child components, referring to each as 1, 2 or 3.
The _child
variable is set up as an identifier for the slot in ChildSlots
This component doesn’t contain any state itself. So we’ll just define our state as Unit
:
type State = Unit
We need to handle one action - the message that our child components send to us.
data Action
= ReceiveMessage Child.Message
Component
Create the component up as normal. We don’t have any state so just pass const unit
(a function that will always return unit
regardless of it’s parameter):
page :: forall m . H.Component HH.HTML (Const Void) Unit Void m
page =
H.mkComponent { initialState: const unit
, render
, eval: H.mkEval $ H.defaultEval
{ handleAction = handleAction }
}
handleAction
We need to handle the message that we are recieving from our child. This is sent to us via an Action that we can handle in the usual way:
handleAction :: forall m. Action -> H.HalogenM State Action ChildSlots Void m Unit
handleAction ( ReceiveMessage ( Child.SendMessage post@(Child.Post _ id) ) ) =
traverse_ send ( 1..3 )
where
send id'
| id' == id = pure Nothing
| otherwise = H.query _child id' <<<
H.tell $
Child.ReceiveMessage post
The message we recieve contains a Post
- in the parameter for handleAction
we deconstruct this message (Child.SendMessage post@(Child.Post _ id)
in order to extract the full post and the id of the sender. We don’t need the actual text of the post since it is just passed straight to the other children.
send
Let’s first look at the send
function - the function that will send the message to a child component. It takes a parameter (id'
) of the id to send the message to.
If the id is the same as the id of the component that sent the message, we do nothing - we don’t want to send the message back to the original sender.
Otherwise, we need to send a query to the child. Recall that in our child component we coded the handleQuery
function that allowed us to receive messages from the parent. Here is where we are going to send that message using H.query
. The parameters it takes are:
- The first parameter
_child
indicates which slot to send the message to. - The second parameter (
id'
) is the id of the component in the slot - since we are going to have three components of type_child
, each needs a unique id to indicate which one to query. - The query we pass to the component is a /tell style/ query - a query that will not recieve a return value, it is just there to cause some kind of effect in the component. The third parameter,
H.tell
turns our message into a tell style query. Note if we were requesting a result from the component, we would useH.request
to create a /request style/ query. - Finally we pass a
Child.RecieveMessage
value constructed with thepost
.
We need to call send for each of our child components. One thing to bear in mind is that H.query
is an effectful function. It retrns a result in the Halogen monad.
We could do this the long way using do notation like:
do
_ <- send 1
_ <- send 2
_ <- send 3
pure unit
But that is a bit repetitive. We can create an array containing numbers 1 to 3 using range like 1..3
. Instinctively you might think that you could map over this range:
send <$> ( 1 .. 3 )
But this doesn’t work because send returns a HalogenM
monad. Monads need to be run in sequence with the result of each feeding into the next one, map will just return an array contaning 3 monads.
So instead we use traverse which will do what we need. More precisely we use traverse_ (with a trailing underscore) which will discard the final result.
render
Finally we render the component.
render :: forall m. State -> H.ComponentHTML Action ChildSlots m
render _ =
HH.div_ $ renderSlot <$> 1..3
where
renderSlot id =
HH.slot _child id Child.control { id } ( Just <<< ReceiveMessage )
We wrap the view in a div with HH.div_
and then we are going to call renderSlot
3 times. This time we can call map on the range 1 to 3 as renderSlot
doesn’t return a monad.
renderSlot
inserts a child component using HH.slot
. Lets look at the parameters:
_child
first identifies the type of the slot. Recall this was defined above as part ofChildSlots
.- Then we pass
id
- the parameter torenderSlot
, the integer that will identify the slot. Because we are creating three copies of the same component we need an identifier to know which component we are talking about. - Next we call the
control
function in theChild
module that returns the component. This is the child function that callsH.mkComponent
and sets up the component. - Next we pass in any parameters that we want to send to the component. These will get passed to the child component to the
initState
function. - Finally we pass the Action that will be invoked when the child component sends a message to us. This is a function that takes the child message and returns the action to invoke. If we don’t want to invoke an action we can just pass
const Nothing
here, or indeed we can pass a function and process the childs message to determine if we should call an action or not.
Finally
That wraps it up. The code for these last two posts can be found right here.