Copyright | (c) Galois Inc 2014-2019 |
---|---|
Maintainer | Joe Hendrix <jhendrix@galois.com> |
Safe Haskell | Trustworthy |
Language | Haskell2010 |
This module reexports either Data.Parameterized.Context.Safe or Data.Parameterized.Context.Unsafe depending on the the unsafe-operations compile-time flag.
It also defines some utility typeclasses for transforming between curried and uncurried versions of functions over contexts.
The Assignment
type is isomorphic to the List
type, except Assignment
s construct lists from the right-hand side,
and instead of using type-level '[]
-style lists, an Assignment
is
indexed by a type-level Ctx
. The
implementation of Assignment
s is also more efficent than
List
for lists of many elements, as it uses a
balanced binary tree representation rather than a linear-time
list. For a motivating example, see List
.
Synopsis
- module Data.Parameterized.Ctx
- class KnownContext (ctx :: Ctx k) where
- data Size (ctx :: Ctx k)
- sizeInt :: Size ctx -> Int
- zeroSize :: Size 'EmptyCtx
- incSize :: Size ctx -> Size (ctx ::> tp)
- decSize :: Size (ctx ::> tp) -> Size ctx
- extSize :: Size l -> Diff l r -> Size r
- addSize :: Size x -> Size y -> Size (x <+> y)
- data SizeView (ctx :: Ctx k) where
- viewSize :: Size ctx -> SizeView ctx
- data Diff (l :: Ctx k) (r :: Ctx k)
- noDiff :: Diff l l
- addDiff :: Diff a b -> Diff b c -> Diff a c
- extendRight :: Diff l r -> Diff l (r ::> tp)
- appendDiff :: Size r -> Diff l (l <+> r)
- data DiffView a b where
- viewDiff :: Diff a b -> DiffView a b
- class KnownDiff (l :: Ctx k) (r :: Ctx k) where
- data IsAppend l r where
- diffIsAppend :: Diff l r -> IsAppend l r
- data Index (ctx :: Ctx k) (tp :: k)
- indexVal :: Index ctx tp -> Int
- baseIndex :: Index ('EmptyCtx ::> tp) tp
- skipIndex :: Index ctx x -> Index (ctx ::> y) x
- lastIndex :: Size (ctx ::> tp) -> Index (ctx ::> tp) tp
- nextIndex :: Size ctx -> Index (ctx ::> tp) tp
- leftIndex :: Size r -> Index l tp -> Index (l <+> r) tp
- rightIndex :: Size l -> Size r -> Index r tp -> Index (l <+> r) tp
- extendIndex :: KnownDiff l r => Index l tp -> Index r tp
- extendIndex' :: Diff l r -> Index l tp -> Index r tp
- extendIndexAppendLeft :: Size l -> Size r -> Index r tp -> Index (l <+> r) tp
- forIndex :: forall ctx r. Size ctx -> (forall tp. r -> Index ctx tp -> r) -> r -> r
- forIndexRange :: forall ctx r. Int -> Size ctx -> (forall tp. Index ctx tp -> r -> r) -> r -> r
- intIndex :: Int -> Size ctx -> Maybe (Some (Index ctx))
- data IndexView ctx tp where
- IndexViewLast :: !(Size ctx) -> IndexView (ctx ::> t) t
- IndexViewInit :: !(Index ctx t) -> IndexView (ctx ::> u) t
- viewIndex :: Size ctx -> Index ctx tp -> IndexView ctx tp
- data IndexRange (ctx :: Ctx k) (sub :: Ctx k)
- allRange :: Size ctx -> IndexRange ctx ctx
- indexOfRange :: IndexRange ctx (EmptyCtx ::> e) -> Index ctx e
- dropHeadRange :: IndexRange ctx (x <+> y) -> Size x -> IndexRange ctx y
- dropTailRange :: IndexRange ctx (x <+> y) -> Size y -> IndexRange ctx x
- data Assignment (f :: k -> Type) (ctx :: Ctx k)
- size :: Assignment f ctx -> Size ctx
- replicate :: Size ctx -> (forall tp. f tp) -> Assignment f ctx
- generate :: Size ctx -> (forall tp. Index ctx tp -> f tp) -> Assignment f ctx
- generateM :: Applicative m => Size ctx -> (forall tp. Index ctx tp -> m (f tp)) -> m (Assignment f ctx)
- empty :: Assignment f EmptyCtx
- extend :: Assignment f ctx -> f x -> Assignment f (ctx ::> x)
- adjust :: (f tp -> f tp) -> Index ctx tp -> Assignment f ctx -> Assignment f ctx
- update :: Index ctx tp -> f tp -> Assignment f ctx -> Assignment f ctx
- adjustM :: Functor m => (f tp -> m (f tp)) -> Index ctx tp -> Assignment f ctx -> m (Assignment f ctx)
- data AssignView f ctx where
- AssignEmpty :: AssignView f EmptyCtx
- AssignExtend :: Assignment f ctx -> f tp -> AssignView f (ctx ::> tp)
- viewAssign :: forall f ctx. Assignment f ctx -> AssignView f ctx
- (!) :: Assignment f ctx -> Index ctx tp -> f tp
- (!^) :: KnownDiff l r => Assignment f r -> Index l tp -> f tp
- zipWith :: (forall x. f x -> g x -> h x) -> Assignment f a -> Assignment g a -> Assignment h a
- zipWithM :: Applicative m => (forall x. f x -> g x -> m (h x)) -> Assignment f a -> Assignment g a -> m (Assignment h a)
- (<++>) :: Assignment f x -> Assignment f y -> Assignment f (x <+> y)
- traverseWithIndex :: Applicative m => (forall tp. Index ctx tp -> f tp -> m (g tp)) -> Assignment f ctx -> m (Assignment g ctx)
- singleton :: f tp -> Assignment f (EmptyCtx ::> tp)
- toVector :: Assignment f tps -> (forall tp. f tp -> e) -> Vector e
- pattern (:>) :: () => ctx' ~ (ctx ::> tp) => Assignment f ctx -> f tp -> Assignment f ctx'
- pattern Empty :: () => ctx ~ EmptyCtx => Assignment f ctx
- decompose :: Assignment f (ctx ::> tp) -> (Assignment f ctx, f tp)
- null :: Assignment f ctx -> Bool
- init :: Assignment f (ctx ::> tp) -> Assignment f ctx
- last :: Assignment f (ctx ::> tp) -> f tp
- view :: forall f ctx. Assignment f ctx -> AssignView f ctx
- take :: forall f ctx ctx'. Size ctx -> Size ctx' -> Assignment f (ctx <+> ctx') -> Assignment f ctx
- drop :: forall f ctx ctx'. Size ctx -> Size ctx' -> Assignment f (ctx <+> ctx') -> Assignment f ctx'
- forIndexM :: forall ctx m. Applicative m => Size ctx -> (forall tp. Index ctx tp -> m ()) -> m ()
- generateSome :: forall f. Int -> (Int -> Some f) -> Some (Assignment f)
- generateSomeM :: forall m f. Applicative m => Int -> (Int -> m (Some f)) -> m (Some (Assignment f))
- fromList :: [Some f] -> Some (Assignment f)
- traverseAndCollect :: (Monoid w, Applicative m) => (forall tp. Index ctx tp -> f tp -> m w) -> Assignment f ctx -> m w
- traverseWithIndex_ :: Applicative m => (forall tp. Index ctx tp -> f tp -> m ()) -> Assignment f ctx -> m ()
- dropPrefix :: forall f xs prefix a. TestEquality f => Assignment f xs -> Assignment f prefix -> a -> (forall addl. xs ~ (prefix <+> addl) => Assignment f addl -> a) -> a
- data CtxEmbedding (ctx :: Ctx k) (ctx' :: Ctx k) = CtxEmbedding {
- _ctxeSize :: Size ctx'
- _ctxeAssignment :: Assignment (Index ctx') ctx
- class ExtendContext (f :: Ctx k -> *) where
- extendContext :: Diff ctx ctx' -> f ctx -> f ctx'
- class ExtendContext' (f :: Ctx k -> k' -> *) where
- extendContext' :: Diff ctx ctx' -> f ctx v -> f ctx' v
- class ApplyEmbedding (f :: Ctx k -> *) where
- applyEmbedding :: CtxEmbedding ctx ctx' -> f ctx -> f ctx'
- class ApplyEmbedding' (f :: Ctx k -> k' -> *) where
- applyEmbedding' :: CtxEmbedding ctx ctx' -> f ctx v -> f ctx' v
- identityEmbedding :: Size ctx -> CtxEmbedding ctx ctx
- extendEmbeddingRightDiff :: forall ctx ctx' ctx''. Diff ctx' ctx'' -> CtxEmbedding ctx ctx' -> CtxEmbedding ctx ctx''
- extendEmbeddingRight :: CtxEmbedding ctx ctx' -> CtxEmbedding ctx (ctx' ::> tp)
- extendEmbeddingBoth :: forall ctx ctx' tp. CtxEmbedding ctx ctx' -> CtxEmbedding (ctx ::> tp) (ctx' ::> tp)
- appendEmbedding :: Size ctx -> Size ctx' -> CtxEmbedding ctx (ctx <+> ctx')
- appendEmbeddingLeft :: Size ctx -> Size ctx' -> CtxEmbedding ctx' (ctx <+> ctx')
- ctxeSize :: Simple Lens (CtxEmbedding ctx ctx') (Size ctx')
- ctxeAssignment :: Lens (CtxEmbedding ctx1 ctx') (CtxEmbedding ctx2 ctx') (Assignment (Index ctx') ctx1) (Assignment (Index ctx') ctx2)
- type Idx n ctx r = (ValidIx n ctx, Idx' (FromLeft ctx n) ctx r)
- field :: forall n ctx f r. Idx n ctx r => Lens' (Assignment f ctx) (f r)
- natIndex :: forall n ctx r. Idx n ctx r => Index ctx r
- natIndexProxy :: forall n ctx r proxy. Idx n ctx r => proxy n -> Index ctx r
- type family CurryAssignment (ctx :: Ctx k) (f :: k -> *) (x :: *) :: * where ...
- class CurryAssignmentClass (ctx :: Ctx k) where
- curryAssignment :: (Assignment f ctx -> x) -> CurryAssignment ctx f x
- uncurryAssignment :: CurryAssignment ctx f x -> Assignment f ctx -> x
- size1 :: Size (EmptyCtx ::> a)
- size2 :: Size ((EmptyCtx ::> a) ::> b)
- size3 :: Size (((EmptyCtx ::> a) ::> b) ::> c)
- size4 :: Size ((((EmptyCtx ::> a) ::> b) ::> c) ::> d)
- size5 :: Size (((((EmptyCtx ::> a) ::> b) ::> c) ::> d) ::> e)
- size6 :: Size ((((((EmptyCtx ::> a) ::> b) ::> c) ::> d) ::> e) ::> f)
- i1of2 :: Index ((EmptyCtx ::> a) ::> b) a
- i2of2 :: Index ((EmptyCtx ::> a) ::> b) b
- i1of3 :: Index (((EmptyCtx ::> a) ::> b) ::> c) a
- i2of3 :: Index (((EmptyCtx ::> a) ::> b) ::> c) b
- i3of3 :: Index (((EmptyCtx ::> a) ::> b) ::> c) c
- i1of4 :: Index ((((EmptyCtx ::> a) ::> b) ::> c) ::> d) a
- i2of4 :: Index ((((EmptyCtx ::> a) ::> b) ::> c) ::> d) b
- i3of4 :: Index ((((EmptyCtx ::> a) ::> b) ::> c) ::> d) c
- i4of4 :: Index ((((EmptyCtx ::> a) ::> b) ::> c) ::> d) d
- i1of5 :: Index (((((EmptyCtx ::> a) ::> b) ::> c) ::> d) ::> e) a
- i2of5 :: Index (((((EmptyCtx ::> a) ::> b) ::> c) ::> d) ::> e) b
- i3of5 :: Index (((((EmptyCtx ::> a) ::> b) ::> c) ::> d) ::> e) c
- i4of5 :: Index (((((EmptyCtx ::> a) ::> b) ::> c) ::> d) ::> e) d
- i5of5 :: Index (((((EmptyCtx ::> a) ::> b) ::> c) ::> d) ::> e) e
- i1of6 :: Index ((((((EmptyCtx ::> a) ::> b) ::> c) ::> d) ::> e) ::> f) a
- i2of6 :: Index ((((((EmptyCtx ::> a) ::> b) ::> c) ::> d) ::> e) ::> f) b
- i3of6 :: Index ((((((EmptyCtx ::> a) ::> b) ::> c) ::> d) ::> e) ::> f) c
- i4of6 :: Index ((((((EmptyCtx ::> a) ::> b) ::> c) ::> d) ::> e) ::> f) d
- i5of6 :: Index ((((((EmptyCtx ::> a) ::> b) ::> c) ::> d) ::> e) ::> f) e
- i6of6 :: Index ((((((EmptyCtx ::> a) ::> b) ::> c) ::> d) ::> e) ::> f) f
Documentation
module Data.Parameterized.Ctx
class KnownContext (ctx :: Ctx k) where Source #
A context that can be determined statically at compiler time.
Instances
KnownContext ('EmptyCtx :: Ctx k) Source # | |
KnownContext ctx => KnownContext (ctx ::> tp :: Ctx k) Source # | |
Size
data Size (ctx :: Ctx k) Source #
Represents the size of a context.
Diff
data Diff (l :: Ctx k) (r :: Ctx k) Source #
Difference in number of elements between two contexts. The first context must be a sub-context of the other.
addDiff :: Diff a b -> Diff b c -> Diff a c Source #
The addition of differences. Flipped binary operation
of Category
instance.
extendRight :: Diff l r -> Diff l (r ::> tp) Source #
Extend the difference to a sub-context of the right side.
class KnownDiff (l :: Ctx k) (r :: Ctx k) where Source #
A difference that can be automatically inferred at compile time.
diffIsAppend :: Diff l r -> IsAppend l r Source #
If l
is a sub-context of r
then extract out their "contextual
difference", i.e., the app
such that r = l + app
Indexing
data Index (ctx :: Ctx k) (tp :: k) Source #
An index is a reference to a position with a particular type in a context.
Instances
ExtendContext' (Index :: Ctx k' -> k' -> Type) Source # | |
Defined in Data.Parameterized.Context | |
ApplyEmbedding' (Index :: Ctx k' -> k' -> Type) Source # | |
Defined in Data.Parameterized.Context applyEmbedding' :: forall (ctx :: Ctx k) (ctx' :: Ctx k) (v :: k'0). CtxEmbedding ctx ctx' -> Index ctx v -> Index ctx' v Source # | |
TestEquality (Index ctx :: k -> Type) Source # | |
Defined in Data.Parameterized.Context.Unsafe | |
HashableF (Index ctx :: k -> Type) Source # | |
ShowF (Index ctx :: k -> Type) Source # | |
OrdF (Index ctx :: k -> Type) Source # | |
Defined in Data.Parameterized.Context.Unsafe compareF :: forall (x :: k0) (y :: k0). Index ctx x -> Index ctx y -> OrderingF x y Source # leqF :: forall (x :: k0) (y :: k0). Index ctx x -> Index ctx y -> Bool Source # ltF :: forall (x :: k0) (y :: k0). Index ctx x -> Index ctx y -> Bool Source # geqF :: forall (x :: k0) (y :: k0). Index ctx x -> Index ctx y -> Bool Source # gtF :: forall (x :: k0) (y :: k0). Index ctx x -> Index ctx y -> Bool Source # | |
Eq (Index ctx tp) Source # | |
Ord (Index ctx tp) Source # | |
Defined in Data.Parameterized.Context.Unsafe | |
Show (Index ctx tp) Source # | |
Hashable (Index ctx tp) Source # | |
Defined in Data.Parameterized.Context.Unsafe |
skipIndex :: Index ctx x -> Index (ctx ::> y) x Source #
Increase context while staying at same index.
nextIndex :: Size ctx -> Index (ctx ::> tp) tp Source #
Return the index of a element one past the size.
leftIndex :: Size r -> Index l tp -> Index (l <+> r) tp Source #
Adapts an index in the left hand context of an append operation.
rightIndex :: Size l -> Size r -> Index r tp -> Index (l <+> r) tp Source #
Adapts an index in the right hand context of an append operation.
forIndex :: forall ctx r. Size ctx -> (forall tp. r -> Index ctx tp -> r) -> r -> r Source #
Given a size n
, an initial value v0
, and a function f
, the
expression forIndex n v0 f
is equivalent to v0
when n
is
zero, and f (forIndex (n-1) v0) n
otherwise. Unlike the safe
version, which starts from Index
0
and increments Index
values, this version starts at Index
(n-1)
and decrements
Index
values to Index
0
.
forIndexRange :: forall ctx r. Int -> Size ctx -> (forall tp. Index ctx tp -> r -> r) -> r -> r Source #
Given an index i
, size n
, a function f
, value v
, and a
function f
, the expression forIndex i n f v
is equivalent to
v
when i >= sizeInt n
, and f i (forIndexRange (i+1) n v)
otherwise.
intIndex :: Int -> Size ctx -> Maybe (Some (Index ctx)) Source #
Return index at given integer or nothing if integer is out of bounds.
data IndexView ctx tp where Source #
View of indexes as pointing to the last element in the index range or pointing to an earlier element in a smaller range.
IndexViewLast :: !(Size ctx) -> IndexView (ctx ::> t) t | |
IndexViewInit :: !(Index ctx t) -> IndexView (ctx ::> u) t |
IndexRange
data IndexRange (ctx :: Ctx k) (sub :: Ctx k) Source #
This represents a contiguous range of indices.
allRange :: Size ctx -> IndexRange ctx ctx Source #
Return a range containing all indices in the context.
indexOfRange :: IndexRange ctx (EmptyCtx ::> e) -> Index ctx e Source #
indexOfRange
returns the only index in a range.
dropHeadRange :: IndexRange ctx (x <+> y) -> Size x -> IndexRange ctx y Source #
dropHeadRange r n
drops the first n
elements in r
.
dropTailRange :: IndexRange ctx (x <+> y) -> Size y -> IndexRange ctx x Source #
dropTailRange r n
drops the last n
elements in r
.
Assignments
data Assignment (f :: k -> Type) (ctx :: Ctx k) Source #
An assignment is a sequence that maps each index with type tp
to
a value of type f tp
.
This assignment implementation uses a binomial tree implementation that offers lookups and updates in time and space logarithmic with respect to the number of elements in the context.
Instances
size :: Assignment f ctx -> Size ctx Source #
Return number of elements in assignment.
replicate :: Size ctx -> (forall tp. f tp) -> Assignment f ctx Source #
replicate n
make a context with different copies of the same
polymorphic value.
generate :: Size ctx -> (forall tp. Index ctx tp -> f tp) -> Assignment f ctx Source #
Generate an assignment
generateM :: Applicative m => Size ctx -> (forall tp. Index ctx tp -> m (f tp)) -> m (Assignment f ctx) Source #
Generate an assignment in an Applicative
context
empty :: Assignment f EmptyCtx Source #
Return empty assignment
extend :: Assignment f ctx -> f x -> Assignment f (ctx ::> x) Source #
adjust :: (f tp -> f tp) -> Index ctx tp -> Assignment f ctx -> Assignment f ctx Source #
Deprecated: Replace 'adjust f i asgn' with 'Lens.over (ixF i) f asgn' instead.
update :: Index ctx tp -> f tp -> Assignment f ctx -> Assignment f ctx Source #
Deprecated: Replace 'update idx val asgn' with 'Lens.set (ixF idx) val asgn' instead.
adjustM :: Functor m => (f tp -> m (f tp)) -> Index ctx tp -> Assignment f ctx -> m (Assignment f ctx) Source #
Modify the value of an assignment at a particular index.
data AssignView f ctx where Source #
Represent an assignment as either empty or an assignment with one appended.
AssignEmpty :: AssignView f EmptyCtx | |
AssignExtend :: Assignment f ctx -> f tp -> AssignView f (ctx ::> tp) |
viewAssign :: forall f ctx. Assignment f ctx -> AssignView f ctx Source #
View an assignment as either empty or an assignment with one appended.
(!) :: Assignment f ctx -> Index ctx tp -> f tp Source #
Return value of assignment.
(!^) :: KnownDiff l r => Assignment f r -> Index l tp -> f tp Source #
Return value of assignment, where the index is into an initial sequence of the assignment.
zipWith :: (forall x. f x -> g x -> h x) -> Assignment f a -> Assignment g a -> Assignment h a Source #
zipWithM :: Applicative m => (forall x. f x -> g x -> m (h x)) -> Assignment f a -> Assignment g a -> m (Assignment h a) Source #
(<++>) :: Assignment f x -> Assignment f y -> Assignment f (x <+> y) Source #
traverseWithIndex :: Applicative m => (forall tp. Index ctx tp -> f tp -> m (g tp)) -> Assignment f ctx -> m (Assignment g ctx) Source #
toVector :: Assignment f tps -> (forall tp. f tp -> e) -> Vector e Source #
Convert the assignment to a vector.
pattern (:>) :: () => ctx' ~ (ctx ::> tp) => Assignment f ctx -> f tp -> Assignment f ctx' infixl 9 Source #
Pattern synonym for extending an assignment on the right
pattern Empty :: () => ctx ~ EmptyCtx => Assignment f ctx Source #
Pattern synonym for the empty assignment
decompose :: Assignment f (ctx ::> tp) -> (Assignment f ctx, f tp) Source #
null :: Assignment f ctx -> Bool Source #
Return true if assignment is empty.
init :: Assignment f (ctx ::> tp) -> Assignment f ctx Source #
Return assignment with all but the last block.
last :: Assignment f (ctx ::> tp) -> f tp Source #
Return the last element in the assignment.
view :: forall f ctx. Assignment f ctx -> AssignView f ctx Source #
Deprecated: Use viewAssign or the Empty and :> patterns instead.
View an assignment as either empty or an assignment with one appended.
take :: forall f ctx ctx'. Size ctx -> Size ctx' -> Assignment f (ctx <+> ctx') -> Assignment f ctx Source #
Return the prefix of an appended Assignment
drop :: forall f ctx ctx'. Size ctx -> Size ctx' -> Assignment f (ctx <+> ctx') -> Assignment f ctx' Source #
Return the suffix of an appended Assignment
forIndexM :: forall ctx m. Applicative m => Size ctx -> (forall tp. Index ctx tp -> m ()) -> m () Source #
'forIndexM sz f' calls f
on indices '[0..sz-1]'.
generateSome :: forall f. Int -> (Int -> Some f) -> Some (Assignment f) Source #
Generate an assignment with some context type that is not known.
generateSomeM :: forall m f. Applicative m => Int -> (Int -> m (Some f)) -> m (Some (Assignment f)) Source #
Generate an assignment with some context type that is not known.
traverseAndCollect :: (Monoid w, Applicative m) => (forall tp. Index ctx tp -> f tp -> m w) -> Assignment f ctx -> m w Source #
Visit each of the elements in an Assignment
in order
from left to right and collect the results using the provided Monoid
.
traverseWithIndex_ :: Applicative m => (forall tp. Index ctx tp -> f tp -> m ()) -> Assignment f ctx -> m () Source #
Visit each of the elements in an Assignment
in order
from left to right, executing an action with each.
:: forall f xs prefix a. TestEquality f | |
=> Assignment f xs | Assignment to split |
-> Assignment f prefix | Expected prefix |
-> a | error continuation |
-> (forall addl. xs ~ (prefix <+> addl) => Assignment f addl -> a) | success continuation |
-> a |
Utility function for testing if xs
is an assignment with
prefix
as a prefix, and computing the tail of xs
not in the prefix, if so.
Context extension and embedding utilities
data CtxEmbedding (ctx :: Ctx k) (ctx' :: Ctx k) Source #
This datastructure contains a proof that the first context is embeddable in the second. This is useful if we want to add extend an existing term under a larger context.
CtxEmbedding | |
|
class ExtendContext (f :: Ctx k -> *) where Source #
extendContext :: Diff ctx ctx' -> f ctx -> f ctx' Source #
class ExtendContext' (f :: Ctx k -> k' -> *) where Source #
extendContext' :: Diff ctx ctx' -> f ctx v -> f ctx' v Source #
Instances
ExtendContext' (Index :: Ctx k' -> k' -> Type) Source # | |
Defined in Data.Parameterized.Context |
class ApplyEmbedding (f :: Ctx k -> *) where Source #
applyEmbedding :: CtxEmbedding ctx ctx' -> f ctx -> f ctx' Source #
class ApplyEmbedding' (f :: Ctx k -> k' -> *) where Source #
applyEmbedding' :: CtxEmbedding ctx ctx' -> f ctx v -> f ctx' v Source #
Instances
ApplyEmbedding' (Index :: Ctx k' -> k' -> Type) Source # | |
Defined in Data.Parameterized.Context applyEmbedding' :: forall (ctx :: Ctx k) (ctx' :: Ctx k) (v :: k'0). CtxEmbedding ctx ctx' -> Index ctx v -> Index ctx' v Source # |
identityEmbedding :: Size ctx -> CtxEmbedding ctx ctx Source #
extendEmbeddingRightDiff :: forall ctx ctx' ctx''. Diff ctx' ctx'' -> CtxEmbedding ctx ctx' -> CtxEmbedding ctx ctx'' Source #
extendEmbeddingRight :: CtxEmbedding ctx ctx' -> CtxEmbedding ctx (ctx' ::> tp) Source #
extendEmbeddingBoth :: forall ctx ctx' tp. CtxEmbedding ctx ctx' -> CtxEmbedding (ctx ::> tp) (ctx' ::> tp) Source #
appendEmbedding :: Size ctx -> Size ctx' -> CtxEmbedding ctx (ctx <+> ctx') Source #
Prove that the prefix of an appended context is embeddable in it
appendEmbeddingLeft :: Size ctx -> Size ctx' -> CtxEmbedding ctx' (ctx <+> ctx') Source #
Prove that the suffix of an appended context is embeddable in it
ctxeAssignment :: Lens (CtxEmbedding ctx1 ctx') (CtxEmbedding ctx2 ctx') (Assignment (Index ctx') ctx1) (Assignment (Index ctx') ctx2) Source #
Static indexing and lenses for assignments
field :: forall n ctx f r. Idx n ctx r => Lens' (Assignment f ctx) (f r) Source #
Get a lens for an position in an Assignment
by zero-based, left-to-right position.
The position must be specified using TypeApplications
for the n
parameter.
natIndexProxy :: forall n ctx r proxy. Idx n ctx r => proxy n -> Index ctx r Source #
This version of natIndex
is suitable for use without the TypeApplications
extension.
Currying and uncurrying for assignments
type family CurryAssignment (ctx :: Ctx k) (f :: k -> *) (x :: *) :: * where ... Source #
This type family is used to define currying/uncurrying operations on assignments. It is best understood by seeing its evaluation on several examples:
CurryAssignment EmptyCtx f x = x CurryAssignment (EmptyCtx ::> a) f x = f a -> x CurryAssignment (EmptyCtx ::> a ::> b) f x = f a -> f b -> x CurryAssignment (EmptyCtx ::> a ::> b ::> c) f x = f a -> f b -> f c -> x
CurryAssignment EmptyCtx f x = x | |
CurryAssignment (ctx ::> a) f x = CurryAssignment ctx f (f a -> x) |
class CurryAssignmentClass (ctx :: Ctx k) where Source #
This class implements two methods that witness the isomorphism between curried and uncurried functions.
curryAssignment :: (Assignment f ctx -> x) -> CurryAssignment ctx f x Source #
Transform a function that accepts an assignment into one with a separate variable for each element of the assignment.
uncurryAssignment :: CurryAssignment ctx f x -> Assignment f ctx -> x Source #
Transform a curried function into one that accepts an assignment value.
Instances
CurryAssignmentClass (EmptyCtx :: Ctx k) Source # | |
Defined in Data.Parameterized.Context curryAssignment :: forall (f :: k0 -> Type) x. (Assignment f EmptyCtx -> x) -> CurryAssignment EmptyCtx f x Source # uncurryAssignment :: forall (f :: k0 -> Type) x. CurryAssignment EmptyCtx f x -> Assignment f EmptyCtx -> x Source # | |
CurryAssignmentClass ctx => CurryAssignmentClass (ctx ::> a :: Ctx k) Source # | |
Defined in Data.Parameterized.Context curryAssignment :: forall (f :: k0 -> Type) x. (Assignment f (ctx ::> a) -> x) -> CurryAssignment (ctx ::> a) f x Source # uncurryAssignment :: forall (f :: k0 -> Type) x. CurryAssignment (ctx ::> a) f x -> Assignment f (ctx ::> a) -> x Source # |