Skip to content

Commit

Permalink
ComponentsHalogenHooks in style of React
Browse files Browse the repository at this point in the history
  • Loading branch information
milesfrain committed Dec 8, 2020
1 parent 35243fa commit 3e377e7
Showing 1 changed file with 14 additions and 26 deletions.
40 changes: 14 additions & 26 deletions recipes/ComponentsHalogenHooks/src/Main.purs
Original file line number Diff line number Diff line change
@@ -1,9 +1,8 @@
module ComponentsHalogenHooks.Main where

import Prelude hiding (top)
import Prelude

import Data.Maybe (Maybe(..), maybe)
import Data.Symbol (SProxy(..))
import Data.Tuple.Nested ((/\))
import Effect (Effect)
import Halogen as H
Expand All @@ -20,53 +19,42 @@ main =
body <- HA.awaitBody
void $ runUI containerComponent unit body

_button :: SProxy "button"
_button = SProxy

containerComponent
:: forall unusedQuery unusedInput unusedOutput anyMonad
. H.Component HH.HTML unusedQuery unusedInput unusedOutput anyMonad
containerComponent = Hooks.component \rec _ -> Hooks.do
enabled /\ enabledIdx <- Hooks.useState false
toggleCount /\ toggleCountIdx <- Hooks.useState 0
buttonState /\ buttonStateIdx <- Hooks.useState (Nothing :: Maybe Boolean)
let
handleClick _ =
Just do
Hooks.modify_ toggleCountIdx (_ + 1)
Hooks.modify_ enabledIdx not
label = if enabled then "On" else "Off"
Hooks.pure $
HH.div_
[ HH.slot _button unit buttonComponent unit \_ -> Just do
Hooks.modify_ toggleCountIdx (_ + 1)
[ renderButton {enabled, handleClick}
, HH.p_
[ HH.text ("Button has been toggled " <> show toggleCount <> " time(s)") ]
[ HH.text ("the Button has been toggled " <> show toggleCount <> " time(s)") ]
, HH.p_
[ HH.text
$ "Last time I checked, the button was: "
<> (maybe "(not checked yet)" (if _ then "on" else "off") buttonState)
<> ". "
, HH.button
[ HE.onClick \_ -> Just do
mbBtnState <- Hooks.query rec.slotToken _button unit $ H.request IsOn
Hooks.put buttonStateIdx mbBtnState
Hooks.put buttonStateIdx $ Just enabled
]
[ HH.text "Check now" ]
]
]

data ButtonMessage = Toggled Boolean
data ButtonQuery a = IsOn (Boolean -> a)

buttonComponent
:: forall unusedInput anyMonad
. H.Component HH.HTML ButtonQuery unusedInput ButtonMessage anyMonad
buttonComponent = Hooks.component \rec _ -> Hooks.do
enabled /\ enabledIdx <- Hooks.useState false
Hooks.useQuery rec.queryToken case _ of
IsOn reply -> do
isEnabled <- Hooks.get enabledIdx
pure $ Just $ reply isEnabled
renderButton {enabled, handleClick} =
let label = if enabled then "On" else "Off"
Hooks.pure $
in
HH.button
[ HP.title label
, HE.onClick \_ -> Just do
newState <- Hooks.modify enabledIdx not
Hooks.raise rec.outputToken $ Toggled newState
, HE.onClick handleClick
]
[ HH.text label ]

0 comments on commit 3e377e7

Please sign in to comment.