| Copyright | (c) Tim Watson 2017 |
|---|---|
| License | BSD3 (see the file LICENSE) |
| Maintainer | Tim Watson <watson.timothy@gmail.com> |
| Stability | experimental |
| Portability | non-portable (requires concurrency) |
| Safe Haskell | None |
| Language | Haskell98 |
Control.Distributed.Process.FSM.Internal.Types
Description
Types and common functionality.
- apply :: Show s => State s d -> Message -> Step s d -> Process (Maybe (State s d))
- applyTransitions :: forall s d. Show s => State s d -> [GenProcess (State s d) ()] -> Action (State s d)
- data State s d = (Show s, Eq s) => State {}
- data Transition s d
- data Event m where
- Wait :: Serializable m => Event m
- WaitP :: Serializable m => Priority () -> Event m
- Event :: Serializable m => m -> Event m
- data Stopping = Stopping {
- reason :: ExitReason
- errored :: Bool
- resolveEvent :: forall s d m. Serializable m => Event m -> Message -> State s d -> m -> Process (Int, Message)
- data Step s d where
- Init :: Step s d -> Step s d -> Step s d
- Yield :: s -> d -> Step s d
- SafeWait :: Serializable m => Event m -> Step s d -> Step s d
- Await :: Serializable m => Event m -> Step s d -> Step s d
- Always :: Serializable m => (m -> FSM s d (Transition s d)) -> Step s d
- Perhaps :: Eq s => s -> FSM s d (Transition s d) -> Step s d
- Matching :: Serializable m => (m -> Bool) -> (m -> FSM s d (Transition s d)) -> Step s d
- Sequence :: Step s d -> Step s d -> Step s d
- Alternate :: Step s d -> Step s d -> Step s d
- Reply :: Serializable r => FSM s d r -> Step s d
- newtype FSM s d o = FSM {}
- runFSM :: State s d -> FSM s d o -> Process (o, State s d)
- lift :: Process a -> FSM s d a
- liftIO :: IO a -> FSM s d a
- currentState :: FSM s d s
- currentInput :: forall s d m. Serializable m => FSM s d (Maybe m)
- currentMessage :: forall s d. FSM s d Message
- stateData :: FSM s d d
- addTransition :: Transition s d -> FSM s d ()
- baseErr :: String
- decodeToEvent :: Serializable m => Event m -> Message -> Maybe (Event m)
Documentation
applyTransitions :: forall s d. Show s => State s d -> [GenProcess (State s d) ()] -> Action (State s d) Source #
data Transition s d Source #
Represents a transition from one world state to another. Transitions can be used to alter the process state, state data, to modify and/or interact with the process mailbox, and to postpone processing of messages until state changes take place.
The fundmental state transactions are Remain, Enter newState, and
Stop exitReason.
Constructors
| Remain | |
| PutBack | |
| Push Message | |
| Enqueue Message | |
| Postpone | |
| Enter s | |
| Stop ExitReason | |
| Eval (GenProcess (State s d) ()) |
Instances
| Show s => Show (Transition s d) Source # | |
Represents an event arriving, parameterised by the type m of the event.
Used in a combinatorial style to wire FSM steps, actions and transitions to
specific types of input event.
Constructors
| Wait :: Serializable m => Event m | |
| WaitP :: Serializable m => Priority () -> Event m | |
| Event :: Serializable m => m -> Event m |
Event type wrapper passed to the FSM whenever we're shutting down.
Constructors
| Stopping | |
Fields
| |
resolveEvent :: forall s d m. Serializable m => Event m -> Message -> State s d -> m -> Process (Int, Message) Source #
Resolve an event into a priority setting, for insertion into a priority queue.
Represents a step in a FSM definition
Constructors
| Init :: Step s d -> Step s d -> Step s d | |
| Yield :: s -> d -> Step s d | |
| SafeWait :: Serializable m => Event m -> Step s d -> Step s d | |
| Await :: Serializable m => Event m -> Step s d -> Step s d | |
| Always :: Serializable m => (m -> FSM s d (Transition s d)) -> Step s d | |
| Perhaps :: Eq s => s -> FSM s d (Transition s d) -> Step s d | |
| Matching :: Serializable m => (m -> Bool) -> (m -> FSM s d (Transition s d)) -> Step s d | |
| Sequence :: Step s d -> Step s d -> Step s d | |
| Alternate :: Step s d -> Step s d -> Step s d | |
| Reply :: Serializable r => FSM s d r -> Step s d |
State monad transformer.
liftIO :: IO a -> FSM s d a Source #
Lift an IO action directly into FSM, liftIO = lift . Process.LiftIO.
currentState :: FSM s d s Source #
Fetch the state for the current pass.
currentInput :: forall s d m. Serializable m => FSM s d (Maybe m) Source #
Retrieve the currentMessage and attempt to decode it to type m
currentMessage :: forall s d. FSM s d Message Source #
Fetch the message that initiated the current pass.
addTransition :: Transition s d -> FSM s d () Source #
Add a Transition to be evaluated once the current pass completes.
decodeToEvent :: Serializable m => Event m -> Message -> Maybe (Event m) Source #
Given an Event for any Serializable type m and a raw message, decode
the message and map it to either Event m if the types are aligned, otherwise
Nothing.