module Control.SessionTypes.Types (
  
  ST(..),
  Cap(..),
  GetST,
  GetCtx,
  
  Dual,
  DualST,
  MapDual,
  
  RemoveSend,
  RemoveSendST,
  MapRemoveSend,
  RemoveRecv,
  RemoveRecvST,
  MapRemoveRecv,
  
  HasConstraint,
  HasConstraintST,
  MapHasConstraint,
  HasConstraints,
  
  IfThenElse,
  Not,
  Or,
  
  Prod (..),
  Left,
  Right,
  
  Nat(..),
  Ref(..),
  TypeEqList,
  Append
) where
import Data.Kind
import Data.Typeable
infixr 6 :?>
infixr 6 :!>
data ST a = (:?>) a (ST a) 
    | (:!>) a (ST a) 
    | Sel [ST a] 
    | Off [ST a] 
    | R (ST a)  
    | Wk (ST a) 
    | V 
    | Eps 
    deriving Typeable
data Cap a = Cap [ST a] (ST a) deriving Typeable
type family GetST s where
  GetST ('Cap ctx s) = s
type family GetCtx s where
  GetCtx ('Cap ctx s) = ctx
type family Dual s = r | r -> s where
  Dual ('Cap ctx s) = 'Cap (MapDual ctx) (DualST s)
type family DualST (a :: ST c) = (b :: ST c) | b -> a where
  DualST (s :!> r) = s :?> DualST r
  DualST (s :?> r) = s :!> DualST r
  DualST (Sel xs)  = Off (MapDual xs)
  DualST (Off xs)  = Sel (MapDual xs)
  DualST (R s)     = R (DualST s)
  DualST (Wk s)    = Wk (DualST s)
  DualST V         = V
  DualST Eps       = Eps
type family MapDual xs = ys | ys -> xs where
  MapDual '[] = '[]
  MapDual (s ': xs) = DualST s ': MapDual xs
type family RemoveSend s where
  RemoveSend ('Cap ctx s) = 'Cap (MapRemoveSend ctx) (RemoveSendST s)
type family RemoveSendST s where
  RemoveSendST (a :!> r) = RemoveSendST r
  RemoveSendST (a :?> r) = a :?> RemoveSendST r
  RemoveSendST (Sel xs) = Sel (MapRemoveSend xs)
  RemoveSendST (Off xs) = Off (MapRemoveSend xs)
  RemoveSendST (R s) = R (RemoveSendST s)
  RemoveSendST (Wk s) = Wk (RemoveSendST s)
  RemoveSendST s = s
type family MapRemoveSend ctx where
  MapRemoveSend '[] = '[]
  MapRemoveSend (s ': ctx) = RemoveSendST s ': MapRemoveSend ctx
type family RemoveRecv s where
  RemoveRecv ('Cap ctx s) = 'Cap (MapRemoveRecv ctx) (RemoveRecvST s)
type family MapRemoveRecv ctx where
  MapRemoveRecv '[] = '[]
  MapRemoveRecv (s ': ctx) = RemoveRecvST s ': MapRemoveRecv ctx
type family RemoveRecvST s where
  RemoveRecvST (a :!> r) = a :!> RemoveRecvST r
  RemoveRecvST (a :?> r) = RemoveRecvST r
  RemoveRecvST (Sel xs) = Sel (MapRemoveRecv xs)
  RemoveRecvST (Off xs) = Off (MapRemoveRecv xs)
  RemoveRecvST (R s) = R (RemoveRecvST s)
  RemoveRecvST (Wk s) = Wk (RemoveRecvST s)
  RemoveRecvST s = s
type family HasConstraint (c :: Type -> Constraint) s :: Constraint where
  HasConstraint c ('Cap ctx s) = (HasConstraintST c s, MapHasConstraint c ctx)
type family MapHasConstraint (c :: Type -> Constraint) ss :: Constraint where
  MapHasConstraint c '[] = ()
  MapHasConstraint c (s ': ss) = (HasConstraintST c s, MapHasConstraint c ss)
type family HasConstraintST (c :: Type -> Constraint) s :: Constraint where
  HasConstraintST c (a :!> r) = (c a, HasConstraintST c r)
  HasConstraintST c (a :?> r) = (c a, HasConstraintST c r)
  HasConstraintST c (Sel '[]) = ()
  HasConstraintST c (Sel (s ': xs)) = (HasConstraintST c s, HasConstraintST c (Sel xs))
  HasConstraintST c (Off '[]) = ()
  HasConstraintST c (Off (s ': xs)) = (HasConstraintST c s, HasConstraintST c (Off xs))
  HasConstraintST c (R s) = HasConstraintST c s
  HasConstraintST c (Wk s) = HasConstraintST c s
  HasConstraintST c V = ()
  HasConstraintST c s = ()
type family HasConstraints (cs :: [Type -> Constraint]) s :: Constraint where
  HasConstraints '[] s = ()
  HasConstraints (c ': cs) s = (HasConstraint c s, HasConstraints cs s)
type family HasConstraintsST (cs :: [Type -> Constraint]) s :: Constraint where
  HasConstraintsST '[] s = ()
  HasConstraintsST (c ': cs) s = (HasConstraintST c s, HasConstraintsST cs s)
type family MapHasConstraints (cs :: [Type -> Constraint]) ctx :: Constraint where
  MapHasConstraints '[] ctx = ()
  MapHasConstraints (c ': cs) ctx = (MapHasConstraint c ctx, MapHasConstraints cs ctx)
type family IfThenElse (b :: Bool) (l :: k) (r :: k) :: k where
  IfThenElse 'True l r = l
  IfThenElse 'False l r = r 
type family Not b :: Bool where
  Not 'True  = 'False
  Not 'False = 'True
type family Or b1 b2 :: Bool where
  Or 'True b = 'True
  Or b 'True = 'True
  Or b1 b2 = 'False
data Prod t = (:*:) (Cap t) (Cap t)
type family Left p where
  Left (l :*: r) = l
type family Right p where
  Right (l :*: r) = r
data Nat = Z | S Nat deriving (Show, Eq, Ord)
data Ref s xs where
  RefZ :: Ref s (s ': xs)
  RefS :: Ref s (k ': xs) -> Ref s (t ': k ': xs)
type family TypeEqList xs s where
  TypeEqList '[s] s = '[True]
  TypeEqList '[r] s = '[False]
  TypeEqList (s ': xs) s = 'True ': TypeEqList xs s
  TypeEqList (r ': xs) s = 'False ': TypeEqList xs s
type family Append xs ys where
  Append '[] ys = ys
  Append (x ': xs) ys = x ': xs `Append` ys