Safe Haskell | Trustworthy |
---|---|
Language | Haskell98 |
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
- 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
- extendIndex :: KnownDiff l r => Index l tp -> Index r tp
- extendIndex' :: Diff l r -> Index l tp -> Index 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 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)
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
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.
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' :: 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 | |
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.
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-1)
otherwise.
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.
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 #