{-# LANGUAGE ConstraintKinds #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE ExplicitNamespaces #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE KindSignatures #-}
{-# LANGUAGE LiberalTypeSynonyms #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE PolyKinds #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE UndecidableInstances #-}
module Motor.FSM.Sugar
( Action(..)
, ActionMapping(..)
, FromActions
, NoActions
, Actions
, OnlyActions
, Get
, type (!-->)
, type (!+)
, type (!-)
) where
import Data.Kind
import Data.Row.Records
import GHC.TypeLits (Symbol)
data Action
= Add Type
| Remain Type
| To Type
Type
| Delete Type
data ActionMapping = (:=) Symbol Action
infixr 5 :=
type family FromActions (as :: [ActionMapping]) (rs :: Row *) (c :: Constraint) :: (Row *, Constraint) where
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 NoConstraint = (() :: Constraint)
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
infixl 6 !-->
type (!+) (n :: Symbol) s = n ':= 'Add s
infix 6 !+
type (!-) (n :: Symbol) s = n ':= 'Delete s
infix 6 !-