@@ -35,11 +35,15 @@ import Control.Distributed.Process.ManagedProcess
3535 , setProcessState
3636 , processState
3737 )
38- import qualified Control.Distributed.Process.ManagedProcess.Internal.Types as MP (lift , liftIO )
39- import Control.Distributed.Process.ManagedProcess.Server.Priority
40- ( push
41- , act
38+ import qualified Control.Distributed.Process.ManagedProcess.Internal.GenProcess as Gen (enqueue , push )
39+ import Control.Distributed.Process.ManagedProcess.Internal.Types
40+ ( Priority (.. )
4241 )
42+ import qualified Control.Distributed.Process.ManagedProcess.Internal.Types as MP
43+ ( lift
44+ , liftIO
45+ )
46+ import Control.Distributed.Process.ManagedProcess.Server.Priority (act )
4347import Control.Distributed.Process.Serializable (Serializable )
4448import Control.Monad.Fix (MonadFix )
4549import Control.Monad.IO.Class (MonadIO )
@@ -65,13 +69,14 @@ import Data.Typeable (Typeable, typeOf)
6569import Data.Tuple (swap , uncurry )
6670-- import GHC.Generics
6771
68- data State s d = State { stName :: s
72+ data State s d = (Show s , Eq s ) =>
73+ State { stName :: s
6974 , stData :: d
7075 , stProg :: Step s d -- original program
71- , stInstr :: Step s d -- current step in the program
7276 , stInput :: Maybe P. Message
7377 , stReply :: (P. Message -> Process () )
7478 , stTrans :: Seq (Transition s d )
79+ , stQueue :: Seq P. Message
7580 }
7681
7782instance forall s d . (Show s ) => Show (State s d ) where
@@ -80,24 +85,42 @@ instance forall s d . (Show s) => Show (State s d) where
8085
8186data Transition s d = Remain
8287 | PutBack
88+ | Push P. Message
89+ | Enqueue P. Message
90+ | Postpone
8391 | Enter s
8492 | Stop ExitReason
8593 | Eval (GenProcess (State s d ) () )
8694
8795instance forall s d . (Show s ) => Show (Transition s d ) where
8896 show Remain = " Remain"
8997 show PutBack = " PutBack"
98+ show Postpone = " Postpone"
99+ show (Push m) = " Push " ++ (show m)
100+ show (Enqueue m) = " Enqueue " ++ (show m)
90101 show (Enter s) = " Enter " ++ (show s)
91102 show (Stop er) = " Stop " ++ (show er)
92103 show (Eval _) = " Eval"
93104
94105data Event m where
95- Wait :: (Serializable m ) => Event m
96- Event :: (Serializable m ) => m -> Event m
106+ Wait :: (Serializable m ) => Event m
107+ WaitP :: (Serializable m ) => Priority () -> Event m
108+ Event :: (Serializable m ) => m -> Event m
109+
110+ resolveEvent :: forall s d m . (Serializable m )
111+ => Event m
112+ -> P. Message
113+ -> State s d
114+ -> m
115+ -> Process (Int , P. Message )
116+ resolveEvent ev m _ _
117+ | WaitP p <- ev = return (getPrio p, m)
118+ | otherwise = return (0 , m)
97119
98120instance forall m . (Typeable m ) => Show (Event m ) where
99- show ev@ Wait = show $ " Wait::" ++ (show $ typeOf ev)
100- show ev = show $ typeOf ev
121+ show ev@ Wait = show $ " Wait::" ++ (show $ typeOf ev)
122+ show ev@ (WaitP _) = show $ " WaitP::" ++ (show $ typeOf ev)
123+ show ev = show $ typeOf ev
101124
102125data Step s d where
103126 Init :: Step s d -> Step s d -> Step s d
@@ -171,9 +194,13 @@ seqEnqueue s a = a <| s
171194seqPush :: Seq a -> a -> Seq a
172195seqPush s a = s |> a
173196
197+ {-# INLINE seqPop #-}
198+ seqPop :: Seq a -> Maybe (a , Seq a )
199+ seqPop s = maybe Nothing (\ (s' :> a) -> Just (a, s')) $ getR s
200+
174201{-# INLINE seqDequeue #-}
175202seqDequeue :: Seq a -> Maybe (a , Seq a )
176- seqDequeue s = maybe Nothing ( \ (s' :> a) -> Just (a, s')) $ getR s
203+ seqDequeue = seqPop
177204
178205{-# INLINE peek #-}
179206peek :: Seq a -> Maybe a
@@ -198,7 +225,7 @@ apply st msg step
198225 P. liftIO $ putStrLn " Init _ _"
199226 st' <- apply st msg is
200227 case st' of
201- Just s -> apply (s { stProg = ns, stInstr = ns }) msg ns
228+ Just s -> apply (s { stProg = ns }) msg ns
202229 Nothing -> die $ ExitOther $ baseErr ++ " :InitFailed"
203230 | Yield sn sd <- step = do
204231 P. liftIO $ putStrLn " Yield s d"
@@ -255,28 +282,38 @@ applyTransitions st@State{..} evals
255282 MP. liftIO $ putStrLn $ " ProcessState: " ++ (show stName)
256283 mapM_ id evals
257284 | (tr, st2) <- next
258- , Enter s <- tr = let st' = st2 { stName = s }
259- in do P. liftIO $ putStrLn $ " NEWSTATE: " ++ (show st')
260- applyTransitions st' evals
285+ , PutBack <- tr = applyTransitions st2 ((Gen. enqueue $ fromJust stInput) : evals)
286+ | isJust stInput
287+ , input <- fromJust stInput
288+ , (tr, st2) <- next
289+ , Postpone <- tr = applyTransitions (st2 { stQueue = seqEnqueue stQueue input }) evals
261290 | (tr, st2) <- next
262- , PutBack <- tr = applyTransitions st2 ((push $ fromJust stInput) : evals)
263- {- let act' = setProcessState $ fsmSt { fsmName = stName, fsmData = stData }
264- push stInput -}
291+ , Enqueue m <- tr = applyTransitions st2 ((Gen. enqueue m) : evals)
292+ | (tr, st2) <- next
293+ , Push m <- tr = applyTransitions st2 (( Gen. push m) : evals)
265294 | (tr, st2) <- next
266295 , Eval proc <- tr = applyTransitions st2 (proc : evals)
267296 | (tr, st2) <- next
268297 , Remain <- tr = applyTransitions st2 evals
269298 | (tr, _) <- next
270299 , Stop er <- tr = stopWith st er
271- | otherwise = error $ baseErr ++ " .Internal.Process.applyTransitions:InvalidState"
300+ | (tr, st2) <- next
301+ , Enter s <- tr =
302+ if s == stName then applyTransitions st2 evals
303+ else do let st' = st2 { stName = s }
304+ let evals' = if Q. null stQueue then evals
305+ else (mapM_ Gen. push stQueue) : evals
306+ applyTransitions st' evals'
307+ | otherwise = error $ baseErr ++ " .Internal.Process.applyTransitions:InvalidTransition"
272308 where
273309 -- don't call if Q.null!
274- next = let (t, q) = fromJust $ seqDequeue stTrans
310+ next = let (t, q) = fromJust $ seqPop stTrans
275311 in (t, st { stTrans = q })
276312
277313baseErr :: String
278314baseErr = " Control.Distributed.Process.FSM"
279315
280316decodeToEvent :: Serializable m => Event m -> P. Message -> Maybe (Event m )
281317decodeToEvent Wait msg = unwrapMessage msg >>= fmap Event
318+ decodeToEvent (WaitP _) msg = unwrapMessage msg >>= fmap Event
282319decodeToEvent ev@ (Event _) _ = Just ev -- it's a bit odd that we'd end up here....
0 commit comments