Copyright | (c) Galois Inc 2017 |
---|---|
Maintainer | Joe Hendrix <jhendrix@galois.com> |
Safe Haskell | Safe |
Language | Haskell98 |
This module defines a list over two parameters. The first
is a fixed type-level function k -> *
for some kind k
, and the
second is a list of types with kind k that provide the indices for
the values in the list.
This type is closely related to the Context
type in
Data.Parameterized.Context
.
- data List :: (k -> *) -> [k] -> * where
- data Index :: [k] -> k -> * where
- IndexHere :: Index (x ': r) x
- IndexThere :: !(Index r y) -> Index (x ': r) y
- indexValue :: Index l tp -> Integer
- (!!) :: List f l -> Index l x -> f x
- update :: List f l -> Index l s -> (f s -> f s) -> List f l
- indexed :: Index l x -> Simple Lens (List f l) (f x)
- imap :: forall f g l. (forall x. Index l x -> f x -> g x) -> List f l -> List g l
- ifoldr :: forall sh a b. (forall tp. Index sh tp -> a tp -> b -> b) -> b -> List a sh -> b
- itraverse :: forall a b sh t. Applicative t => (forall tp. Index sh tp -> a tp -> t (b tp)) -> List a sh -> t (List b sh)
- index0 :: Index (x ': r) x
- index1 :: Index (x0 ': (x1 ': r)) x1
- index2 :: Index (x0 ': (x1 ': (x2 ': r))) x2
- index3 :: Index (x0 ': (x1 ': (x2 ': (x3 ': r)))) x3
Documentation
data List :: (k -> *) -> [k] -> * where Source #
Parameterized list of elements.
TraversableFC k [k] (List k) Source # | |
FoldableFC k [k] (List k) Source # | |
FunctorFC k [k] (List k) Source # | |
TestEquality k f => TestEquality [k] (List k f) Source # | |
ShowF k f => ShowF [k] (List k f) Source # | |
OrdF k f => OrdF [k] (List k f) Source # | |
KnownRepr [k] (List k f) ([] k) Source # | |
(KnownRepr a f s, KnownRepr [a] (List a f) sh) => KnownRepr [a] (List a f) ((:) a s sh) Source # | |
ShowF k f => Show (List k f sh) Source # | |
data Index :: [k] -> k -> * where Source #
Represents an index into a type-level list. Used in place of integers to 1. ensure that the given index *does* exist in the list 2. guarantee that it has the given kind
IndexHere :: Index (x ': r) x | |
IndexThere :: !(Index r y) -> Index (x ': r) y |
indexValue :: Index l tp -> Integer Source #
Return the index as an integer.
indexed :: Index l x -> Simple Lens (List f l) (f x) Source #
Provides a lens for manipulating the element at the given index.
imap :: forall f g l. (forall x. Index l x -> f x -> g x) -> List f l -> List g l Source #
Map over the elements in the list, and provide the index into each element along with the element itself.
ifoldr :: forall sh a b. (forall tp. Index sh tp -> a tp -> b -> b) -> b -> List a sh -> b Source #
Right-fold with an additional index.
itraverse :: forall a b sh t. Applicative t => (forall tp. Index sh tp -> a tp -> t (b tp)) -> List a sh -> t (List b sh) Source #
Traverse with an additional index.