@@ -21,110 +21,94 @@ import Control.Distributed.Process.Extras.Time
21
21
( TimeInterval
22
22
, seconds
23
23
)
24
+ import Control.Distributed.Process.ManagedProcess
25
+ ( processState
26
+ , setProcessState
27
+ , runAfter
28
+ )
29
+ import Control.Distributed.Process.FSM.Internal.Types
30
+ import Control.Distributed.Process.FSM.Internal.Process
31
+ ( start
32
+ )
24
33
import Control.Distributed.Process.Serializable (Serializable )
25
34
import Control.Monad (void )
26
- import Control.Monad.Fix (MonadFix )
27
- import Control.Monad.IO.Class (MonadIO )
28
- import qualified Control.Monad.State.Strict as ST
29
- ( MonadState
30
- , StateT
31
- , get
32
- , lift
33
- , runStateT
34
- )
35
35
import Data.Binary (Binary )
36
36
import Data.Typeable (Typeable )
37
37
import GHC.Generics
38
38
39
- data State s d m = State
40
-
41
- newtype FSM s d m o = FSM {
42
- unFSM :: ST. StateT (State s d m ) Process o
43
- }
44
- deriving ( Functor
45
- , Monad
46
- , ST.MonadState (State s d m)
47
- , MonadIO
48
- , MonadFix
49
- , Typeable
50
- , Applicative
51
- )
52
-
53
- data Action = Consume | Produce | Skip
54
- data Transition s m = Remain | PutBack m | Change s
55
- data Event m = Event
56
-
57
- data Step s d where
58
- Start :: s -> d -> Step s d
59
- Await :: (Serializable m ) => Event m -> Step s d -> Step s d
60
- Always :: FSM s d m (Transition s d ) -> Step s d
61
- Perhaps :: (Eq s ) => s -> FSM s d m (Transition s d ) -> Step s d
62
- Matching :: (m -> Bool ) -> FSM s d m (Transition s d ) -> Step s d
63
- Sequence :: Step s d -> Step s d -> Step s d
64
- Alternate :: Step s d -> Step s d -> Step s d
65
- Reply :: (Serializable r ) => FSM s f m r -> Step s d
66
-
67
39
type Pipeline = forall s d . Step s d
68
40
69
41
initState :: forall s d . s -> d -> Step s d
70
- initState = Start
71
-
72
- -- endState :: Action -> State
73
- -- endState = undefined
42
+ initState = Yield
74
43
75
- enter :: forall s d m . s -> FSM s d m (Transition s d )
76
- enter = undefined
77
-
78
- stopWith :: ExitReason -> Action
79
- stopWith = undefined
44
+ enter :: forall s d . s -> FSM s d (Transition s d )
45
+ enter = return . Enter
80
46
81
47
event :: (Serializable m ) => Event m
82
- event = Event
83
-
84
- currentState :: forall s d m . FSM s d m s
85
- currentState = undefined
48
+ event = Wait
86
49
87
- reply :: forall s d m r . (Serializable r ) => FSM s d m r -> Step s d
50
+ reply :: forall s d r . (Serializable r ) => FSM s d r -> Step s d
88
51
reply = Reply
89
52
90
- timeout :: Serializable a => TimeInterval -> a -> FSM s d m (Transition s d )
91
- timeout = undefined
53
+ timeout :: Serializable m => TimeInterval -> m -> FSM s d (Transition s d )
54
+ timeout t m = return $ Eval $ runAfter t m
55
+
56
+ stop :: ExitReason -> FSM s d (Transition s d )
57
+ stop = return . Stop
92
58
93
- set :: forall s d m . (d -> d ) -> FSM s d m ()
94
- set = undefined
59
+ set :: forall s d . (d -> d ) -> FSM s d ()
60
+ set f = addTransition $ Eval $ do
61
+ processState >>= \ s -> setProcessState $ s { fsmData = (f $ fsmData s) }
95
62
96
- put :: forall s d m . d -> FSM s d m ()
97
- put = undefined
63
+ put :: forall s d . d -> FSM s d ()
64
+ put d = addTransition $ Eval $ do
65
+ processState >>= \ s -> setProcessState $ s { fsmData = d }
98
66
99
67
(.|) :: Step s d -> Step s d -> Step s d
100
68
(.|) = Alternate
101
69
infixr 9 .|
102
70
71
+ pick :: Step s d -> Step s d -> Step s d
72
+ pick = Alternate
73
+
103
74
(|>) :: Step s d -> Step s d -> Step s d
104
75
(|>) = Sequence
105
76
infixr 9 |>
106
77
78
+ join :: Step s d -> Step s d -> Step s d
79
+ join = Sequence
80
+
107
81
(<|) :: Step s d -> Step s d -> Step s d
108
- (<|) = undefined
109
- infixr 9 <|
82
+ (<|) = flip Sequence
83
+ -- infixl 9 <|
84
+
85
+ reverseJoin :: Step s d -> Step s d -> Step s d
86
+ reverseJoin = flip Sequence
110
87
111
88
(~>) :: forall s d m . (Serializable m ) => Event m -> Step s d -> Step s d
112
89
(~>) = Await
113
90
infixr 9 ~>
114
91
115
- (~@) :: forall s d m . (Eq s ) => s -> FSM s d m (Transition s d ) -> Step s d
92
+ await :: forall s d m . (Serializable m ) => Event m -> Step s d -> Step s d
93
+ await = Await
94
+
95
+ (~@) :: forall s d . (Eq s ) => s -> FSM s d (Transition s d ) -> Step s d
116
96
(~@) = Perhaps
117
97
infixr 9 ~@
118
98
119
- allState :: forall s d m . FSM s d m (Transition s d ) -> Step s d
99
+ atState :: forall s d . (Eq s ) => s -> FSM s d (Transition s d ) -> Step s d
100
+ atState = Perhaps
101
+
102
+ allState :: forall s d m . (Serializable m ) => (m -> FSM s d (Transition s d )) -> Step s d
120
103
allState = Always
121
104
122
- (~?) :: forall s d m . (m -> Bool ) -> FSM s d m (Transition s d ) -> Step s d
105
+ (~?) :: forall s d m . (Serializable m ) => ( m -> Bool ) -> ( m -> FSM s d (Transition s d ) ) -> Step s d
123
106
(~?) = Matching
124
107
125
- start :: Pipeline -> Process ()
126
- start = const $ return ()
108
+ matching :: forall s d m . ( Serializable m ) => ( m -> Bool ) -> ( m -> FSM s d ( Transition s d )) -> Step s d
109
+ matching = Matching
127
110
111
+ {-
128
112
data StateName = On | Off deriving (Eq, Show, Typeable, Generic)
129
113
instance Binary StateName where
130
114
@@ -144,10 +128,14 @@ startState = initState Off initCount
144
128
demo :: Step StateName StateData
145
129
demo = startState
146
130
|> (event :: Event ButtonPush)
147
- ~> ( (On ~@ (set (+ 1 ) >> enter Off ))
131
+ ~> ( (On ~@ (set (+1) >> enter Off)) -- on => off => on is possible with |> here...
148
132
.| (Off ~@ (set (+1) >> enter On))
149
- ) <| (reply currentState)
133
+ ) |> (reply currentState)
150
134
.| (event :: Event Stop)
151
- ~> ((== ExitShutdown ) ~? (timeout (seconds 3 ) Reset ))
152
- .| (event :: Event Reset ) ~> (allState $ put initCount >> enter Off )
153
- -- .| endState $ stopWith ExitNormal
135
+ ~> ( ((== ExitShutdown) ~? (\_ -> timeout (seconds 3) Reset))
136
+ .| ((const True) ~? (\r -> (liftIO $ putStrLn "stopping...") >> stop r))
137
+ )
138
+ .| (event :: Event Reset)
139
+ ~> (allState $ \Reset -> put initCount >> enter Off)
140
+
141
+ -}
0 commit comments