Skip to content

Commit

Permalink
Add UseSelector hook (#3)
Browse files Browse the repository at this point in the history
  • Loading branch information
katsujukou authored Aug 7, 2021
1 parent abf7d72 commit f889de1
Show file tree
Hide file tree
Showing 10 changed files with 149 additions and 1 deletion.
20 changes: 20 additions & 0 deletions README.md
Original file line number Diff line number Diff line change
Expand Up @@ -198,3 +198,23 @@ main = launchAff_ do
root <- runStoreT BS.initialStore BS.reduce Counter.component
runUI root unit body
```

### Using store with hooks

If you want to write your component with [Halogen Hooks library](https://github.com/thomashoneyman/purescript-halogen-hooks) ,then you can use `useSelector` hook to access store. It takes selector and return the part of current store retrieved via given selector.

```purs
import Halogen.Hooks as Hooks
import Halogen.Store.Hooks (useSelector)
import Halogen.Store.Select (selectAll)
component :: forall q i o m
. MonadStore BS.Action BS.Store m
=> H.Component q i o m
component = Hooks.component \_ _ -> Hooks.do
ctx <- useSelector selectAll
Hooks.pure do
...
```

Unlike the case with connect, though, context returned by `useSelector` hook has type `Maybe store`, because the hook does not have access to store before it has been initialized.
30 changes: 30 additions & 0 deletions example/basic-hooks/Basic/Counter.purs
Original file line number Diff line number Diff line change
@@ -0,0 +1,30 @@
module Hooks.Counter where

import Prelude

import Basic.Store as BS
import Data.Maybe (fromMaybe)
import Halogen as H
import Halogen.HTML as HH
import Halogen.HTML.Events as HE
import Halogen.Hooks as Hooks
import Halogen.Store.Hooks.UseSelector (useSelector)
import Halogen.Store.Monad (class MonadStore, updateStore)
import Halogen.Store.Select (selectEq)

component :: forall q i o m
. MonadStore BS.Action BS.Store m
=> H.Component q i o m
component = Hooks.component \_ _ -> Hooks.do
count <- useSelector $ selectEq _.count
Hooks.pure do
let cnt = fromMaybe 0 count
HH.div_
[ HH.button
[ HE.onClick \_ -> updateStore BS.Increment ]
[ HH.text "Increment"]
, HH.text $ " Count: " <> show cnt <> " "
, HH.button
[ HE.onClick \_ -> updateStore BS.Decrement ]
[ HH.text "Decrement" ]
]
17 changes: 17 additions & 0 deletions example/basic-hooks/Basic/Main.purs
Original file line number Diff line number Diff line change
@@ -0,0 +1,17 @@
module Hooks.Main where

import Prelude

import Basic.Counter as Counter
import Basic.Store as BS
import Effect (Effect)
import Effect.Aff (launchAff_)
import Halogen.Aff as HA
import Halogen.Store.Monad (runStoreT)
import Halogen.VDom.Driver (runUI)

main :: Effect Unit
main = launchAff_ do
body <- HA.awaitBody
root <- runStoreT BS.initialStore BS.reduce Counter.component
runUI root unit body
17 changes: 17 additions & 0 deletions example/basic-hooks/Basic/Store.purs
Original file line number Diff line number Diff line change
@@ -0,0 +1,17 @@
module Hooks.Store where

import Prelude

type Store = { count :: Int }

initialStore :: Store
initialStore = { count: 0 }

data Action
= Increment
| Decrement

reduce :: Store -> Action -> Store
reduce store = case _ of
Increment -> store { count = store.count + 1 }
Decrement -> store { count = store.count - 1 }
3 changes: 3 additions & 0 deletions example/basic-hooks/README.md
Original file line number Diff line number Diff line change
@@ -0,0 +1,3 @@
# Hooks Example

The basic-hooks example is yet another alternative to the basic example. It demonstrates how to access a small store from a single component (a counter) using hooks functionality (`useSeletor`) instead of stateful component.
17 changes: 17 additions & 0 deletions example/basic-hooks/index.html
Original file line number Diff line number Diff line change
@@ -0,0 +1,17 @@
<!DOCTYPE html>
<html>
<head>
<title>Halogen Store - Basic with Hooks</title>
<style>
body {
font-family: sans-serif;
max-width: 800px;
margin: auto;
padding: 50px;
}
</style>
</head>
<body>
<script src="app.js"></script>
</body>
</html>
3 changes: 2 additions & 1 deletion package.json
Original file line number Diff line number Diff line change
Expand Up @@ -4,6 +4,7 @@
"examples": "npm run examples:basic && npm run examples:basic-no-action && npm run examples:redux-todo",
"examples:basic": "spago -x example/example.dhall bundle-app --main Basic.Main --to example/basic/app.js",
"examples:basic-no-action": "spago -x example/example.dhall bundle-app --main NoAction.Main --to example/basic-no-action/app.js",
"examples:redux-todo": "spago -x example/example.dhall bundle-app --main ReduxTodo.Main --to example/redux-todo/app.js"
"examples:redux-todo": "spago -x example/example.dhall bundle-app --main ReduxTodo.Main --to example/redux-todo/app.js",
"examples:basic-hooks": "spago -x example/example.dhall bundle-app --main Hooks.Main --to example/basic-hooks/app.js"
}
}
2 changes: 2 additions & 0 deletions spago.dhall
Original file line number Diff line number Diff line change
Expand Up @@ -4,11 +4,13 @@
, "effect"
, "foldable-traversable"
, "halogen"
, "halogen-hooks"
, "halogen-subscriptions"
, "maybe"
, "prelude"
, "refs"
, "transformers"
, "tuples"
, "unsafe-coerce"
, "unsafe-reference"
]
Expand Down
35 changes: 35 additions & 0 deletions src/Halogen/Store/Hooks/UseSelector.purs
Original file line number Diff line number Diff line change
@@ -0,0 +1,35 @@
module Halogen.Store.Hooks.UseSelector where

import Prelude

import Data.Maybe (Maybe(..))
import Data.Tuple.Nested ((/\))
import Halogen.Hooks (class HookNewtype, type (<>), Hook, UseEffect, UseState)
import Halogen.Hooks as Hooks
import Halogen.Store.Monad (class MonadStore, emitSelected)
import Halogen.Store.Select (Selector(..))

foreign import data UseSelector :: Type -> Type -> Type -> Hooks.HookType

type UseSelector' :: Type -> Type -> Type -> Hooks.HookType
type UseSelector' act store ctx = UseState (Maybe ctx) <> UseEffect <> Hooks.Pure

instance newtypeUseSelector
:: HookNewtype (UseSelector act store ctx) (UseSelector' act store ctx)

useSelector :: forall m act store ctx
. MonadStore act store m
=> Selector store ctx
-> Hook m (UseSelector act store ctx) (Maybe ctx)
useSelector (Selector selector) = Hooks.wrap hook
where
hook :: Hook m (UseSelector' act store ctx) (Maybe ctx)
hook = Hooks.do
ctx /\ ctxId <- Hooks.useState Nothing

Hooks.useLifecycleEffect do
emitter <- emitSelected (Selector selector)
subscriptionId <- Hooks.subscribe $ map (Hooks.put ctxId <<< Just) emitter
pure $ Just $ Hooks.unsubscribe subscriptionId

Hooks.pure ctx
6 changes: 6 additions & 0 deletions src/Halogen/Store/Monad.purs
Original file line number Diff line number Diff line change
Expand Up @@ -13,6 +13,7 @@ import Effect.Ref (Ref)
import Effect.Ref as Ref
import Halogen (HalogenM, hoist)
import Halogen as H
import Halogen.Hooks as Hooks
import Halogen.Store.Select (Selector(..))
import Halogen.Subscription (Emitter, Listener, makeEmitter)
import Halogen.Subscription as HS
Expand Down Expand Up @@ -98,6 +99,11 @@ instance monadStoreHalogenM :: MonadStore a s m => MonadStore a s (HalogenM st a
updateStore = lift <<< updateStore
emitSelected = lift <<< emitSelected

instance monadStoreHookM :: MonadStore a s m => MonadStore a s (Hooks.HookM m) where
getStore = lift getStore
updateStore = lift <<< updateStore
emitSelected = lift <<< emitSelected

-- | Run a component in the `StoreT` monad.
-- |
-- | Requires an initial value for the store, `s`, and a reducer that updates
Expand Down

0 comments on commit f889de1

Please sign in to comment.