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

Safe HaskellNone
LanguageHaskell2010

Motor.FSM

Contents

Description

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

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:

  1. A Row of input resource states
  2. A Row of output resource state
  3. A return type (just as in Monad)

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 ("connection" ::= Idle :| r) ()

A computation spawnTwoPlayers that adds two resources could have this type:

>>> :t spawnTwoPlayers
spawnTwoPlayers ::
  :: MonadFSM m =>
     m r ("hero2" ::= Standing :| "hero1" ::= Standing :| r) ()

Motor uses the extensible records in Data.OpenRecords, provided by the CTRex 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](https:/hackage.haskell.orgpackage/indexed-0.1.3) 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 matching the CTRex row combinators with the expectations of Motor, which can be tricky to do by hand.

There are three state actions:

  • Add adds a new resource.
  • 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 CTRex works, FSM computations that have a free variable as their input row of resources, i.e. that are polymorphic in the sense of other resource states, must list all their actions in reverse order.

doFourThings ::
     Game m
  => Actions m '[ "hero2" !- Standing
                , "hero1" !- Standing
                , "hero2" !+ Standing
                , "hero1" !+ 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 where Source #

An indexed monad for finite-state machines, managing the state of named resources.

Minimal complete definition

new, delete, enter, call

Methods

new :: Name n -> a -> m r (Extend n a r) () Source #

Creates a new resource and returns its Name.

delete :: Name n -> m r (r :- n) () Source #

Deletes an existing resource named by its Name.

enter :: Name n -> b -> m r ((n ::= b) :| (r :- n)) () Source #

Replaces the state of an existing resource named by its Name.

call :: m Empty Empty a -> m r r a Source #

Run another MonadFSM computation, with empty resource rows, in this computation.

Instances

Monad m => MonadFSM (FSM m) Source # 

Methods

new :: Name n -> a -> FSM m r (Extend n a r) () Source #

delete :: Name n -> FSM m r (r :- n) () Source #

enter :: Name n -> b -> FSM m r ((* ::= n) b :| (r :- n)) () Source #

call :: FSM m Empty Empty a -> FSM m r r a Source #

Resource Names

data Name n where Source #

A name of a resource, represented using a Symbol.

Constructors

Name :: KnownSymbol n => Name n 

State Actions

data n :-> a infixr 5 Source #

Mapping from Symbol to some action k.

data To a b Source #

Action that transitions the state of an existing resource from state a to b.

data Add s Source #

Action that adds a new resource in state s.

data Delete s Source #

Action that deletes an existing resource in state s.

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

Translates a list of Actions to a Row.

Equations

FromActions '[] rs = rs 
FromActions ((n :-> Add a) ': ts) r = Extend n a (FromActions ts r) 
FromActions ((n :-> Delete a) ': ts) r = FromActions ts r :- n 
FromActions ((n :-> To a b) ': ts) r = Extend n b (FromActions ts r :- n) 

type NoActions m r a = m r r a Source #

Alias for MonadFSM that includes no actions.

type Actions m as r a = m r (FromActions as r) 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

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

Infix version of To.

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

Add a named resource. Alias of Add.

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

Delete a named resource. Alias of Delete.

FSM

data FSM m i o a Source #

IxStateT-based implementation of MonadFSM.

Instances

Monad m => MonadFSM (FSM m) Source # 

Methods

new :: Name n -> a -> FSM m r (Extend n a r) () Source #

delete :: Name n -> FSM m r (r :- n) () Source #

enter :: Name n -> b -> FSM m r ((* ::= n) b :| (r :- n)) () Source #

call :: FSM m Empty Empty a -> FSM m r r a Source #

IxMonadTrans (Row *) FSM Source # 

Methods

ilift :: Monad m => m a -> t m i i a #

Monad m => IxMonad (Row *) (FSM m) Source # 

Methods

ibind :: (a -> m j k1 b) -> m i j a -> m i k1 b #

Monad m => IxApplicative (Row *) (FSM m) Source # 

Methods

iap :: m i j (a -> b) -> m j k1 a -> m i k1 b #

Monad m => IxPointed (Row *) (FSM m) Source # 

Methods

ireturn :: a -> m i i a #

Monad m => IxFunctor (Row *) (Row *) (FSM m) Source # 

Methods

imap :: (a -> b) -> f j k2 a -> f j k2 b #

Monad m => Monad (FSM m i i) Source # 

Methods

(>>=) :: FSM m i i a -> (a -> FSM m i i b) -> FSM m i i b #

(>>) :: FSM m i i a -> FSM m i i b -> FSM m i i b #

return :: a -> FSM m i i a #

fail :: String -> FSM m i i a #

Monad m => Functor (FSM m i i) Source # 

Methods

fmap :: (a -> b) -> FSM m i i a -> FSM m i i b #

(<$) :: a -> FSM m i i b -> FSM m i i a #

Monad m => Applicative (FSM m i i) Source # 

Methods

pure :: a -> FSM m i i a #

(<*>) :: FSM m i i (a -> b) -> FSM m i i a -> FSM m i i b #

(*>) :: FSM m i i a -> FSM m i i b -> FSM m i i b #

(<*) :: FSM m i i a -> FSM m i i b -> FSM m i i a #

MonadIO m => MonadIO (FSM m i i) Source # 

Methods

liftIO :: IO a -> FSM m i i a #

runFSM :: Monad m => FSM m Empty Empty a -> m a Source #

Run an FSM state machine and retrieve its return value. Note that all resources added in the FSM computation must be deleted eventually, as the output row is Empty.