Safe Haskell | None |
---|---|
Language | Haskell2010 |
Motor is an experimental Haskell library for building finite-state machines with type-safe transitions and effects. It draws inspiration from the Idris ST library.
Synopsis
- class IxMonad m => MonadFSM (m :: Row * -> Row * -> * -> *) where
- data Name (n :: Symbol) where
- Name :: KnownSymbol n => Name n
- data Action
- data ActionMapping = (:=) Symbol Action
- type family FromActions (as :: [ActionMapping]) (rs :: Row *) (c :: Constraint) :: (Row *, Constraint) where ...
- type NoActions m (r :: Row *) a = m r r a
- type Actions m as (i :: Row *) a = forall o c. (FromActions as i NoConstraint ~ '(o, c), c) => m i o a
- type OnlyActions m as a = Actions m as Empty a
- type Get m (r :: Row *) n = m r r (r .! n)
- type (!-->) i o = To i o
- type (!+) (n :: Symbol) s = n := Add s
- type (!-) (n :: Symbol) s = n := Delete s
- data FSM m (i :: Row *) (o :: Row *) a
- runFSM :: Monad m => FSM m Empty Empty a -> m a
- (>>>) :: IxMonad m => m i j a -> m j k b -> m i k b
- module Control.Monad.Indexed
Usage
The central finite-state machine abstraction in Motor is the MonadFSM
type class.
MonadFSM
is an indexed monad type class, meaning that it has not one,
but three type parameters:
The MonadFSM
parameter kinds might look a bit scary, but they state
the same:
class IxMonad m => MonadFSM (m :: (Row *) -> (Row *) -> * -> *) where ...
The rows describe how the FSM computation will affect the state of its resources when evaluated. A row is essentially a type-level map, from resource names to state types, and the FSM computation's rows describe the resource states before and after the computation.
An FSM computation newConn
that adds a resource named "connection"
with state Idle
could have the following type:
>>>
:t newConn
newConn :: MonadFSM m => m r (Extend "connection" Idle r) ()
A computation spawnTwoPlayers
that adds two resources could have
this type:
>>>
:t spawnTwoPlayers
spawnTwoPlayers :: :: MonadFSM m => m r (Extend "hero2" Standing (Extend "hero1" Standing r)) ()
Motor uses the extensible records in Data.Row.Records, provided by the row-types library, for row kinds. Have a look at it's documentation to learn more about the type-level operators available for rows.
Indexed Monads
As mentioned above, MonadFSM
is an indexed monad. It uses the
definition from Control.Monad.Indexed, in the indexed
package. This means that you can use ibind
and friends to compose
FSM computations.
c1 >>>= \_ -> c2
You can combine this with the RebindableSyntax
language extension to
get do-syntax for FSM programs:
test :: MonadFSM m => m Empty Empty () test = do c1 c2 r <- c3 c4 r where (>>) a = (>>>=) a . const (>>=) = (>>>=)
See 24 Days of GHC Extensions: Rebindable
Syntax
for some more information on how to use RebindableSyntax
.
State Actions
To make it easier to read and write FSM computation types, there is some syntax sugar available.
State actions allow you two describe state changes of named resources with a single list, as opposed two writing two rows. They also take care of building the correct row types and constraints for Motor, which can be tricky to do by hand.
There are three state Action
s:
Add
adds a new resource.Remain
keeps an existing resource in the same state.To
transitions the state of a resource.Delete
deletes an existing resource.
A mapping between a resource name is written using the :=
type operator,
with a Symbol
on the left, and a state action type on the right. Here are
some examples:
"container" := Add Empty "list" := To Empty NonEmpty "game" := Delete GameEnded
So, the list of mappings from resource names to state actions describe
what happens to each resource. Together with an initial row of
resources r
, and a return value a
, we can declare the type of an
FSM computation using the Actions
type:
MonadFSM m => Actions m '[ n1 := a1, n2 := a2, ... ] r a
A computation that adds two resources could have the following type:
addingTwoThings :: MonadFSM m => Actions m '[ "container" := Add Empty, "game" := Add Started ] r ()
Infix Operators
As an alternative to the Add
, To
, and Delete
types,
Motor offers infix operator aliases. These start with !
to indicate
that they can be effectful.
The !-->
operator is an infix alias for To
:
useStateMachines :: MonadFSM m => Actions m '[ "program" := NotCool !--> Cool ] r ()
The !+
and !-
are infix aliases for mappings from resource names to Add
and Delete
state actions, respectively:
startNewGame :: MonadFSM m => Actions m '[ "game" !+ Started ] r () endGameWhenWon :: MonadFSM m => Actions m '[ "game" !- Won ] r ()
Row Polymorphism
Because of how the row polymorphism implementation works, FSM computations that are polymorphic (in the sense of other resource states) must list all their actions in order. This limitation will hopefully be addressed soon.
doFourThings :: Game m => Actions m '[ "hero1" !+ Standing , "hero2" !+ Standing , "hero1" !- Standing , "hero2" !- Standing ] r () doFourThings = spawn hero1 >>>= _ -> spawn hero2 >>>= _ -> perish hero1 >>>= _ -> perish hero2
Had the r
been replaced by Empty
in the type signature above, it could
have had type NoActions m Empty ()
instead.
If the computation removes all resources that it creates, i.e. that it
could be run as NoActions m Empty ()
, you can use call
to run it
in a row-polymorphic computation without having to list all actions:
doFourThings :: Game m => NoActions m r () doFourThings = call $ spawn hero1 >>>= _ -> spawn hero2 >>>= _ -> perish hero1 >>>= _ -> perish hero2
In a future version, call
might support the rows of the called
computation being subsets of the resulting computation's rows.
Examples
The GitHub repository includes some examples, check that out.
API
MonadFSM Class
class IxMonad m => MonadFSM (m :: Row * -> Row * -> * -> *) where Source #
An indexed monad for finite-state machines, managing the state of named resources.
new :: Name n -> a -> m r (Extend n a r) () Source #
Creates a new resource by name.
get :: HasType n a r => Name n -> m r r a Source #
Returns an existing resource.
delete :: Name n -> m r (r .- n) () Source #
Deletes an existing resource named by its Name
.
enter :: r' ~ ((n .== b) .// r) => Name n -> b -> m r r' () Source #
Replaces the state of an existing resource named by its Name
.
update :: (HasType n a r, Modify n a r ~ r) => Name n -> (a -> a) -> m r r () Source #
Updates the state, using a pure function, of an existing
resource named by its Name
.
call :: m Empty Empty a -> m r r a Source #
Embed another MonadFSM
computation, with empty resource rows,
in this computation.
Instances
Monad m => MonadFSM (FSM m) Source # | |
Defined in Motor.FSM new :: Name n -> a -> FSM m r (Extend n a r) () Source # get :: HasType n a r => Name n -> FSM m r r a Source # delete :: Name n -> FSM m r (r .- n) () Source # enter :: r' ~ ((n .== b) .// r) => Name n -> b -> FSM m r r' () Source # update :: (HasType n a r, Modify n a r ~ r) => Name n -> (a -> a) -> FSM m r r () Source # |
Resource Names
data Name (n :: Symbol) where Source #
A name of a resource, represented using a Symbol
.
Name :: KnownSymbol n => Name n |
Instances
(KnownSymbol n, n ~ n') => IsLabel n (Name n') Source # | |
Defined in Motor.FSM.Class |
State Actions
An Action
describes a resource action.
type family FromActions (as :: [ActionMapping]) (rs :: Row *) (c :: Constraint) :: (Row *, Constraint) where ... Source #
FromActions '[] rs c = '(rs, c) | |
FromActions ((n := Add a) ': ts) r c = FromActions ts (Extend n a r) (c, (Extend n a r .! n) ~ a) | |
FromActions ((n := Delete a) ': ts) r c = FromActions ts (r .- n) (c, (r .! n) ~ a) | |
FromActions ((n := To a b) ': ts) r c = FromActions ts ((n .== b) .// r) (c, (r .! n) ~ a, (((n .== b) .// r) .! n) ~ b) | |
FromActions ((n := Remain a) ': ts) r c = FromActions ts r (c, (r .! n) ~ a) |
type Actions m as (i :: Row *) a = forall o c. (FromActions as i NoConstraint ~ '(o, c), c) => m i o a Source #
Alias for MonadFSM
that uses FromActions
to construct rows.
type OnlyActions m as a = Actions m as Empty a Source #
Alias for MonadFSM
that uses FromActions
to construct rows,
starting from an Empty
row, i.e. allowing no other resources.
Aliases
FSM
data FSM m (i :: Row *) (o :: Row *) a Source #
IxStateT-based implementation of MonadFSM
.
Instances
Monad m => MonadFSM (FSM m) Source # | |
Defined in Motor.FSM new :: Name n -> a -> FSM m r (Extend n a r) () Source # get :: HasType n a r => Name n -> FSM m r r a Source # delete :: Name n -> FSM m r (r .- n) () Source # enter :: r' ~ ((n .== b) .// r) => Name n -> b -> FSM m r r' () Source # update :: (HasType n a r, Modify n a r ~ r) => Name n -> (a -> a) -> FSM m r r () Source # | |
IxMonadTrans FSM Source # | |
Monad m => IxMonad (FSM m :: Row Type -> Row Type -> Type -> Type) Source # | |
Monad m => IxApplicative (FSM m :: Row Type -> Row Type -> Type -> Type) Source # | |
Monad m => IxPointed (FSM m :: Row Type -> Row Type -> Type -> Type) Source # | |
Monad m => IxFunctor (FSM m :: Row Type -> Row Type -> Type -> Type) Source # | |
Monad m => Monad (FSM m i i) Source # | |
Monad m => Functor (FSM m i i) Source # | |
Monad m => Applicative (FSM m i i) Source # | |
MonadIO m => MonadIO (FSM m i i) Source # | |
Indexed Monad Utilities
module Control.Monad.Indexed