@@ -20,19 +20,22 @@ import Control.Distributed.Process
20
20
, handleMessage
21
21
, handleMessageIf
22
22
, wrapMessage
23
+ , die
23
24
)
24
25
import qualified Control.Distributed.Process as P
25
26
( liftIO
26
27
, Message
27
28
)
28
- import Control.Distributed.Process.Extras (ExitReason )
29
+ import Control.Distributed.Process.Extras (ExitReason ( .. ) )
29
30
import Control.Distributed.Process.ManagedProcess
30
31
( Action
31
32
, GenProcess
32
33
, continue
33
34
, stopWith
34
35
, setProcessState
36
+ , processState
35
37
)
38
+ import qualified Control.Distributed.Process.ManagedProcess.Internal.Types as MP (lift , liftIO )
36
39
import Control.Distributed.Process.ManagedProcess.Server.Priority
37
40
( push
38
41
, act
@@ -62,16 +65,23 @@ import Data.Typeable (Typeable, typeOf)
62
65
import Data.Tuple (swap , uncurry )
63
66
-- import GHC.Generics
64
67
65
- data FsmState s d = FsmState { fsmName :: s
66
- , fsmData :: d
67
- , fsmProg :: Step s d
68
- }
68
+ data State s d = State { stName :: s
69
+ , stData :: d
70
+ , stProg :: Step s d
71
+ , stInput :: Maybe P. Message
72
+ , stReply :: (P. Message -> Process () )
73
+ , stTrans :: Seq (Transition s d )
74
+ }
75
+
76
+ instance forall s d . (Show s ) => Show (State s d ) where
77
+ show State {.. } = " State{stName=" ++ (show stName)
78
+ ++ " , stTrans=" ++ (show stTrans) ++ " }"
69
79
70
80
data Transition s d = Remain
71
81
| PutBack
72
82
| Enter s
73
83
| Stop ExitReason
74
- | Eval (GenProcess (FsmState s d ) () )
84
+ | Eval (GenProcess (State s d ) () )
75
85
76
86
instance forall s d . (Show s ) => Show (Transition s d ) where
77
87
show Remain = " Remain"
@@ -89,6 +99,7 @@ instance forall m . (Typeable m) => Show (Event m) where
89
99
show ev = show $ typeOf ev
90
100
91
101
data Step s d where
102
+ Init :: Step s d -> Step s d -> Step s d
92
103
Yield :: s -> d -> Step s d
93
104
Await :: (Serializable m ) => Event m -> Step s d -> Step s d
94
105
Always :: (Serializable m ) => (m -> FSM s d (Transition s d )) -> Step s d
@@ -100,28 +111,16 @@ data Step s d where
100
111
101
112
instance forall s d . (Show s ) => Show (Step s d ) where
102
113
show st
114
+ | Init _ _ <- st = " Init"
103
115
| Yield _ _ <- st = " Yield"
104
- | Await _ s <- st = " Await (_" ++ (show s) ++ " )"
116
+ | Await _ s <- st = " Await (_ " ++ (show s) ++ " )"
105
117
| Always _ <- st = " Always _"
106
118
| Perhaps s _ <- st = " Perhaps (" ++ (show s) ++ " )"
107
119
| Matching _ _ <- st = " Matching _ _"
108
- | Sequence a b <- st = " Sequence [" ++ (show a) ++ " |> " ++ (show b) ++ " ) "
109
- | Alternate a b <- st = " Alternate [" ++ (show a) ++ " .| " ++ (show b) ++ " ) "
120
+ | Sequence a b <- st = " Sequence [" ++ (show a) ++ " |> " ++ (show b) ++ " ] "
121
+ | Alternate a b <- st = " Alternate [" ++ (show a) ++ " .| " ++ (show b) ++ " ] "
110
122
| Reply _ <- st = " Reply"
111
123
112
- -- instance forall s d (Show s) => Show (Step s d)
113
-
114
- data State s d = State { stName :: s
115
- , stData :: d
116
- , stInput :: P. Message
117
- , stReply :: (P. Message -> Process () )
118
- , stTrans :: Seq (Transition s d )
119
- }
120
-
121
- instance forall s d . (Show s ) => Show (State s d ) where
122
- show State {.. } = " State{stName=" ++ (show stName)
123
- ++ " stTrans" ++ (show stTrans)
124
-
125
124
newtype FSM s d o = FSM {
126
125
unFSM :: ST. StateT (State s d ) Process o
127
126
}
@@ -180,11 +179,18 @@ getR s =
180
179
181
180
enqueue :: State s d -> Maybe (Transition s d ) -> Maybe (State s d )
182
181
enqueue st@ State {.. } trans
183
- | isJust trans = Just $ st { stTrans = seqEnqueue stTrans (fromJust trans) }
182
+ | isJust trans = Just $ st { stTrans = seqPush stTrans (fromJust trans) }
184
183
| otherwise = Nothing
185
184
186
- apply :: State s d -> P. Message -> Step s d -> Process (Maybe (State s d ))
187
- apply st@ State {.. } msg step
185
+ apply :: (Show s ) => State s d -> P. Message -> Step s d -> Process (Maybe (State s d ))
186
+ apply st msg step
187
+ | Init is ns <- step = do
188
+ -- ensure we only `init` successfully once
189
+ P. liftIO $ putStrLn " Init _ _"
190
+ st' <- apply st msg is
191
+ case st' of
192
+ Just s -> apply (s { stProg = ns }) msg ns
193
+ Nothing -> die $ ExitOther $ baseErr ++ " :InitFailed"
188
194
| Yield sn sd <- step = do
189
195
P. liftIO $ putStrLn " Yield s d"
190
196
return $ Just $ st { stName = sn, stData = sd }
@@ -197,9 +203,9 @@ apply st@State{..} msg step
197
203
P. liftIO $ putStrLn " Always..."
198
204
runFSM st (handleMessage msg fsm) >>= mstash
199
205
| Perhaps eqn act <- step = do
200
- P. liftIO $ putStrLn $ " Perhaps"
201
- if eqn == stName then runFSM st act >>= stash
202
- else (P. liftIO $ putStrLn " Perhaps Not..." ) >> return Nothing
206
+ P. liftIO $ putStrLn $ " Perhaps " ++ ( show eqn) ++ " in " ++ ( show $ stName st)
207
+ if eqn == ( stName st) then runFSM st act >>= stash
208
+ else (P. liftIO $ putStrLn " Perhaps Not..." ) >> return Nothing
203
209
| Matching chk fsm <- step = do
204
210
P. liftIO $ putStrLn " Matching..."
205
211
runFSM st (handleMessageIf msg chk fsm) >>= mstash
@@ -211,40 +217,45 @@ apply st@State{..} msg step
211
217
P. liftIO $ putStrLn $ " Alt LHS valid: " ++ (show $ isJust s)
212
218
if isJust s then return s
213
219
else (P. liftIO $ putStrLn " try br 2" ) >> apply st msg al2
214
- | Reply rply <- step = do (r, s) <- runFSM st rply
215
- stReply $ wrapMessage r
216
- return $ Just s
220
+ | Reply rply <- step = do
221
+ let ev = Eval $ do fSt <- processState
222
+ MP. lift $ do
223
+ P. liftIO $ putStrLn $ " Replying from " ++ (show fSt)
224
+ (r, s) <- runFSM fSt rply
225
+ (stReply fSt) $ wrapMessage r
226
+ -- (_, st') <- runFSM st (addTransition ev)
227
+ return $ enqueue st (Just ev)
217
228
| otherwise = error $ baseErr ++ " .Internal.Types.apply:InvalidStep"
218
229
where
219
230
mstash = return . uncurry enqueue . swap
220
231
stash (o, s) = return $ enqueue s (Just o)
221
232
222
- applyTransitions :: forall s d . FsmState s d
223
- -> State s d
224
- -> [GenProcess (FsmState s d ) () ]
225
- -> Action (FsmState s d )
226
- applyTransitions fsmSt st@ State {.. } evals
227
- | Q. null stTrans, [] <- evals = continue $ copyState fsmSt stName stData
228
- | Q. null stTrans = act $ do setProcessState $ copyState fsmSt stName stData
233
+ applyTransitions :: forall s d . (Show s )
234
+ => State s d
235
+ -> [GenProcess (State s d ) () ]
236
+ -> Action (State s d )
237
+ applyTransitions st@ State {.. } evals
238
+ | Q. null stTrans, [] <- evals = continue $ st
239
+ | Q. null stTrans = act $ do setProcessState st
240
+ MP. liftIO $ putStrLn $ " ProcessState: " ++ (show stName)
229
241
mapM_ id evals
230
242
| (tr, st2) <- next
231
243
, Enter s <- tr = let st' = st2 { stName = s }
232
- in applyTransitions (copyState fsmSt s stData) st' evals
244
+ in do P. liftIO $ putStrLn $ " NEWSTATE: " ++ (show st')
245
+ applyTransitions st' evals
233
246
| (tr, st2) <- next
234
- , PutBack <- tr = applyTransitions fsmSt st2 ((push stInput) : evals)
247
+ , PutBack <- tr = applyTransitions st2 ((push $ fromJust stInput) : evals)
235
248
{- let act' = setProcessState $ fsmSt { fsmName = stName, fsmData = stData }
236
249
push stInput -}
237
250
| (tr, st2) <- next
238
- , Eval proc <- tr = applyTransitions fsmSt st2 (proc : evals)
251
+ , Eval proc <- tr = applyTransitions st2 (proc : evals)
239
252
| (tr, st2) <- next
240
- , Remain <- tr = applyTransitions fsmSt st2 evals
253
+ , Remain <- tr = applyTransitions st2 evals
241
254
| (tr, _) <- next
242
- , Stop er <- tr = stopWith (copyState fsmSt stName stData) er
255
+ , Stop er <- tr = stopWith st er
243
256
| otherwise = error $ baseErr ++ " .Internal.Process.applyTransitions:InvalidState"
244
257
where
245
- copyState f sn sd = f { fsmName = sn, fsmData = sd }
246
-
247
- -- don't call splatQ if Q.null
258
+ -- don't call if Q.null!
248
259
next = let (t, q) = fromJust $ seqDequeue stTrans
249
260
in (t, st { stTrans = q })
250
261
0 commit comments