Safe Haskell | None |
---|---|
Language | GHC2021 |
TypedFsm.Driver.Op
Description
Running FSM
The core function is runOp
, and the other functions are to make it work properly.
Synopsis
- type Op ps state (m :: Type -> Type) a (o :: ps) (i :: ps) = Operate (StateT state m) (At a o) i
- type SomeOp ps state (m :: Type -> Type) a = SomeOperate ps (StateT state m) a
- newtype GenMsg ps state event (from :: ps) = GenMsg (state -> event -> Maybe (SomeMsg ps from))
- type State2GenMsg ps state event = DMap (Sing :: ps -> Type) (GenMsg ps state event)
- sOrdToGCompare :: forall n (a :: n) (b :: n). SOrd n => Sing a -> Sing b -> GOrdering a b
- newtype NotFoundGenMsg ps = NotFoundGenMsg (SomeSing ps)
- runOp :: forall ps event state (m :: Type -> Type) a (input :: ps) (output :: ps). (GCompare (Sing :: ps -> Type), Monad m) => State2GenMsg ps state event -> [event] -> Sing input -> Operate (StateT state m) (At a output) input -> StateT state m (Result ps (NotFoundGenMsg ps) (StateT state m) a)
Documentation
type Op ps state (m :: Type -> Type) a (o :: ps) (i :: ps) = Operate (StateT state m) (At a o) i Source #
Op
adds new assumptions based on Operate
: assume that the internal monad contains at least a state monad.
type Op ps state m a o i = Operate (StateT state m) (At a (o :: ps)) (i :: ps)
Op
contains two states, ps
and state
.
ps
represents the state of the state machine
state
represents the internal state.
The external event needs to be converted to Msg.
It is essentially a function `event -> Msg`, but this function is affected by both ps
and state
.
newtype NotFoundGenMsg ps Source #
Constructors
NotFoundGenMsg (SomeSing ps) |
runOp :: forall ps event state (m :: Type -> Type) a (input :: ps) (output :: ps). (GCompare (Sing :: ps -> Type), Monad m) => State2GenMsg ps state event -> [event] -> Sing input -> Operate (StateT state m) (At a output) input -> StateT state m (Result ps (NotFoundGenMsg ps) (StateT state m) a) Source #