Safe Haskell | Safe-Inferred |
---|---|
Language | GHC2021 |
This is the main module of the whole library. It defines the central
StateMachineT
type, which allows us to create composable state machines.
Synopsis
- data StateMachineT m input output where
- Basic :: forall m vertex (topology :: Topology vertex) input output. (Demote vertex ~ vertex, SingKind vertex, SingI topology, Eq vertex, Show vertex, RenderableVertices vertex) => BaseMachineT m topology input output -> StateMachineT m input output
- Sequential :: StateMachineT m a b -> StateMachineT m b c -> StateMachineT m a c
- Parallel :: StateMachineT m a b -> StateMachineT m c d -> StateMachineT m (a, c) (b, d)
- Alternative :: StateMachineT m a b -> StateMachineT m c d -> StateMachineT m (Either a c) (Either b d)
- Feedback :: (Foldable n, Monoid (n a), Monoid (n b)) => StateMachineT m a (n b) -> StateMachineT m b (n a) -> StateMachineT m a (n b)
- Kleisli :: (Foldable n, Monoid (n c)) => StateMachineT m a (n b) -> StateMachineT m b (n c) -> StateMachineT m a (n c)
- type StateMachine a b = forall m. Monad m => StateMachineT m a b
- hoist :: (forall x. m x -> n x) -> StateMachineT m a b -> StateMachineT n a b
- statelessT :: Applicative m => (a -> m b) -> StateMachineT m a b
- stateless :: Applicative m => (a -> b) -> StateMachineT m a b
- unrestrictedMachine :: (Demote vertex ~ vertex, SingKind vertex, SingI (AllowAllTopology @vertex), Eq vertex, Show vertex, RenderableVertices vertex) => (forall initialVertex. state initialVertex -> a -> ActionResult m (AllowAllTopology @vertex) state initialVertex b) -> InitialState (state :: vertex -> Type) -> StateMachineT m a b
- run :: Monad m => StateMachineT m a b -> a -> m (b, StateMachineT m a b)
- runMultiple :: (Monad m, Foldable f, Monoid b) => StateMachineT m a b -> f a -> m (b, StateMachineT m a b)
Documentation
data StateMachineT m input output where Source #
A StateMachineT
is an effectful Mealy machine
with inputs of type input
and outputs of type output
Effects are described by the context m
in which the action of the machine
is executed
StateMachineT
is a tree, where leaves are BaseMachineT
and other nodes
describe how to combine the subtrees to obtain more complex machines.
Please refer to https://github.com/tweag/crem/blob/main/docs/how-to-create-a-machine.md for a more complete discussion on the various constructors.
Basic :: forall m vertex (topology :: Topology vertex) input output. (Demote vertex ~ vertex, SingKind vertex, SingI topology, Eq vertex, Show vertex, RenderableVertices vertex) => BaseMachineT m topology input output -> StateMachineT m input output |
|
Sequential :: StateMachineT m a b -> StateMachineT m b c -> StateMachineT m a c |
|
Parallel :: StateMachineT m a b -> StateMachineT m c d -> StateMachineT m (a, c) (b, d) |
|
Alternative :: StateMachineT m a b -> StateMachineT m c d -> StateMachineT m (Either a c) (Either b d) |
|
Feedback :: (Foldable n, Monoid (n a), Monoid (n b)) => StateMachineT m a (n b) -> StateMachineT m b (n a) -> StateMachineT m a (n b) |
|
Kleisli :: (Foldable n, Monoid (n c)) => StateMachineT m a (n b) -> StateMachineT m b (n c) -> StateMachineT m a (n c) |
|
Instances
Monad m => Category (StateMachineT m :: Type -> Type -> Type) Source # | |
Defined in Crem.StateMachine id :: forall (a :: k). StateMachineT m a a # (.) :: forall (b :: k) (c :: k) (a :: k). StateMachineT m b c -> StateMachineT m a b -> StateMachineT m a c # | |
Monad m => Arrow (StateMachineT m) Source # | |
Defined in Crem.StateMachine arr :: (b -> c) -> StateMachineT m b c # first :: StateMachineT m b c -> StateMachineT m (b, d) (c, d) # second :: StateMachineT m b c -> StateMachineT m (d, b) (d, c) # (***) :: StateMachineT m b c -> StateMachineT m b' c' -> StateMachineT m (b, b') (c, c') # (&&&) :: StateMachineT m b c -> StateMachineT m b c' -> StateMachineT m b (c, c') # | |
Monad m => ArrowChoice (StateMachineT m) Source # | |
Defined in Crem.StateMachine left :: StateMachineT m b c -> StateMachineT m (Either b d) (Either c d) # right :: StateMachineT m b c -> StateMachineT m (Either d b) (Either d c) # (+++) :: StateMachineT m b c -> StateMachineT m b' c' -> StateMachineT m (Either b b') (Either c c') # (|||) :: StateMachineT m b d -> StateMachineT m c d -> StateMachineT m (Either b c) d # | |
Monad m => Choice (StateMachineT m) Source # | An instance of |
Defined in Crem.StateMachine left' :: StateMachineT m a b -> StateMachineT m (Either a c) (Either b c) # right' :: StateMachineT m a b -> StateMachineT m (Either c a) (Either c b) # | |
Monad m => Strong (StateMachineT m) Source # | |
Defined in Crem.StateMachine first' :: StateMachineT m a b -> StateMachineT m (a, c) (b, c) # second' :: StateMachineT m a b -> StateMachineT m (c, a) (c, b) # | |
Applicative m => Profunctor (StateMachineT m) Source # | |
Defined in Crem.StateMachine dimap :: (a -> b) -> (c -> d) -> StateMachineT m b c -> StateMachineT m a d # lmap :: (a -> b) -> StateMachineT m b c -> StateMachineT m a c # rmap :: (b -> c) -> StateMachineT m a b -> StateMachineT m a c # (#.) :: forall a b c q. Coercible c b => q b c -> StateMachineT m a b -> StateMachineT m a c # (.#) :: forall a b c q. Coercible b a => StateMachineT m b c -> q a b -> StateMachineT m a c # |
type StateMachine a b = forall m. Monad m => StateMachineT m a b Source #
A StateMachine
is an effectful machine for every possible monad m
.
Needing to work for every monad, in fact it can not perform any kind of
effect and needs to be pure in nature.
Hoist
hoist :: (forall x. m x -> n x) -> StateMachineT m a b -> StateMachineT n a b Source #
Allows to change the context m
where the machine operates to another
context n
, provided we have a natural transformation
from m
to n
statelessT :: Applicative m => (a -> m b) -> StateMachineT m a b Source #
a state machine which does not rely on state
stateless :: Applicative m => (a -> b) -> StateMachineT m a b Source #
a state machine which does not rely on state and does not perform side effects
unrestrictedMachine :: (Demote vertex ~ vertex, SingKind vertex, SingI (AllowAllTopology @vertex), Eq vertex, Show vertex, RenderableVertices vertex) => (forall initialVertex. state initialVertex -> a -> ActionResult m (AllowAllTopology @vertex) state initialVertex b) -> InitialState (state :: vertex -> Type) -> StateMachineT m a b Source #
a machine modelled with explicit state, where every transition is allowed
Category
Profunctor
Strong
Choice
Arrow
ArrowChoice
Run a state machine
run :: Monad m => StateMachineT m a b -> a -> m (b, StateMachineT m a b) Source #
Given an input
, run the machine to get an output and a new version of
the machine
runMultiple :: (Monad m, Foldable f, Monoid b) => StateMachineT m a b -> f a -> m (b, StateMachineT m a b) Source #
process multiple inputs in one go, accumulating the results in a monoid