{-# LANGUAGE ConstraintKinds #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE KindSignatures #-}
{-# LANGUAGE PolyKinds #-}
{-# LANGUAGE Safe #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE UndecidableInstances #-}
module Data.Parameterized.Ctx
( type Ctx(..)
, EmptyCtx
, SingleCtx
, (::>)
, type (<+>)
, CtxSize
, CtxLookup
, CtxUpdate
, CtxLookupRight
, CtxUpdateRight
, CheckIx
, ValidIx
, FromLeft
) where
import Data.Kind (Constraint)
import GHC.TypeLits (Nat, type (+), type (-), type (<=?), TypeError, ErrorMessage(..))
type EmptyCtx = 'EmptyCtx
type (c :: Ctx k) ::> (a::k) = c '::> a
type SingleCtx x = EmptyCtx ::> x
data Ctx k
= EmptyCtx
| Ctx k ::> k
type family (<+>) (x :: Ctx k) (y :: Ctx k) :: Ctx k where
x <+> EmptyCtx = x
x <+> (y ::> e) = (x <+> y) ::> e
type family CtxSize (a :: Ctx k) :: Nat where
CtxSize 'EmptyCtx = 0
CtxSize (xs '::> x) = 1 + CtxSize xs
type family CheckIx (ctx :: Ctx k) (n :: Nat) (b :: Bool) :: Constraint where
CheckIx ctx n 'True = ()
CheckIx ctx n 'False = TypeError ('Text "Index " ':<>: 'ShowType n
':<>: 'Text " out of range in " ':<>: 'ShowType ctx)
type ValidIx (n :: Nat) (ctx :: Ctx k)
= CheckIx ctx n (n+1 <=? CtxSize ctx)
type FromLeft ctx n = CtxSize ctx - 1 - n
type family CtxLookupRight (n :: Nat) (ctx :: Ctx k) :: k where
CtxLookupRight 0 (ctx '::> r) = r
CtxLookupRight n (ctx '::> r) = CtxLookupRight (n-1) ctx
type family CtxUpdateRight (n :: Nat) (x::k) (ctx :: Ctx k) :: Ctx k where
CtxUpdateRight n x 'EmptyCtx = 'EmptyCtx
CtxUpdateRight 0 x (ctx '::> old) = ctx '::> x
CtxUpdateRight n x (ctx '::> y) = CtxUpdateRight (n-1) x ctx '::> y
type CtxLookup (n :: Nat) (ctx :: Ctx k)
= CtxLookupRight (FromLeft ctx n) ctx
type CtxUpdate (n :: Nat) (x :: k) (ctx :: Ctx k)
= CtxUpdateRight (FromLeft ctx n) x ctx