| Safe Haskell | Safe-Inferred |
|---|---|
| Language | GHC2021 |
Crem.BaseMachine
Description
A BaseMachine is a Mealy machine constrained by a provided Topology of
allowed transitions.
Synopsis
- data BaseMachineT m (topology :: Topology vertex) (input :: Type) (output :: Type) = forall state.BaseMachineT {
- initialState :: InitialState state
- action :: forall initialVertex. state initialVertex -> input -> ActionResult m topology state initialVertex output
- type BaseMachine (topology :: Topology vertex) (input :: Type) (output :: Type) = forall m. Monad m => BaseMachineT m topology input output
- baseHoist :: (forall x. m x -> n x) -> BaseMachineT m topology a b -> BaseMachineT n topology a b
- data InitialState (state :: vertex -> Type) where
- InitialState :: state vertex -> InitialState state
- data ActionResult m (topology :: Topology vertex) (state :: vertex -> Type) (initialVertex :: vertex) (output :: Type) where
- ActionResult :: AllowedTransition topology initialVertex finalVertex => m (output, state finalVertex) -> ActionResult m topology state initialVertex output
- hoistResult :: (forall x. m x -> n x) -> ActionResult m topology state initialVertex output -> ActionResult n topology state initialVertex output
- pureResult :: (Applicative m, AllowedTransition topology initialVertex finalVertex) => output -> state finalVertex -> ActionResult m topology state initialVertex output
- sequence :: Functor f => ActionResult Identity topology state initialVertex (f output) -> ActionResult f topology state initialVertex output
- maybeM :: Applicative m => BaseMachineT m topology a b -> BaseMachineT m topology (Maybe a) (Maybe b)
- eitherM :: Applicative m => BaseMachineT m topology a b -> BaseMachineT m topology (Either e a) (Either e b)
- statelessBaseT :: Applicative m => (a -> m b) -> BaseMachineT m (TrivialTopology @()) a b
- statelessBase :: (a -> b) -> BaseMachine (TrivialTopology @()) a b
- identity :: BaseMachine (TrivialTopology @()) a a
- unrestrictedBaseMachineT :: (forall initialVertex. state initialVertex -> a -> ActionResult m (AllowAllTopology @vertex) state initialVertex b) -> InitialState (state :: vertex -> Type) -> BaseMachineT m (AllowAllTopology @vertex) a b
- runBaseMachineT :: Functor m => BaseMachineT m topology input output -> input -> m (output, BaseMachineT m topology input output)
Specifying state machines
data BaseMachineT m (topology :: Topology vertex) (input :: Type) (output :: Type) Source #
A BaseMachineT m topology input output describes a state machine with
allowed transitions constrained by a given topology.
A state machine is composed by an initialState and an action, which
defines the output and the new state given the current state and an
input.
The m parameter describes the context where the action of the machine is
executed
Constructors
| forall state. BaseMachineT | |
Fields
| |
Instances
| Applicative m => Choice (BaseMachineT m topology) Source # | |
Defined in Crem.BaseMachine Methods left' :: BaseMachineT m topology a b -> BaseMachineT m topology (Either a c) (Either b c) # right' :: BaseMachineT m topology a b -> BaseMachineT m topology (Either c a) (Either c b) # | |
| Functor m => Strong (BaseMachineT m topology) Source # | |
Defined in Crem.BaseMachine Methods first' :: BaseMachineT m topology a b -> BaseMachineT m topology (a, c) (b, c) # second' :: BaseMachineT m topology a b -> BaseMachineT m topology (c, a) (c, b) # | |
| Functor m => Profunctor (BaseMachineT m topology) Source # | |
Defined in Crem.BaseMachine Methods dimap :: (a -> b) -> (c -> d) -> BaseMachineT m topology b c -> BaseMachineT m topology a d # lmap :: (a -> b) -> BaseMachineT m topology b c -> BaseMachineT m topology a c # rmap :: (b -> c) -> BaseMachineT m topology a b -> BaseMachineT m topology a c # (#.) :: forall a b c q. Coercible c b => q b c -> BaseMachineT m topology a b -> BaseMachineT m topology a c # (.#) :: forall a b c q. Coercible b a => BaseMachineT m topology b c -> q a b -> BaseMachineT m topology a c # | |
type BaseMachine (topology :: Topology vertex) (input :: Type) (output :: Type) = forall m. Monad m => BaseMachineT m topology input output Source #
A BaseMachine 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
baseHoist :: (forall x. m x -> n x) -> BaseMachineT m topology a b -> BaseMachineT n topology 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
data InitialState (state :: vertex -> Type) where Source #
A value of type InitialState state describes the initial state of a
state machine, describing the initial vertex in the topology and the
actual initial data of type state vertex
Constructors
| InitialState :: state vertex -> InitialState state |
data ActionResult m (topology :: Topology vertex) (state :: vertex -> Type) (initialVertex :: vertex) (output :: Type) where Source #
The result of an action of the state machine.
An ActionResult m topology state initialVertex output contains an output
and a state finalVertex, where the transition from initialVertex to
finalVertex is allowed by the machine topology
Constructors
| ActionResult :: AllowedTransition topology initialVertex finalVertex => m (output, state finalVertex) -> ActionResult m topology state initialVertex output |
Instances
| Functor m => Functor (ActionResult m topology state initialVertex) Source # | |
Defined in Crem.BaseMachine Methods fmap :: (a -> b) -> ActionResult m topology state initialVertex a -> ActionResult m topology state initialVertex b # (<$) :: a -> ActionResult m topology state initialVertex b -> ActionResult m topology state initialVertex a # | |
hoistResult :: (forall x. m x -> n x) -> ActionResult m topology state initialVertex output -> ActionResult n topology state initialVertex output Source #
Allows to change the computational context of an ActionResult from m
to n, given we have a natural transformation
from m to n.
pureResult :: (Applicative m, AllowedTransition topology initialVertex finalVertex) => output -> state finalVertex -> ActionResult m topology state initialVertex output Source #
Create an ActionResult without performing any side effect in the m
context
sequence :: Functor f => ActionResult Identity topology state initialVertex (f output) -> ActionResult f topology state initialVertex output Source #
This is fairly similar to sequenceA from Traversable and in fact
it does the same job, with the slight difference that sequenceA would
return f (ActionResult Identity topology state initialVertex output)
Lift machines
maybeM :: Applicative m => BaseMachineT m topology a b -> BaseMachineT m topology (Maybe a) (Maybe b) Source #
eitherM :: Applicative m => BaseMachineT m topology a b -> BaseMachineT m topology (Either e a) (Either e b) Source #
Stateless machines
statelessBaseT :: Applicative m => (a -> m b) -> BaseMachineT m (TrivialTopology @()) a b Source #
statelessBaseT transforms its input to its output and never changes its
state
statelessBase :: (a -> b) -> BaseMachine (TrivialTopology @()) a b Source #
statelessBase transforms its input to its output and never changes its
state, without performing any side effect
Identity machine
identity :: BaseMachine (TrivialTopology @()) a a Source #
The identity machine simply outputs its input and never changes its
state.
Unrestricted machines
unrestrictedBaseMachineT :: (forall initialVertex. state initialVertex -> a -> ActionResult m (AllowAllTopology @vertex) state initialVertex b) -> InitialState (state :: vertex -> Type) -> BaseMachineT m (AllowAllTopology @vertex) a b Source #
a machine modelled with explicit state, where every transition is allowed
Run a machine
runBaseMachineT :: Functor m => BaseMachineT m topology input output -> input -> m (output, BaseMachineT m topology input output) Source #
Given an input, run the machine to get an output and a new version of
the machine