Copyright | (c) Galois Inc 2015-2019 |
---|---|
Maintainer | Joe Hendrix <jhendrix@galois.com> |
Safe Haskell | Safe |
Language | Haskell2010 |
This module defines type-level lists used for representing the type of variables in a context.
A Ctx
is never intended to be manipulated at the value level; it is
used purely as a type-level list, just like '[]
. To see how it is
used, see the module header for Data.Parameterized.Context.
Synopsis
- data Ctx k
- type EmptyCtx = 'EmptyCtx
- type SingleCtx x = EmptyCtx ::> x
- type (::>) (c :: Ctx k) (a :: k) = c ::> a
- type family (x :: Ctx k) <+> (y :: Ctx k) :: Ctx k where ...
- type family CtxSize (a :: Ctx k) :: Nat where ...
- 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
- type family CtxLookupRight (n :: Nat) (ctx :: Ctx k) :: k where ...
- type family CtxUpdateRight (n :: Nat) (x :: k) (ctx :: Ctx k) :: Ctx k where ...
- type family CtxFlatten (ctx :: Ctx (Ctx a)) :: Ctx a where ...
- type family CheckIx (ctx :: Ctx k) (n :: Nat) (b :: Bool) :: Constraint where ...
- type ValidIx (n :: Nat) (ctx :: Ctx k) = CheckIx ctx n ((n + 1) <=? CtxSize ctx)
- type FromLeft ctx n = (CtxSize ctx - 1) - n
Documentation
Kind
comprises lists of types of kind Ctx
kk
.
Instances
TraversableFC (Assignment :: (k -> Type) -> Ctx k -> Type) Source # | |
Defined in Data.Parameterized.Context.Unsafe traverseFC :: forall f g m. Applicative m => (forall (x :: k0). f x -> m (g x)) -> forall (x :: l). Assignment f x -> m (Assignment g x) Source # | |
FoldableFC (Assignment :: (k -> Type) -> Ctx k -> Type) Source # | |
Defined in Data.Parameterized.Context.Unsafe foldMapFC :: forall f m. Monoid m => (forall (x :: k0). f x -> m) -> forall (x :: l). Assignment f x -> m Source # foldrFC :: (forall (x :: k0). f x -> b -> b) -> forall (x :: l). b -> Assignment f x -> b Source # foldlFC :: forall f b. (forall (x :: k0). b -> f x -> b) -> forall (x :: l). b -> Assignment f x -> b Source # foldrFC' :: (forall (x :: k0). f x -> b -> b) -> forall (x :: l). b -> Assignment f x -> b Source # foldlFC' :: forall f b. (forall (x :: k0). b -> f x -> b) -> forall (x :: l). b -> Assignment f x -> b Source # toListFC :: (forall (x :: k0). f x -> a) -> forall (x :: l). Assignment f x -> [a] Source # | |
OrdFC (Assignment :: (k -> Type) -> Ctx k -> Type) Source # | |
Defined in Data.Parameterized.Context.Unsafe compareFC :: (forall (x :: k0) (y :: k0). f x -> f y -> OrderingF x y) -> forall (x :: l) (y :: l). Assignment f x -> Assignment f y -> OrderingF x y Source # | |
TestEqualityFC (Assignment :: (k -> Type) -> Ctx k -> Type) Source # | |
Defined in Data.Parameterized.Context.Unsafe testEqualityFC :: (forall (x :: k0) (y :: k0). f x -> f y -> Maybe (x :~: y)) -> forall (x :: l) (y :: l). Assignment f x -> Assignment f y -> Maybe (x :~: y) Source # | |
FunctorFC (Assignment :: (k -> Type) -> Ctx k -> Type) Source # | |
Defined in Data.Parameterized.Context.Unsafe fmapFC :: (forall (x :: k0). f x -> g x) -> forall (x :: l). Assignment f x -> Assignment g x Source # | |
TraversableFCWithIndex (Assignment :: (k -> Type) -> Ctx k -> Type) Source # | |
Defined in Data.Parameterized.Context.Unsafe itraverseFC :: forall m (z :: l) f g. Applicative m => (forall (x :: k0). IndexF (Assignment f z) x -> f x -> m (g x)) -> Assignment f z -> m (Assignment g z) Source # | |
FoldableFCWithIndex (Assignment :: (k -> Type) -> Ctx k -> Type) Source # | |
Defined in Data.Parameterized.Context.Unsafe ifoldMapFC :: forall f m (z :: l). Monoid m => (forall (x :: k0). IndexF (Assignment f z) x -> f x -> m) -> Assignment f z -> m Source # ifoldrFC :: forall (z :: l) f b. (forall (x :: k0). IndexF (Assignment f z) x -> f x -> b -> b) -> b -> Assignment f z -> b Source # ifoldlFC :: forall f b (z :: l). (forall (x :: k0). IndexF (Assignment f z) x -> b -> f x -> b) -> b -> Assignment f z -> b Source # ifoldrFC' :: forall f b (z :: l). (forall (x :: k0). IndexF (Assignment f z) x -> f x -> b -> b) -> b -> Assignment f z -> b Source # ifoldlFC' :: forall f b. (forall (x :: k0). b -> f x -> b) -> forall (x :: l). b -> Assignment f x -> b Source # itoListFC :: forall f a (z :: l). (forall (x :: k0). IndexF (Assignment f z) x -> f x -> a) -> Assignment f z -> [a] Source # | |
FunctorFCWithIndex (Assignment :: (k -> Type) -> Ctx k -> Type) Source # | |
Defined in Data.Parameterized.Context.Unsafe imapFC :: forall f g (z :: l). (forall (x :: k0). IndexF (Assignment f z) x -> f x -> g x) -> Assignment f z -> Assignment g z Source # | |
Category (Diff :: Ctx k -> Ctx k -> Type) Source # | |
ShowF (Size :: Ctx k -> Type) Source # | |
TestEquality f => TestEquality (Assignment f :: Ctx k -> Type) Source # | |
Defined in Data.Parameterized.Context.Unsafe testEquality :: forall (a :: k0) (b :: k0). Assignment f a -> Assignment f b -> Maybe (a :~: b) # | |
HashableF f => HashableF (Assignment f :: Ctx k -> Type) Source # | |
Defined in Data.Parameterized.Context.Unsafe hashWithSaltF :: forall (tp :: k0). Int -> Assignment f tp -> Int Source # hashF :: forall (tp :: k0). Assignment f tp -> Int Source # | |
ShowF f => ShowF (Assignment f :: Ctx k -> Type) Source # | |
Defined in Data.Parameterized.Context.Unsafe withShow :: forall p q (tp :: k0) a. p (Assignment f) -> q tp -> (Show (Assignment f tp) => a) -> a Source # showF :: forall (tp :: k0). Assignment f tp -> String Source # showsPrecF :: forall (tp :: k0). Int -> Assignment f tp -> String -> String Source # | |
OrdF f => OrdF (Assignment f :: Ctx k -> Type) Source # | |
Defined in Data.Parameterized.Context.Unsafe compareF :: forall (x :: k0) (y :: k0). Assignment f x -> Assignment f y -> OrderingF x y Source # leqF :: forall (x :: k0) (y :: k0). Assignment f x -> Assignment f y -> Bool Source # ltF :: forall (x :: k0) (y :: k0). Assignment f x -> Assignment f y -> Bool Source # geqF :: forall (x :: k0) (y :: k0). Assignment f x -> Assignment f y -> Bool Source # gtF :: forall (x :: k0) (y :: k0). Assignment f x -> Assignment f y -> Bool Source # | |
IsRepr f => IsRepr (Assignment f :: Ctx k -> Type) Source # | |
Defined in Data.Parameterized.WithRepr withRepr :: forall (a :: k0) r. Assignment f a -> (KnownRepr (Assignment f) a => r) -> r Source # | |
KnownRepr (Assignment f :: Ctx k -> Type) (EmptyCtx :: Ctx k) Source # | |
Defined in Data.Parameterized.Context.Unsafe knownRepr :: Assignment f EmptyCtx Source # | |
(KnownRepr (Assignment f) ctx, KnownRepr f bt) => KnownRepr (Assignment f :: Ctx k -> Type) (ctx ::> bt :: Ctx k) Source # | |
Defined in Data.Parameterized.Context.Unsafe knownRepr :: Assignment f (ctx ::> bt) Source # |
type family (x :: Ctx k) <+> (y :: Ctx k) :: Ctx k where ... Source #
Append two type-level contexts.
Type context manipulation
type family CtxSize (a :: Ctx k) :: Nat where ... Source #
This type family computes the number of elements in a Ctx
type CtxLookup (n :: Nat) (ctx :: Ctx k) = CtxLookupRight (FromLeft ctx n) ctx Source #
Lookup the value in a context by number, from the left. Produce a type error if the index is out of range.
type CtxUpdate (n :: Nat) (x :: k) (ctx :: Ctx k) = CtxUpdateRight (FromLeft ctx n) x ctx Source #
Update the value in a context by number, from the left. If the index is out of range, the context is unchanged.
type family CtxLookupRight (n :: Nat) (ctx :: Ctx k) :: k where ... Source #
Lookup the value in a context by number, from the right
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 ... Source #
Update the value in a context by number, from the right. If the index is out of range, the context is unchanged.
CtxUpdateRight n x 'EmptyCtx = 'EmptyCtx | |
CtxUpdateRight 0 x (ctx ::> old) = ctx ::> x | |
CtxUpdateRight n x (ctx ::> y) = CtxUpdateRight (n - 1) x ctx ::> y |
type family CtxFlatten (ctx :: Ctx (Ctx a)) :: Ctx a where ... Source #
Flatten a nested context
CtxFlatten EmptyCtx = EmptyCtx | |
CtxFlatten (ctxs ::> ctx) = CtxFlatten ctxs <+> ctx |
type family CheckIx (ctx :: Ctx k) (n :: Nat) (b :: Bool) :: Constraint where ... Source #
Helper type family used to generate descriptive error messages when
an index is larger than the length of the Ctx
being indexed.