@@ -17,16 +17,18 @@ module Elmish.Component
17
17
18
18
import Prelude
19
19
20
+ import Data.Array ((:))
20
21
import Data.Bifunctor (bimap , lmap , rmap ) as Bifunctor
21
22
import Data.Bifunctor (class Bifunctor )
23
+ import Data.Foldable (sequence_ )
22
24
import Data.Function.Uncurried (Fn2 , runFn2 )
23
- import Data.Maybe (Maybe , maybe )
25
+ import Data.Maybe (Maybe , fromMaybe , maybe )
24
26
import Debug as Debug
25
27
import Effect (Effect , foreachE )
26
28
import Effect.Aff (Aff , Milliseconds (..), delay , launchAff_ )
27
29
import Effect.Class (class MonadEffect , liftEffect )
28
30
import Elmish.Dispatch (Dispatch )
29
- import Elmish.React (ReactComponent , ReactComponentInstance , ReactElement )
31
+ import Elmish.React (ReactComponent , ReactComponentInstance , ReactElement , getField , setField )
30
32
import Elmish.State (StateStrategy , dedicatedStorage , localState )
31
33
import Elmish.Trace (traceTime )
32
34
@@ -36,12 +38,12 @@ import Elmish.Trace (traceTime)
36
38
-- |
37
39
-- | Instances of this type may be created either by using the smart constructor:
38
40
-- |
39
- -- | update :: State -> Message -> Transition' Aff Message State
41
+ -- | update :: State -> Message -> Transition Message State
40
42
-- | update state m = transition state [someCommand]
41
43
-- |
42
44
-- | or in monadic style (see comments on `fork` for more on this):
43
45
-- |
44
- -- | update :: State -> Message -> Transition' Aff Message State
46
+ -- | update :: State -> Message -> Transition Message State
45
47
-- | update state m = do
46
48
-- | s1 <- Child1.update state.child1 Child1.SomeMessage # lmap Child1Msg
47
49
-- | s2 <- Child2.modifyFoo state.child2 # lmap Child2Msg
@@ -51,7 +53,7 @@ import Elmish.Trace (traceTime)
51
53
-- | or, for simple sub-component delegation, the `BiFunctor` instance may be
52
54
-- | used:
53
55
-- |
54
- -- | update :: State -> Message -> Transition' Aff Message State
56
+ -- | update :: State -> Message -> Transition Message State
55
57
-- | update state (ChildMsg m) =
56
58
-- | Child.update state.child m
57
59
-- | # bimap ChildMsg (state { child = _ })
@@ -63,31 +65,36 @@ type Transition msg state = Transition' Aff msg state
63
65
64
66
-- | An effect that is launched as a result of a component state transition.
65
67
-- | It's a function that takes a callback, which allows it to produce (aka
66
- -- | "dispatch") messages.
67
- type Command m msg = (msg -> Effect Unit ) -> m Unit
68
+ -- | "dispatch") messages, as well as an `onStop` function, which allows it to
69
+ -- | install a handler to be executed whent the component is destroyed (aka
70
+ -- | "unmounted").
71
+ -- |
72
+ -- | See `forks` for a more detailed explanation.
73
+ type Command m msg = { dispatch :: Dispatch msg , onStop :: m Unit -> Effect Unit } -> m Unit
68
74
69
- instance trBifunctor :: Functor m => Bifunctor (Transition' m ) where
70
- bimap f g (Transition s cmds) = Transition (g s) (cmds <#> \cmd sink -> cmd $ sink <<< f)
71
- instance trFunctor :: Functor (Transition' m msg ) where
75
+ instance Functor m => Bifunctor (Transition' m ) where
76
+ bimap f g (Transition s cmds) =
77
+ Transition (g s) (cmds <#> \cmd { dispatch, onStop } -> cmd { dispatch: dispatch <<< f, onStop })
78
+ instance Functor (Transition' m msg ) where
72
79
map f (Transition x cmds) = Transition (f x) cmds
73
- instance trApply :: Apply (Transition' m msg ) where
80
+ instance Apply (Transition' m msg ) where
74
81
apply (Transition f cmds1) (Transition x cmds2) = Transition (f x) (cmds1 <> cmds2)
75
- instance trApplicative :: Applicative (Transition' m msg ) where
82
+ instance Applicative (Transition' m msg ) where
76
83
pure a = Transition a []
77
- instance trBind :: Bind (Transition' m msg ) where
84
+ instance Bind (Transition' m msg ) where
78
85
bind (Transition s cmds) f =
79
86
let (Transition s' cmds') = f s
80
87
in Transition s' (cmds <> cmds')
81
- instance trMonad :: Monad (Transition' m msg )
88
+ instance Monad (Transition' m msg )
82
89
83
90
-- | Smart constructor for the `Transition'` type. See comments there. This
84
91
-- | function takes the new (i.e. updated) state and an array of commands - i.e.
85
92
-- | effects producing messages - and constructs a `Transition'` out of them
86
- transition :: forall m state msg . Bind m => MonadEffect m => state -> Array (m msg ) -> Transition' m msg state
93
+ transition :: ∀ m state msg . Bind m => MonadEffect m => state -> Array (m msg ) -> Transition' m msg state
87
94
transition s cmds =
88
- Transition s $ cmds <#> \cmd sink -> do
95
+ Transition s $ cmds <#> \cmd { dispatch } -> do
89
96
msg <- cmd
90
- liftEffect $ sink msg
97
+ liftEffect $ dispatch msg
91
98
92
99
-- | Creates a `Transition'` that contains the given command (i.e. a
93
100
-- | message-producing effect). This is intended to be used for "accumulating"
@@ -116,7 +123,7 @@ transition s cmds =
116
123
-- |
117
124
-- | data Message = ButtonClicked | OnNewItem String
118
125
-- |
119
- -- | update :: State -> Message -> Transition' Aff Message State
126
+ -- | update :: State -> Message -> Transition Message State
120
127
-- | update state ButtonClick = do
121
128
-- | fork $ insertItem "new list"
122
129
-- | incButtonClickCount state
@@ -128,46 +135,63 @@ transition s cmds =
128
135
-- | delay $ Milliseconds 1000.0
129
136
-- | pure $ OnNewItem name
130
137
-- |
131
- -- | incButtonClickCount :: Transition' Aff Message State
138
+ -- | incButtonClickCount :: Transition Message State
132
139
-- | incButtonClickCount state = do
133
140
-- | forkVoid $ trackingEvent "Button click"
134
141
-- | pure $ state { buttonsClicked = state.buttonsClicked + 1 }
135
142
-- |
136
- fork :: forall m message . MonadEffect m => m message -> Transition' m message Unit
143
+ fork :: ∀ m message . MonadEffect m => m message -> Transition' m message Unit
137
144
fork cmd = transition unit [cmd]
138
145
139
146
-- | Similar to `fork` (see comments there for detailed explanation), but the
140
- -- | parameter is a function that takes a message-dispatching callback. This
141
- -- | structure allows the command to produce zero or multiple messages, unlike
142
- -- | `fork`, whose callback has to produce exactly one.
147
+ -- | parameter is a function that takes `dispatch` - a message-dispatching
148
+ -- | callback, as well as `onStop` - a way to be notified when the component is
149
+ -- | destroyed (aka "unmounted"). This structure allows the command to produce
150
+ -- | zero or multiple messages, unlike `fork`, whose callback has to produce
151
+ -- | exactly one, as well as stop listening or free resources etc. when the
152
+ -- | component is unmounted.
153
+ -- |
154
+ -- | NOTE: the `onStop` callback is not recommended for direct use, use the
155
+ -- | subscriptions API in `Elmish.Subscription` instead.
143
156
-- |
144
157
-- | Example:
145
158
-- |
146
- -- | update :: State -> Message -> Transition' Aff Message State
159
+ -- | update :: State -> Message -> Transition Message State
147
160
-- | update state msg = do
148
161
-- | forks countTo10
162
+ -- | forks listenToUrl
149
163
-- | pure state
150
164
-- |
151
165
-- | countTo10 :: Command Aff Message
152
- -- | countTo10 msgSink =
166
+ -- | countTo10 { dispatch } =
153
167
-- | for_ (1..10) \n ->
154
168
-- | delay $ Milliseconds 1000.0
155
- -- | msgSink $ Count n
169
+ -- | dispatch $ Count n
170
+ -- |
171
+ -- | listenToUrl :: Command Aff Message
172
+ -- | listenToUrl { dispatch, onStop } =
173
+ -- | listener <-
174
+ -- | window >>= addEventListener "popstate" do
175
+ -- | newUrl <- window >>= location >>= href
176
+ -- | dispatch $ UrlChanged newUrl
156
177
-- |
157
- forks :: forall m message . Command m message -> Transition' m message Unit
178
+ -- | onStop $
179
+ -- | window >>= removeEventListener listener
180
+ -- |
181
+ forks :: ∀ m message . Command m message -> Transition' m message Unit
158
182
forks cmd = Transition unit [cmd]
159
183
160
184
-- | Similar to `fork` (see comments there for detailed explanation), but the
161
185
-- | effect doesn't produce any messages, it's a fire-and-forget sort of effect.
162
- forkVoid :: forall m message . m Unit -> Transition' m message Unit
186
+ forkVoid :: ∀ m message . m Unit -> Transition' m message Unit
163
187
forkVoid cmd = forks $ const cmd
164
188
165
189
-- | Similar to `fork` (see comments there for detailed explanation), but the
166
190
-- | effect may or may not produce a message, as modeled by returning `Maybe`.
167
- forkMaybe :: forall m message . MonadEffect m => m (Maybe message ) -> Transition' m message Unit
168
- forkMaybe cmd = forks \sink -> do
191
+ forkMaybe :: ∀ m message . MonadEffect m => m (Maybe message ) -> Transition' m message Unit
192
+ forkMaybe cmd = forks \{ dispatch } -> do
169
193
msg <- cmd
170
- liftEffect $ maybe (pure unit) sink msg
194
+ liftEffect $ maybe (pure unit) dispatch msg
171
195
172
196
-- | Definition of a component according to The Elm Architecture. Consists of
173
197
-- | three functions - `init`, `view`, `update`, - that together describe the
@@ -207,12 +231,12 @@ type ComponentDef msg state = ComponentDef' Aff msg state
207
231
-- | Even though this type is rather trivial, it is included in the library for
208
232
-- | the purpose of attaching this documentation to it.
209
233
type ComponentReturnCallback m a =
210
- forall state msg . ComponentDef' m msg state -> a
234
+ ∀ state msg . ComponentDef' m msg state -> a
211
235
212
236
-- | Wraps the given component, intercepts its update cycle, and traces (i.e.
213
237
-- | prints to dev console) every command and every state value (as JSON
214
238
-- | objects), plus timing of renders and state transitions.
215
- withTrace :: forall m msg state
239
+ withTrace :: ∀ m msg state
216
240
. Debug.DebugWarning
217
241
=> ComponentDef' m msg state
218
242
-> ComponentDef' m msg state
@@ -224,16 +248,24 @@ withTrace def = def { update = tracingUpdate, view = tracingView }
224
248
tracingView s d =
225
249
traceTime " Rendering" \_ -> def.view s d
226
250
251
+ -- | This function is low level, not intended for a use in typical consumer
252
+ -- | code. Use `construct` or `wrapWithLocalState` instead.
253
+ -- |
227
254
-- | Takes a component definition (i.e. init+view+update functions) and
228
255
-- | "renders" it as a React DOM element, suitable for passing to
229
256
-- | `ReactDOM.render` or embedding in a JSX DOM tree.
230
- bindComponent :: forall msg state
257
+ bindComponent :: ∀ msg state
231
258
. BaseComponent -- ^ A JS class inheriting from React.Component to serve as base
232
259
-> ComponentDef msg state -- ^ The component definition
233
260
-> StateStrategy state -- ^ Strategy of storing state
234
261
-> ReactElement
235
262
bindComponent cmpt def stateStrategy =
236
- runFn2 instantiateBaseComponent cmpt { init: initialize, render, componentDidMount: runCmds initialCmds }
263
+ runFn2 instantiateBaseComponent cmpt
264
+ { init: initialize
265
+ , render
266
+ , componentDidMount: runCmds initialCmds
267
+ , componentWillUnmount: stopSubscriptions
268
+ }
237
269
where
238
270
Transition initialState initialCmds = def.init
239
271
@@ -256,28 +288,38 @@ bindComponent cmpt def stateStrategy =
256
288
runCmd :: Command Aff msg -> Effect Unit
257
289
runCmd cmd = launchAff_ do
258
290
delay $ Milliseconds 0.0 -- Make sure this call is actually async
259
- cmd $ liftEffect <<< dispatchMsg component
291
+ cmd { dispatch: liftEffect <<< dispatchMsg component, onStop: addSubscription component }
292
+
293
+ addSubscription :: ReactComponentInstance -> Aff Unit -> Effect Unit
294
+ addSubscription component sub = do
295
+ subs <- getSubscriptions component
296
+ setSubscriptions (launchAff_ sub : subs) component
297
+
298
+ stopSubscriptions :: ReactComponentInstance -> Effect Unit
299
+ stopSubscriptions component = do
300
+ sequence_ =<< getSubscriptions component
301
+ setSubscriptions [] component
302
+
303
+ subscriptionsField = " __subscriptions"
304
+ getSubscriptions = getField @(Array (Effect Unit )) subscriptionsField >>> map (fromMaybe [] )
305
+ setSubscriptions = setField @(Array (Effect Unit )) subscriptionsField
260
306
261
307
-- | Given a `ComponentDef'`, binds that def to a freshly created React class,
262
- -- | instantiates that class, and returns a rendering function. Note that the
263
- -- | return type of this function is almost the same as that of
264
- -- | `ComponentDef'::view` - except for state. This is not a coincidence: it is
265
- -- | done this way on purpose, so that the result of this call can be used to
266
- -- | construct another `ComponentDef'`.
308
+ -- | instantiates that class, and returns a rendering function.
267
309
-- |
268
310
-- | Unlike `wrapWithLocalState`, this function uses the bullet-proof strategy
269
311
-- | of storing the component state in a dedicated mutable cell, but that
270
312
-- | happens at the expense of being effectful.
271
- construct :: forall msg state
313
+ construct :: ∀ msg state
272
314
. ComponentDef msg state -- ^ The component definition
273
315
-> Effect ReactElement
274
316
construct def = do
275
317
stateStorage <- liftEffect dedicatedStorage
276
- pure $ withFreshComponent $ \cmpt ->
318
+ pure $ withFreshComponent \cmpt ->
277
319
bindComponent cmpt def stateStorage
278
320
279
321
-- | Monad transformation applied to `ComponentDef'`
280
- nat :: forall m n msg state . (m ~> n ) -> ComponentDef' m msg state -> ComponentDef' n msg state
322
+ nat :: ∀ m n msg state . (m ~> n ) -> ComponentDef' m msg state -> ComponentDef' n msg state
281
323
nat map def =
282
324
{
283
325
view: def.view,
@@ -286,7 +328,7 @@ nat map def =
286
328
}
287
329
where
288
330
mapTransition (Transition state cmds) = Transition state (mapCmd <$> cmds)
289
- mapCmd cmd sink = map $ cmd sink
331
+ mapCmd cmd { dispatch, onStop } = map $ cmd { dispatch, onStop: onStop <<< map }
290
332
291
333
-- | Creates a React component that can be bound to a varying `ComponentDef'`,
292
334
-- | returns a function that performs the binding.
@@ -310,13 +352,13 @@ nat map def =
310
352
-- | proven to be fragile in some specific circumstances (e.g. multiple events
311
353
-- | occurring within the same JS synchronous frame), so it is not recommended
312
354
-- | to use this mechanism for complex components or the top-level program.
313
- wrapWithLocalState :: forall msg state args
355
+ wrapWithLocalState :: ∀ msg state args
314
356
. ComponentName
315
357
-> (args -> ComponentDef msg state )
316
358
-> args
317
359
-> ReactElement
318
360
wrapWithLocalState name mkDef =
319
- runFn2 withCachedComponent name $ \cmpt args ->
361
+ runFn2 withCachedComponent name \cmpt args ->
320
362
bindComponent cmpt (mkDef args) localState
321
363
322
364
-- | A unique name for a component created via `wrapWithLocalState`. These names
@@ -351,11 +393,12 @@ newtype ComponentName = ComponentName String
351
393
352
394
-- Props for the React component that is used as base for this framework. The
353
395
-- component itself is defined in the foreign module.
354
- type BaseComponentProps = {
355
- init :: ReactComponentInstance -> Effect Unit ,
356
- render :: ReactComponentInstance -> Effect ReactElement ,
357
- componentDidMount :: ReactComponentInstance -> Effect Unit
358
- }
396
+ type BaseComponentProps =
397
+ { init :: ReactComponentInstance -> Effect Unit
398
+ , render :: ReactComponentInstance -> Effect ReactElement
399
+ , componentDidMount :: ReactComponentInstance -> Effect Unit
400
+ , componentWillUnmount :: ReactComponentInstance -> Effect Unit
401
+ }
359
402
360
403
type BaseComponent = ReactComponent BaseComponentProps
361
404
@@ -376,9 +419,9 @@ foreign import instantiateBaseComponent :: Fn2 BaseComponent BaseComponentProps
376
419
-- This is essentially a hack, but not quite. It operates in the grey area
377
420
-- between PureScript and JavaScript. See comments on `ComponentName` for a more
378
421
-- detailed explanation.
379
- foreign import withCachedComponent :: forall a . Fn2 ComponentName (BaseComponent -> a ) a
422
+ foreign import withCachedComponent :: ∀ a . Fn2 ComponentName (BaseComponent -> a ) a
380
423
381
424
-- | Creates a fresh React component on every call. This is similar to
382
425
-- | `withCachedComponent`, but without the cache - creates a new component
383
426
-- | every time.
384
- foreign import withFreshComponent :: forall a . (BaseComponent -> a ) -> a
427
+ foreign import withFreshComponent :: ∀ a . (BaseComponent -> a ) -> a
0 commit comments