Safe Haskell | None |
---|---|
Language | Haskell2010 |
Syntactic sugar for MonadFSM
types, adding appropriate row
constraints and hiding complexity of the internal implementation.
Synopsis
- 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
Documentation
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.