1
1
{-# LANGUAGE ExistentialQuantification #-}
2
- {-# LANGUAGE ScopedTypeVariables #-}
3
- {-# LANGUAGE PatternGuards #-}
4
- {-# LANGUAGE BangPatterns #-}
5
- {-# LANGUAGE RecordWildCards #-}
6
- {-# LANGUAGE TupleSections #-}
7
- {-# LANGUAGE DeriveDataTypeable #-}
8
- {-# LANGUAGE DeriveGeneric #-}
9
- {-# LANGUAGE GeneralizedNewtypeDeriving #-}
10
- {-# LANGUAGE MultiParamTypeClasses #-}
11
- {-# LANGUAGE GADTs #-}
12
- {-# LANGUAGE RankNTypes #-}
13
-
14
- module Control.Distributed.Process.FSM where
2
+
3
+ -----------------------------------------------------------------------------
4
+ -- |
5
+ -- Module : Control.Distributed.Process.FSM
6
+ -- Copyright : (c) Tim Watson 2017
7
+ -- License : BSD3 (see the file LICENSE)
8
+ --
9
+ -- Maintainer : Tim Watson <[email protected] >
10
+ -- Stability : experimental
11
+ -- Portability : non-portable (requires concurrency)
12
+ --
13
+ -- A /Managed Process/ API for building finite state machines. Losely based
14
+ -- on http://erlang.org/doc/man/gen_statem.html, but with a Haskell-ish
15
+ -- flavour.
16
+ -----------------------------------------------------------------------------
17
+ module Control.Distributed.Process.FSM
18
+ ( -- * Starting / Running an FSM Process
19
+ start
20
+ , run
21
+ -- * Defining FSM Steps, Actions, and Transitions
22
+ , initState
23
+ , yield
24
+ , event
25
+ , pevent
26
+ , enter
27
+ , resume
28
+ , reply
29
+ , postpone
30
+ , putBack
31
+ , nextEvent
32
+ , publishEvent
33
+ , timeout
34
+ , stop
35
+ , await
36
+ , safeWait
37
+ , whenStateIs
38
+ , pick
39
+ , begin
40
+ , join
41
+ , reverseJoin
42
+ , atState
43
+ , always
44
+ , allState
45
+ , matching
46
+ , set
47
+ , put
48
+ -- * DSL-style API (operator sugar)
49
+ , (.|)
50
+ , (|>)
51
+ , (<|)
52
+ , (~>)
53
+ , (*>)
54
+ , (~@)
55
+ , (~?)
56
+ , (^.)
57
+ -- * Useful / Important Types and Utilities
58
+ , Event
59
+ , FSM
60
+ , lift
61
+ , liftIO
62
+ , stateData
63
+ , currentInput
64
+ , currentState
65
+ , currentMessage
66
+ , addTransition
67
+ , Step
68
+ , Transition
69
+ , State
70
+ ) where
15
71
16
72
import Control.Distributed.Process (wrapMessage )
17
73
import Control.Distributed.Process.Extras (ExitReason )
@@ -22,118 +78,225 @@ import Control.Distributed.Process.ManagedProcess
22
78
( processState
23
79
, setProcessState
24
80
, runAfter
25
- , Priority
26
81
)
27
82
import Control.Distributed.Process.ManagedProcess.Server.Priority (setPriority )
28
- import qualified Control.Distributed.Process.ManagedProcess .Internal.Types as MP ( liftIO )
83
+ import Control.Distributed.Process.FSM .Internal.Process
29
84
import Control.Distributed.Process.FSM.Internal.Types
30
85
import Control.Distributed.Process.Serializable (Serializable )
86
+ import Prelude hiding ((*>) )
31
87
88
+ -- | Fluent way to say "yield" when you're building an initial state up (e.g.
89
+ -- whilst utilising "begin").
32
90
initState :: forall s d . s -> d -> Step s d
33
- initState = Yield
91
+ initState = yield
92
+
93
+ -- | Given a state @s@ and state data @d@, set these for the current pass and
94
+ -- all subsequent passes.
95
+ yield :: forall s d . s -> d -> Step s d
96
+ yield = Yield
34
97
98
+ -- | Creates an @Event m@ for some "Serializable" type @m@. When passed to
99
+ -- functions that follow the combinator pattern (such as "await"), will ensure
100
+ -- that only messages of type @m@ are processed by the handling expression.
101
+ --
35
102
event :: (Serializable m ) => Event m
36
103
event = Wait
37
104
105
+ -- | A /prioritised/ version of "event". The server will prioritise messages
106
+ -- matching the "Event" type @m@.
107
+ --
108
+ -- See "Control.Distributed.Process.ManagedProcess.Server.Priority" for more
109
+ -- details about input prioritisation and prioritised process definitions.
38
110
pevent :: (Serializable m ) => Int -> Event m
39
111
pevent = WaitP . setPriority
40
112
113
+ -- | Evaluates to a "Transition" that instructs the process to enter the given
114
+ -- state @s@. All expressions following evaluation of "enter" will see
115
+ -- "currentState" containing the updated value, and any future events will be
116
+ -- processed in the new state.
117
+ --
118
+ -- In addition, should any events/messages have been postponed in a previous
119
+ -- state, they will be immediately placed at the head of the queue (in front of
120
+ -- received messages) and processed once the current pass has been fully evaluated.
121
+ --
41
122
enter :: forall s d . s -> FSM s d (Transition s d )
42
123
enter = return . Enter
43
124
125
+ -- | Evaluates to a "Transition" that postpones the current event.
126
+ --
127
+ -- Postponed events are placed in a temporary queue, where they remain until
128
+ -- the current state changes.
129
+ --
44
130
postpone :: forall s d . FSM s d (Transition s d )
45
131
postpone = return Postpone
46
132
133
+ -- | Evaluates to a "Transition" that places the current input event/message at
134
+ -- the back of the process mailbox. The message will be processed again in due
135
+ -- course, as the mailbox is processed in priority order.
136
+ --
47
137
putBack :: forall s d . FSM s d (Transition s d )
48
138
putBack = return PutBack
49
139
140
+ -- | Evaluates to a "Transition" that places the given "Serializable" message
141
+ -- at the head of the queue. Once the current pass is fully evaluated, the input
142
+ -- will be the next event to be processed unless it is trumped by another input
143
+ -- with a greater priority.
144
+ --
50
145
nextEvent :: forall s d m . (Serializable m ) => m -> FSM s d (Transition s d )
51
146
nextEvent m = return $ Push (wrapMessage m)
52
147
148
+ -- | As "nextEvent", but places the message at the back of the queue by default.
149
+ --
150
+ -- Mailbox priority ordering will still take precedence over insertion order.
151
+ --
53
152
publishEvent :: forall s d m . (Serializable m ) => m -> FSM s d (Transition s d )
54
153
publishEvent m = return $ Enqueue (wrapMessage m)
55
154
155
+ -- | Evaluates to a "Transition" that resumes evaluating the current step.
56
156
resume :: forall s d . FSM s d (Transition s d )
57
157
resume = return Remain
58
158
159
+ -- | This /step/ will send a reply to a client process if (and only if) the
160
+ -- client provided a reply channel (in the form of @SendPort Message@) when
161
+ -- sending its event to the process.
162
+ --
163
+ -- The expression used to produce the reply message must reside in the "FSM" monad.
164
+ -- The reply is /not/ sent immediately upon evaluating "reply", however if the
165
+ -- sender supplied a reply channel, the reply is guaranteed to be sent prior to
166
+ -- evaluating the next pass.
167
+ --
168
+ -- No attempt is made to ensure the receiving process is still alive or understands
169
+ -- the message - the onus is on the author to ensure the client and server
170
+ -- portions of the API understand each other with regard to types.
171
+ --
172
+ -- No exception handling is applied when evaluating the supplied expression.
59
173
reply :: forall s d r . (Serializable r ) => FSM s d r -> Step s d
60
174
reply = Reply
61
175
176
+ -- | Given a "TimeInterval" and a "Serializable" event of type @m@, produces a
177
+ -- "Transition" that will ensure the event is re-queued after at least
178
+ -- @TimeInterval@ has expired.
179
+ --
180
+ -- The same semantics as "System.Timeout" apply here.
181
+ --
62
182
timeout :: Serializable m => TimeInterval -> m -> FSM s d (Transition s d )
63
183
timeout t m = return $ Eval $ runAfter t m
64
184
185
+ -- | Produces a "Transition" that when evaluated, will cause the FSM server
186
+ -- process to stop with the supplied "ExitReason".
65
187
stop :: ExitReason -> FSM s d (Transition s d )
66
188
stop = return . Stop
67
189
190
+ -- | Given a function from @d -> d@, apply it to the current state data.
191
+ --
192
+ -- This expression functions as a "Transition" and is not applied immediately.
193
+ -- To /see/ state data changes in subsequent expressions during a single pass,
194
+ -- use "yield" instead.
68
195
set :: forall s d . (d -> d ) -> FSM s d ()
69
196
set f = addTransition $ Eval $ do
70
- MP. liftIO $ putStrLn " setting state"
197
+ -- MP.liftIO $ putStrLn "setting state"
71
198
processState >>= \ s -> setProcessState $ s { stData = (f $ stData s) }
72
199
200
+ -- | Set the current state data.
201
+ --
202
+ -- This expression functions as a "Transition" and is not applied immediately.
203
+ -- To /see/ state data changes in subsequent expressions during a single pass,
204
+ -- use "yield" instead.
73
205
put :: forall s d . d -> FSM s d ()
74
206
put d = addTransition $ Eval $ do
75
207
processState >>= \ s -> setProcessState $ s { stData = d }
76
208
209
+ -- | Synonym for "pick"
77
210
(.|) :: Step s d -> Step s d -> Step s d
78
211
(.|) = Alternate
79
212
infixr 9 .|
80
213
214
+ -- | Pick one of the two "Step"s. Evaluates the LHS first, and proceeds to
215
+ -- evaluate the RHS only if the left does not produce a valid result.
81
216
pick :: Step s d -> Step s d -> Step s d
82
217
pick = Alternate
83
218
219
+ -- | Synonym for "begin"
84
220
(^.) :: Step s d -> Step s d -> Step s d
85
221
(^.) = Init
86
222
infixr 9 ^.
87
223
224
+ -- | Provides a means to run a "Step" - the /LHS/ or first argument - only once
225
+ -- on initialisation. Subsequent passes will ignore the LHS and run the RHS only.
88
226
begin :: Step s d -> Step s d -> Step s d
89
227
begin = Init
90
228
229
+ -- | Synonym for "join".
91
230
(|>) :: Step s d -> Step s d -> Step s d
92
231
(|>) = Sequence
93
232
infixr 9 |>
94
233
234
+ -- | Join the first and second "Step" by running them sequentially from left to right.
95
235
join :: Step s d -> Step s d -> Step s d
96
236
join = Sequence
97
237
238
+ -- | Inverse of "(|>)"
98
239
(<|) :: Step s d -> Step s d -> Step s d
99
240
(<|) = flip Sequence
100
241
-- infixl 9 <|
101
242
102
243
reverseJoin :: Step s d -> Step s d -> Step s d
103
244
reverseJoin = flip Sequence
104
245
246
+ -- | Synonym for "await"
105
247
(~>) :: forall s d m . (Serializable m ) => Event m -> Step s d -> Step s d
106
248
(~>) = Await
107
249
infixr 9 ~>
108
250
251
+ -- | For any event that matches the type @m@ of the first argument, evaluate
252
+ -- the "Step" given in the second argument.
109
253
await :: forall s d m . (Serializable m ) => Event m -> Step s d -> Step s d
110
254
await = Await
111
255
256
+ -- | Synonym for "safeWait"
112
257
(*>) :: forall s d m . (Serializable m ) => Event m -> Step s d -> Step s d
113
258
(*>) = SafeWait
114
259
infixr 9 *>
115
260
261
+ -- | A /safe/ version of "await". The FSM will place a @check $ safe@ filter
262
+ -- around all messages matching the input type @m@ of the "Event" argument.
263
+ -- Should an exit signal interrupt the current pass, the input event will be
264
+ -- re-tried if an exit handler can be found for the exit-reason.
265
+ --
266
+ -- In all other respects, this API behaves exactly like "await"
116
267
safeWait :: forall s d m . (Serializable m ) => Event m -> Step s d -> Step s d
117
268
safeWait = SafeWait
118
269
270
+ -- | Synonym for "atState"
119
271
(~@) :: forall s d . (Eq s ) => s -> FSM s d (Transition s d ) -> Step s d
120
272
(~@) = Perhaps
121
273
infixr 9 ~@
122
274
275
+ -- | Given a state @s@ and an expression that evaluates to a "Transition",
276
+ -- proceed with evaluation only if the "currentState" is equal to @s@.
123
277
atState :: forall s d . (Eq s ) => s -> FSM s d (Transition s d ) -> Step s d
124
278
atState = Perhaps
125
279
280
+ -- | Fluent way to say @atState s resume@.
126
281
whenStateIs :: forall s d . (Eq s ) => s -> Step s d
127
282
whenStateIs s = s ~@ resume
128
283
284
+ -- | Given an expression from a "Serializable" event @m@ to an expression in the
285
+ -- "FSM" monad that produces a "Transition", apply the expression to the current
286
+ -- input regardless of what our current state is set to.
129
287
allState :: forall s d m . (Serializable m ) => (m -> FSM s d (Transition s d )) -> Step s d
130
288
allState = Always
131
289
290
+ -- | Synonym for "allState".
132
291
always :: forall s d m . (Serializable m ) => (m -> FSM s d (Transition s d )) -> Step s d
133
292
always = Always
134
293
294
+ -- | Synonym for "matching".
135
295
(~?) :: forall s d m . (Serializable m ) => (m -> Bool ) -> (m -> FSM s d (Transition s d )) -> Step s d
136
296
(~?) = Matching
137
297
298
+ -- | Given an expression from a "Serializable" input event @m@ to @Bool@, if the
299
+ -- expression evaluates to @True@ for the current input, pass the input on to the
300
+ -- expression given as the second argument.
138
301
matching :: forall s d m . (Serializable m ) => (m -> Bool ) -> (m -> FSM s d (Transition s d )) -> Step s d
139
302
matching = Matching
0 commit comments