motor-0.3.0: Type-safe effectful state machines in Haskell

Safe HaskellNone
LanguageHaskell2010

Motor.FSM.Sugar

Description

Syntactic sugar for MonadFSM types, adding appropriate row constraints and hiding complexity of the internal implementation.

Synopsis

Documentation

data Action Source #

An Action describes a resource action.

Constructors

Add Type

Adds a new resource of the given Type.

Remain Type

The existing resource of the given Type remains the same.

To Type Type

Transitions an existing resource from the first Type to a resource of the second Type.

Delete Type

Deletes an existing resource of the given Type.

data ActionMapping Source #

Mapping from Symbol to some action a.

Constructors

(:=) Symbol Action infixr 5 

type family FromActions (as :: [ActionMapping]) (rs :: Row *) (c :: Constraint) :: (Row *, Constraint) where ... Source #

Translates a list of Actions to a Row.

Equations

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 (Modify n b r) (c, (r .! n) ~ a, (Modify n b r .! n) ~ b) 
FromActions ((n := Remain a) ': ts) r c = FromActions ts r (c, (r .! n) ~ a) 

type NoActions m (r :: Row *) a = m r r a Source #

Alias for MonadFSM that includes no actions.

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.

type Get m (r :: Row *) n = m r r (r .! n) Source #

Gets an existing resource in state s.

type (!-->) i o = To i o infixl 6 Source #

Infix version of To.

type (!+) (n :: Symbol) s = n := Add s infix 6 Source #

Add a named resource. Alias of Add.

type (!-) (n :: Symbol) s = n := Delete s infix 6 Source #

Delete a named resource. Alias of Delete.