Skip to content

Commit 43e2a11

Browse files
author
Madeline Trotter
committed
Add non-indexed instances for Render
1 parent 32116d1 commit 43e2a11

File tree

9 files changed

+73
-50
lines changed

9 files changed

+73
-50
lines changed

bower.json

Lines changed: 2 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -16,7 +16,8 @@
1616
"purescript-console": "^4.2.0",
1717
"purescript-effect": "^2.0.0",
1818
"purescript-react-basic": "^7.0.0",
19-
"purescript-indexed-monad": "^1.0.0"
19+
"purescript-indexed-monad": "^1.0.0",
20+
"purescript-unsafe-reference": "^3.0.1"
2021
},
2122
"devDependencies": {
2223
"purescript-psci-support": "^4.0.0"

examples/component/src/Container.purs

Lines changed: 1 addition & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -3,7 +3,6 @@ module Container where
33
import Prelude
44

55
import React.Basic.Hooks(CreateComponent, component, element)
6-
import React.Basic.Hooks as React
76
import React.Basic.DOM as R
87
import ToggleButton (mkToggleButton)
98

@@ -12,7 +11,7 @@ mkToggleButtonContainer = do
1211
toggleButton <- mkToggleButton
1312

1413
component "Container" \_ ->
15-
React.pure $ R.div
14+
pure $ R.div
1615
{ children:
1716
[ element toggleButton { label: "A" }
1817
, element toggleButton { label: "B" }

examples/component/src/ToggleButton.purs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -17,7 +17,7 @@ mkToggleButton = do
1717
log $ "State: " <> if on then "On" else "Off"
1818
pure (pure unit)
1919

20-
React.pure $ R.button
20+
pure $ R.button
2121
{ onClick: handler_ $ setOn not
2222
, children:
2323
[ R.text label

examples/controlled-input/src/ControlledInput.purs

Lines changed: 2 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -2,7 +2,6 @@ module ControlledInput where
22

33
import Prelude
44

5-
import Control.Applicative.Indexed (ipure)
65
import Data.Maybe (Maybe(..), fromMaybe, maybe)
76
import React.Basic.DOM as R
87
import React.Basic.DOM.Events (preventDefault, stopPropagation, targetValue, timeStamp)
@@ -16,7 +15,7 @@ mkControlledInput = do
1615
firstName <- useInput "hello"
1716
lastName <- useInput "world"
1817

19-
React.pure $ R.form_
18+
pure $ R.form_
2019
[ renderInput firstName
2120
, renderInput lastName
2221
]
@@ -38,7 +37,7 @@ useInput
3837
}
3938
useInput initialValue = React.do
4039
{ value, lastChanged } /\ replaceState <- useState { value: initialValue, lastChanged: Nothing }
41-
ipure
40+
pure
4241
{ onChange: handler
4342
(preventDefault >>> stopPropagation >>> merge { targetValue, timeStamp })
4443
\{ timeStamp, targetValue } -> do

examples/counter/src/Counter.purs

Lines changed: 7 additions & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -5,7 +5,7 @@ import Prelude
55
import Effect (Effect)
66
import React.Basic.DOM as R
77
import React.Basic.Events (handler_)
8-
import React.Basic.Hooks (CreateComponent, component, useEffect, useState, (/\))
8+
import React.Basic.Hooks (CreateComponent, component, fragment, useEffect, useState, (/\))
99
import React.Basic.Hooks as React
1010

1111
mkCounter :: CreateComponent {}
@@ -17,9 +17,11 @@ mkCounter = do
1717
setDocumentTitle $ "Count: " <> show counter
1818
pure mempty
1919

20-
React.pure $ R.button
21-
{ onClick: handler_ $ setCounter (_ + 1)
22-
, children: [ R.text $ "Increment: " <> show counter ]
23-
}
20+
pure $ fragment
21+
[ R.button
22+
{ onClick: handler_ $ setCounter (_ + 1)
23+
, children: [ R.text $ "Increment: " <> show counter ]
24+
}
25+
]
2426

2527
foreign import setDocumentTitle :: String -> Effect Unit

examples/reducer/src/Reducer.purs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -20,7 +20,7 @@ mkReducer = do
2020
Increment -> state { counter = state.counter + 1 }
2121
Decrement -> state { counter = state.counter - 1 }
2222

23-
React.pure $ fragment
23+
pure $ fragment
2424
[ R.button
2525
{ onClick: handler_ $ dispatch Decrement
2626
, children: [ R.text $ "Decrement" ]

examples/refs/src/Refs.purs

Lines changed: 21 additions & 21 deletions
Original file line numberDiff line numberDiff line change
@@ -22,27 +22,27 @@ mkRefs :: CreateComponent {}
2222
mkRefs = do
2323
component "Refs" \props -> React.do
2424

25-
mouseDistance1 /\ buttonRef1 <- useNodeDistanceFromMouse
26-
mouseDistance2 /\ buttonRef2 <- useNodeDistanceFromMouse
27-
mouseDistance3 /\ buttonRef3 <- useNodeDistanceFromMouse
25+
mouseDistance1 /\ buttonRef1 <- useNodeDistanceFromMouse
26+
mouseDistance2 /\ buttonRef2 <- useNodeDistanceFromMouse
27+
mouseDistance3 /\ buttonRef3 <- useNodeDistanceFromMouse
2828

29-
React.pure $ fragment
30-
[ element (R.unsafeCreateDOMComponent "button")
31-
{ ref: buttonRef1
32-
, children: [ R.text $ show mouseDistance1 <> "px" ]
33-
, style: R.css { width: "100px", position: "absolute", top: "20px", left: "200px" }
34-
}
35-
, element (R.unsafeCreateDOMComponent "button")
36-
{ ref: buttonRef2
37-
, children: [ R.text $ show mouseDistance2 <> "px" ]
38-
, style: R.css { width: "100px", position: "absolute", top: "60px", left: "40px" }
39-
}
40-
, element (R.unsafeCreateDOMComponent "button")
41-
{ ref: buttonRef3
42-
, children: [ R.text $ show mouseDistance3 <> "px" ]
43-
, style: R.css { width: "100px", position: "absolute", top: "120px", left: "90px" }
44-
}
45-
]
29+
pure $ fragment
30+
[ element (R.unsafeCreateDOMComponent "button")
31+
{ ref: buttonRef1
32+
, children: [ R.text $ show mouseDistance1 <> "px" ]
33+
, style: R.css { width: "100px", position: "absolute", top: "20px", left: "200px" }
34+
}
35+
, element (R.unsafeCreateDOMComponent "button")
36+
{ ref: buttonRef2
37+
, children: [ R.text $ show mouseDistance2 <> "px" ]
38+
, style: R.css { width: "100px", position: "absolute", top: "60px", left: "40px" }
39+
}
40+
, element (R.unsafeCreateDOMComponent "button")
41+
{ ref: buttonRef3
42+
, children: [ R.text $ show mouseDistance3 <> "px" ]
43+
, style: R.css { width: "100px", position: "absolute", top: "120px", left: "90px" }
44+
}
45+
]
4646

4747
type UseNodeDistance hooks = UseEffect Unit (UseState Int (UseRef (Nullable Node) hooks))
4848

@@ -82,4 +82,4 @@ useNodeDistanceFromMouse = React.do
8282
pure do
8383
removeEventListener mouseMoveEventType mouseMoveListener false windowEventTarget
8484

85-
React.pure (mouseDistance /\ elementRef)
85+
pure (mouseDistance /\ elementRef)

examples/todo-app/src/TodoApp.purs

Lines changed: 4 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -67,7 +67,7 @@ mkTodoApp = do
6767

6868
component "TodoApp" \props -> React.do
6969
state /\ dispatch <- useReducer initialState reducer
70-
React.pure $ R.div
70+
pure $ R.div
7171
{ children:
7272
[ element todoInput { dispatch }
7373
, R.div_ $ flip Array.mapWithIndex state.todos \id todo ->
@@ -94,7 +94,7 @@ mkTodoInput :: CreateComponent { dispatch :: Action -> Effect Unit }
9494
mkTodoInput = do
9595
component "TodoInput" \props -> React.do
9696
value /\ setValue <- useState ""
97-
React.pure $ R.form
97+
pure $ R.form
9898
{ onSubmit: handler (preventDefault >>> stopPropagation) \_ -> do
9999
props.dispatch $ CreateTodo value
100100
setValue $ const ""
@@ -113,7 +113,7 @@ mkTodoInput = do
113113

114114
mkTodoRow :: CreateComponent { id :: Int, todo :: Todo, dispatch :: Action -> Effect Unit }
115115
mkTodoRow = component "Todo" \props -> React.do
116-
React.pure $ R.div
116+
pure $ R.div
117117
{ children:
118118
[ R.label
119119
{ children:
@@ -150,7 +150,7 @@ mkTodoFilters = component "TodoFilters" \props -> React.do
150150
then R.css { cursor: "pointer", fontWeight: "bold" }
151151
else R.css { cursor: "pointer" }
152152
}
153-
React.pure $ R.div
153+
pure $ R.div
154154
{ children:
155155
[ R.hr { style: R.css { color: "lightgrey" } }
156156
, filterLink All "All"

src/React/Basic/Hooks.purs

Lines changed: 34 additions & 12 deletions
Original file line numberDiff line numberDiff line change
@@ -40,41 +40,46 @@ module React.Basic.Hooks
4040
, useMemo
4141
, UseMemoLazy
4242
, useMemoLazy
43+
, UnsafeReference(..)
4344
, Render
4445
, Pure
4546
, Hook
4647
, bind
4748
, discard
48-
, pure
4949
, displayName
5050
, module React.Basic
5151
, module Data.Tuple
5252
, module Data.Tuple.Nested
5353
) where
5454

55-
import Prelude hiding (bind, discard, pure)
55+
import Prelude hiding (bind, discard)
5656

57-
import Control.Applicative.Indexed (class IxApplicative, ipure)
57+
import Control.Applicative.Indexed (class IxApplicative)
5858
import Control.Apply.Indexed (class IxApply)
5959
import Control.Bind.Indexed (class IxBind, ibind)
6060
import Data.Function.Uncurried (Fn2, mkFn2)
6161
import Data.Functor.Indexed (class IxFunctor)
6262
import Data.Maybe (Maybe)
63+
import Data.Newtype (class Newtype)
6364
import Data.Nullable (Nullable, toMaybe)
6465
import Data.Tuple (Tuple(..))
6566
import Data.Tuple.Nested (tuple2, (/\))
6667
import Effect (Effect)
6768
import Effect.Uncurried (EffectFn1, EffectFn2, EffectFn3, mkEffectFn1, runEffectFn1, runEffectFn2, runEffectFn3)
68-
import Prelude (bind, pure) as Prelude
69+
import Prelude (bind) as Prelude
6970
import React.Basic (JSX, ReactComponent, empty, keyed, fragment, element, elementKeyed)
71+
import Type.Equality (class TypeEquals)
7072
import Unsafe.Coerce (unsafeCoerce)
73+
import Unsafe.Reference (unsafeRefEq)
7174

72-
-- | Alias for convenience. Creating components is effectful because
73-
-- | React uses the function instance as the component's "identity"
74-
-- | or "type".
75+
-- | Alias for convenience.
7576
type CreateComponent props = Effect (ReactComponent props)
7677

7778
-- | Create a React component given a display name and render function.
79+
-- | Creating components is effectful because React uses the function
80+
-- | instance as the component's "identity" or "type". Components should
81+
-- | be created during a bootstrap phase and not within component
82+
-- | lifecycles or render functions.
7883
component
7984
:: forall hooks props
8085
. String
@@ -191,6 +196,11 @@ useMemoLazy
191196
-> Hook (UseMemoLazy a) a
192197
useMemoLazy key computeA = Render (runEffectFn3 useMemoLazy_ (mkFn2 eq) key computeA)
193198

199+
newtype UnsafeReference a = UnsafeReference a
200+
derive instance newtypeUnsafeReference :: Newtype (UnsafeReference a) _
201+
instance eqUnsafeReference :: Eq (UnsafeReference a) where
202+
eq = unsafeRefEq
203+
194204
-- | Render represents the effects allowed within a React component's
195205
-- | body, i.e. during "render". This includes hooks and ends with
196206
-- | returning JSX (see `pure`), but does not allow arbitrary side
@@ -207,20 +217,32 @@ instance ixFunctorRender :: IxFunctor Render where
207217
instance ixApplyRender :: IxApply Render where
208218
iapply (Render f) (Render a) = Render (apply f a)
209219

220+
instance ixApplicativeRender :: IxApplicative Render where
221+
ipure a = Render (pure a)
222+
210223
instance ixBindRender :: IxBind Render where
211224
ibind (Render m) f = Render (Prelude.bind m \a -> case f a of Render b -> b)
212225

213-
instance ixApplicativeRender :: IxApplicative Render where
214-
ipure a = Render (Prelude.pure a)
215-
226+
-- | Exported for use with qualified-do syntax
216227
bind :: forall a b x y z m. IxBind m => m x y a -> (a -> m y z b) -> m x z b
217228
bind = ibind
218229

230+
-- | Exported for use with qualified-do syntax
219231
discard :: forall a b x y z m. IxBind m => m x y a -> (a -> m y z b) -> m x z b
220232
discard = ibind
221233

222-
pure :: forall a x m. IxApplicative m => a -> m x x a
223-
pure = ipure
234+
instance functorRender :: Functor (Render x y) where
235+
map f (Render a) = Render (map f a)
236+
237+
instance applyRender :: TypeEquals x y => Apply (Render x y) where
238+
apply (Render f) (Render a) = Render (apply f a)
239+
240+
instance applicativeRender :: TypeEquals x y => Applicative (Render x y) where
241+
pure a = Render (pure a)
242+
243+
instance bindRender :: TypeEquals x y => Bind (Render x y) where
244+
bind (Render m) f = Render (Prelude.bind m \a -> case f a of Render b -> b)
245+
224246

225247
-- | Retrieve the Display Name from a `ReactComponent`. Useful for debugging and improving
226248
-- | error messages in logs.

0 commit comments

Comments
 (0)