Copyright | (c) Galois Inc 2017-2019 |
---|---|
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
.
Synopsis
- 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
- izipWith :: forall a b c sh. (forall tp. Index sh tp -> a tp -> b tp -> c tp) -> List a sh -> List b sh -> List c sh
- 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.
Instances
TraversableFC (List :: (k -> Type) -> [k] -> Type) Source # | |
Defined in Data.Parameterized.List traverseFC :: Applicative m => (forall (x :: k0). f x -> m (g x)) -> forall (x :: l). List f x -> m (List g x) Source # | |
FoldableFC (List :: (k -> Type) -> [k] -> Type) Source # | |
Defined in Data.Parameterized.List foldMapFC :: Monoid m => (forall (x :: k0). f x -> m) -> forall (x :: l). List f x -> m Source # foldrFC :: (forall (x :: k0). f x -> b -> b) -> forall (x :: l). b -> List f x -> b Source # foldlFC :: (forall (x :: k0). b -> f x -> b) -> forall (x :: l). b -> List f x -> b Source # foldrFC' :: (forall (x :: k0). f x -> b -> b) -> forall (x :: l). b -> List f x -> b Source # foldlFC' :: (forall (x :: k0). b -> f x -> b) -> forall (x :: l). b -> List f x -> b Source # toListFC :: (forall (x :: k0). f x -> a) -> forall (x :: l). List f x -> [a] Source # | |
FunctorFC (List :: (k -> Type) -> [k] -> Type) Source # | |
TestEquality f => TestEquality (List f :: [k] -> Type) Source # | |
Defined in Data.Parameterized.List | |
ShowF f => ShowF (List f :: [k] -> Type) Source # | |
OrdF f => OrdF (List f :: [k] -> Type) Source # | |
IsRepr f => IsRepr (List f :: [k] -> Type) Source # | |
KnownRepr (List f :: [k] -> Type) ([] :: [k]) Source # | |
Defined in Data.Parameterized.List | |
(KnownRepr f s, KnownRepr (List f) sh) => KnownRepr (List f :: [a] -> Type) (s ': sh :: [a]) Source # | |
Defined in Data.Parameterized.List | |
ShowF f => Show (List 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 |
Instances
TestEquality (Index l :: k -> Type) Source # | |
Defined in Data.Parameterized.List | |
ShowF (Index l :: k -> Type) Source # | |
OrdF (Index l :: k -> Type) Source # | |
Eq (Index l x) Source # | |
Ord (Index sh x) Source # | |
Show (Index l x) Source # | |
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.
izipWith :: forall a b c sh. (forall tp. Index sh tp -> a tp -> b tp -> c tp) -> List a sh -> List b sh -> List c sh Source #
Zip up two lists with a zipper function, which can use the 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.