Skip to content

Commit

Permalink
Migrate UseSelector module and run purs-tidy (#5)
Browse files Browse the repository at this point in the history
  • Loading branch information
thomashoneyman authored Aug 7, 2021
1 parent f889de1 commit 583430d
Show file tree
Hide file tree
Showing 13 changed files with 39 additions and 34 deletions.
21 changes: 13 additions & 8 deletions README.md
Original file line number Diff line number Diff line change
Expand Up @@ -199,22 +199,27 @@ main = launchAff_ do
runUI root unit body
```

### Using store with hooks
### Using `halogen-store` with `halogen-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.
If you want to write your component with [Halogen Hooks](https://github.com/thomashoneyman/purescript-halogen-hooks) ,then you can use the `useSelector` hook to access the store.

```purs
module Main where
import Prelude
import Halogen.Hooks as Hooks
import Halogen.Store.Hooks (useSelector)
import Halogen.Store.Select (selectAll)
import Halogen.Store.UseSelector (useSelector)
component :: forall q i o m
. MonadStore BS.Action BS.Store m
=> H.Component q i o m
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
context <- 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.
Unlike `connect`, the context returned by `useSelector` has the type `Maybe store` because the hook does not have access to the store before it is initialized.
13 changes: 7 additions & 6 deletions example/basic-hooks/Basic/Counter.purs
Original file line number Diff line number Diff line change
Expand Up @@ -8,23 +8,24 @@ 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)
import Halogen.Store.UseSelector (useSelector)

component :: forall q i o m
. MonadStore BS.Action BS.Store m
=> H.Component q i o m
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 "Increment" ]
, HH.text $ " Count: " <> show cnt <> " "
, HH.button
[ HE.onClick \_ -> updateStore BS.Decrement ]
[ HH.text "Decrement" ]
]
]
2 changes: 1 addition & 1 deletion example/basic-no-action/NoAction/Counter.purs
Original file line number Diff line number Diff line change
Expand Up @@ -44,7 +44,7 @@ component = connect selectState $ H.mkComponent
HH.div_
[ HH.button
[ HE.onClick \_ -> Increment ]
[ HH.text "Increment"]
[ HH.text "Increment" ]
, HH.text $ " Count: " <> show count <> " "
, HH.button
[ HE.onClick \_ -> Decrement ]
Expand Down
2 changes: 1 addition & 1 deletion example/basic/Basic/Counter.purs
Original file line number Diff line number Diff line change
Expand Up @@ -41,7 +41,7 @@ component = connect selectCount $ H.mkComponent
HH.div_
[ HH.button
[ HE.onClick \_ -> Increment ]
[ HH.text "Increment"]
[ HH.text "Increment" ]
, HH.text $ " Count: " <> show count <> " "
, HH.button
[ HE.onClick \_ -> Decrement ]
Expand Down
2 changes: 1 addition & 1 deletion example/redux-todo/ReduxTodo/Component/AddTodo.purs
Original file line number Diff line number Diff line change
Expand Up @@ -14,7 +14,7 @@ import ReduxTodo.Store.Todos (createTodo)
import Type.Proxy (Proxy(..))
import Web.Event.Event (Event, preventDefault)

type Slot id slots = ( addTodo :: H.Slot (Const Void) Void id | slots )
type Slot id slots = (addTodo :: H.Slot (Const Void) Void id | slots)

addTodo
:: forall act slots m
Expand Down
2 changes: 1 addition & 1 deletion example/redux-todo/ReduxTodo/Component/FilterLink.purs
Original file line number Diff line number Diff line change
Expand Up @@ -15,7 +15,7 @@ import ReduxTodo.Store as Store
import ReduxTodo.Store.Visibility (Visibility, setVisibility)
import Type.Proxy (Proxy(..))

type Slot id slots = ( filterLink :: H.Slot (Const Void) Void id | slots )
type Slot id slots = (filterLink :: H.Slot (Const Void) Void id | slots)

filterLink
:: forall action id slots m
Expand Down
2 changes: 1 addition & 1 deletion example/redux-todo/ReduxTodo/Component/TodoList.purs
Original file line number Diff line number Diff line change
Expand Up @@ -19,7 +19,7 @@ import ReduxTodo.Store.Todos (Todo, toggleTodo)
import ReduxTodo.Store.Visibility (Visibility(..))
import Type.Proxy (Proxy(..))

type Slot id slots = ( todoList :: H.Slot (Const Void) Void id | slots )
type Slot id slots = (todoList :: H.Slot (Const Void) Void id | slots)

todoList
:: forall action slots m
Expand Down
1 change: 0 additions & 1 deletion example/redux-todo/ReduxTodo/Store.purs
Original file line number Diff line number Diff line change
@@ -1,6 +1,5 @@
module ReduxTodo.Store where


import Data.Variant (Variant)
import Data.Variant as Variant
import ReduxTodo.Store.Todos as Todos
Expand Down
2 changes: 1 addition & 1 deletion example/redux-todo/ReduxTodo/Store/Todos.purs
Original file line number Diff line number Diff line change
Expand Up @@ -51,7 +51,7 @@ reduce store = case _ of

store { todos = newTodos }

type Action' v = ( todos :: Action | v )
type Action' v = (todos :: Action | v)

injAction :: forall v. Action -> Variant (Action' v)
injAction = Variant.inj (Proxy :: Proxy "todos")
Expand Down
2 changes: 1 addition & 1 deletion example/redux-todo/ReduxTodo/Store/Visibility.purs
Original file line number Diff line number Diff line change
Expand Up @@ -41,7 +41,7 @@ reduce store = case _ of
SetVisibility visibility ->
store { visibility = visibility }

type Action' v = ( visibility :: Action | v )
type Action' v = (visibility :: Action | v)

injAction :: forall v. Action -> Variant (Action' v)
injAction = Variant.inj (Proxy :: Proxy "visibility")
Expand Down
2 changes: 1 addition & 1 deletion packages.dhall
Original file line number Diff line number Diff line change
@@ -1,4 +1,4 @@
let upstream =
https://github.com/purescript/package-sets/releases/download/psc-0.14.1-20210506/packages.dhall sha256:d199e142515f9cc15838d8e6d724a98cd0ca776ceb426b7b36e841311643e3ef
https://github.com/purescript/package-sets/releases/download/psc-0.14.3-20210722/packages.dhall sha256:1ceb43aa59436bf5601bac45f6f3781c4e1f0e4c2b8458105b018e5ed8c30f8c

in upstream
2 changes: 1 addition & 1 deletion src/Halogen/Store/Connect.purs
Original file line number Diff line number Diff line change
Expand Up @@ -85,7 +85,7 @@ connect (Selector selector) component =
Update newContext ->
H.gets _.context >>= case _ of
Just oldContext | unsafeRefEq oldContext newContext -> pure unit
_ -> H.modify_ _ { context = Just newContext}
_ -> H.modify_ _ { context = Just newContext }

Raise output ->
H.raise output
Expand Down
Original file line number Diff line number Diff line change
@@ -1,4 +1,4 @@
module Halogen.Store.Hooks.UseSelector where
module Halogen.Store.UseSelector where

import Prelude

Expand All @@ -14,13 +14,13 @@ 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)
instance 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
:: 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)
Expand All @@ -29,7 +29,7 @@ useSelector (Selector selector) = Hooks.wrap hook

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

Hooks.pure ctx

0 comments on commit 583430d

Please sign in to comment.