Copyright | (c) Galois Inc 2014-2015 |
---|---|
Maintainer | Joe Hendrix <jhendrix@galois.com> |
Safe Haskell | None |
Language | Haskell98 |
This module defines type contexts as a data-kind that consists of a list of types. Indexes are defined with respect to these contexts. In addition, finite dependent products (Assignments) are defined over type contexts. The elements of an assignment can be accessed using appropriately-typed indexes.
This module is intended to export exactly the same API as module Data.Parameterized.Context.Unsafe, so that they can be used interchangeably.
This implementation is entirely typesafe, and provides a proof that the signature implemented by this module is consistent. Contexts, indexes, and assignments are represented naively by linear sequences.
Compared to the implementation in Data.Parameterized.Context.Unsafe,
this one suffers from the fact that the operation of extending an
the context of an index is not a no-op. We therefore cannot use
coerce
to understand indexes in a new context without
actually breaking things.
- module Data.Parameterized.Ctx
- 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
- class KnownContext (ctx :: Ctx k) where
- data Diff (l :: Ctx k) (r :: Ctx k)
- noDiff :: Diff l l
- extendRight :: Diff l r -> Diff l (r ::> tp)
- class KnownDiff (l :: Ctx k) (r :: Ctx k) where
- data DiffView a b where
- viewDiff :: Diff a b -> DiffView a b
- data Index (ctx :: Ctx k) (tp :: k)
- indexVal :: Index ctx tp -> Int
- base :: Index (EmptyCtx ::> tp) tp
- skip :: 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
- intIndex :: Int -> Size ctx -> Maybe (Some (Index ctx))
- data Assignment (f :: k -> *) (ctx :: Ctx k)
- size :: Assignment f ctx -> Size ctx
- replicate :: Size ctx -> (forall tp. f tp) -> Assignment f ctx
- generate :: forall ctx f. Size ctx -> (forall tp. Index ctx tp -> f tp) -> Assignment f ctx
- generateM :: forall ctx m f. Applicative m => Size ctx -> (forall tp. Index ctx tp -> m (f tp)) -> m (Assignment f ctx)
- empty :: Assignment f EmptyCtx
- null :: Assignment f ctx -> Bool
- extend :: Assignment f ctx -> f tp -> Assignment f (ctx ::> tp)
- update :: Index ctx tp -> f tp -> Assignment f ctx -> Assignment f ctx
- adjust :: forall f ctx tp. (f tp -> f tp) -> Index ctx tp -> Assignment f ctx -> Assignment f ctx
- adjustM :: forall m f ctx tp. Functor m => (f tp -> m (f tp)) -> Index ctx tp -> Assignment f ctx -> m (Assignment f ctx)
- init :: Assignment f (ctx ::> tp) -> Assignment f ctx
- data AssignView (f :: k -> *) (ctx :: Ctx k) where
- AssignEmpty :: AssignView f EmptyCtx
- AssignExtend :: Assignment f ctx -> f tp -> AssignView f (ctx ::> tp)
- view :: forall f ctx. Assignment f ctx -> AssignView f ctx
- decompose :: Assignment f (ctx ::> tp) -> (Assignment f ctx, f tp)
- (!) :: Assignment f ctx -> Index ctx tp -> f tp
- (!^) :: KnownDiff l r => Assignment f r -> Index l tp -> f tp
- toList :: (forall tp. f tp -> a) -> Assignment f c -> [a]
- zipWith :: (forall x. f x -> g x -> h x) -> Assignment f a -> Assignment g a -> Assignment h a
- zipWithM :: Applicative m => (forall tp. f tp -> g tp -> m (h tp)) -> Assignment f c -> Assignment g c -> m (Assignment h c)
- (<++>) :: 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.
KnownContext k (EmptyCtx k) Source # | |
KnownContext k ctx => KnownContext k ((::>) k ctx tp) Source # | |
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.
Indexing
data Index (ctx :: Ctx k) (tp :: k) Source #
An index is a reference to a position with a particular type in a context.
indexVal :: Index ctx tp -> Int Source #
Convert an index to an Int
, where the index of the left-most type in the context is 0.
nextIndex :: Size ctx -> Index (ctx ::> tp) tp Source #
Return the index of an 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
,
forIndex n v0 f
calls f
on each index less than n
starting
from 0
and v0
, with the value v
obtained from the last call.
intIndex :: Int -> Size ctx -> Maybe (Some (Index ctx)) Source #
Return index at given integer or nothing if integer is out of bounds.
Assignments
data Assignment (f :: k -> *) (ctx :: Ctx k) Source #
An assignment is a sequence that maps each index with type tp
to
a value of type 'f tp'.
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 :: forall ctx f. Size ctx -> (forall tp. Index ctx tp -> f tp) -> Assignment f ctx Source #
Generate an assignment
generateM :: forall ctx m f. Applicative m => Size ctx -> (forall tp. Index ctx tp -> m (f tp)) -> m (Assignment f ctx) Source #
Generate an assignment
empty :: Assignment f EmptyCtx Source #
Create empty indexec vector.
null :: Assignment f ctx -> Bool Source #
Return true if assignment is empty.
extend :: Assignment f ctx -> f tp -> Assignment f (ctx ::> tp) Source #
update :: Index ctx tp -> f tp -> Assignment f ctx -> Assignment f ctx Source #
adjust :: forall f ctx tp. (f tp -> f tp) -> Index ctx tp -> Assignment f ctx -> Assignment f ctx Source #
adjustM :: forall m f ctx tp. Functor m => (f tp -> m (f tp)) -> Index ctx tp -> Assignment f ctx -> m (Assignment f ctx) Source #
init :: Assignment f (ctx ::> tp) -> Assignment f ctx Source #
Return assignment with all but the last block.
data AssignView (f :: k -> *) (ctx :: Ctx k) where Source #
View 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) |
view :: forall f ctx. Assignment f ctx -> AssignView f ctx Source #
decompose :: Assignment f (ctx ::> tp) -> (Assignment f ctx, f tp) Source #
(!) :: 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.
toList :: (forall tp. f tp -> a) -> Assignment f c -> [a] Source #
Convert assignment to list.
zipWith :: (forall x. f x -> g x -> h x) -> Assignment f a -> Assignment g a -> Assignment h a Source #
zipWithM :: Applicative m => (forall tp. f tp -> g tp -> m (h tp)) -> Assignment f c -> Assignment g c -> m (Assignment h c) 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 #