Copyright | (c) Fumiaki Kinoshita 2018 |
---|---|
License | BSD3 |
Maintainer | Fumiaki Kinoshita <fumiexcel@gmail.com> |
Safe Haskell | Trustworthy |
Language | Haskell2010 |
Synopsis
- data (h :: k -> *) :* (s :: [k])
- nil :: h :* '[]
- (<:) :: h x -> (h :* xs) -> h :* (x ': xs)
- (<!) :: h x -> (h :* xs) -> h :* (x ': xs)
- (=<:) :: Wrapper h => Repr h x -> (h :* xs) -> h :* (x ': xs)
- hlength :: (h :* xs) -> Int
- type family (xs :: [k]) ++ (ys :: [k]) :: [k] where ...
- happend :: (h :* xs) -> (h :* ys) -> h :* (xs ++ ys)
- hmap :: (forall x. g x -> h x) -> (g :* xs) -> h :* xs
- hmapWithIndex :: (forall x. Membership xs x -> g x -> h x) -> (g :* xs) -> h :* xs
- hmapWithIndexFor :: Forall c xs => proxy c -> (forall x. c x => Membership xs x -> g x -> h x) -> (g :* xs) -> h :* xs
- hzipWith :: (forall x. f x -> g x -> h x) -> (f :* xs) -> (g :* xs) -> h :* xs
- hzipWith3 :: (forall x. f x -> g x -> h x -> i x) -> (f :* xs) -> (g :* xs) -> (h :* xs) -> i :* xs
- hfoldMap :: Monoid a => (forall x. h x -> a) -> (h :* xs) -> a
- hfoldMapWithIndex :: Monoid a => (forall x. Membership xs x -> g x -> a) -> (g :* xs) -> a
- hfoldrWithIndex :: (forall x. Membership xs x -> h x -> r -> r) -> r -> (h :* xs) -> r
- hfoldlWithIndex :: (forall x. Membership xs x -> r -> h x -> r) -> r -> (h :* xs) -> r
- htraverse :: Applicative f => (forall x. g x -> f (h x)) -> (g :* xs) -> f (h :* xs)
- htraverseWithIndex :: Applicative f => (forall x. Membership xs x -> g x -> f (h x)) -> (g :* xs) -> f (h :* xs)
- hsequence :: Applicative f => (Comp f h :* xs) -> f (h :* xs)
- hfoldMapFor :: (Forall c xs, Monoid a) => proxy c -> (forall x. c x => h x -> a) -> (h :* xs) -> a
- hfoldMapWithIndexFor :: (Forall c xs, Monoid a) => proxy c -> (forall x. c x => Membership xs x -> h x -> a) -> (h :* xs) -> a
- hfoldrWithIndexFor :: Forall c xs => proxy c -> (forall x. c x => Membership xs x -> h x -> r -> r) -> r -> (h :* xs) -> r
- hfoldlWithIndexFor :: Forall c xs => proxy c -> (forall x. c x => Membership xs x -> r -> h x -> r) -> r -> (h :* xs) -> r
- hforce :: (h :* xs) -> h :* xs
- haccumMap :: Foldable f => (a -> g :| xs) -> (forall x. Membership xs x -> g x -> h x -> h x) -> (h :* xs) -> f a -> h :* xs
- haccum :: Foldable f => (forall x. Membership xs x -> g x -> h x -> h x) -> (h :* xs) -> f (g :| xs) -> h :* xs
- hpartition :: (Foldable f, Generate xs) => (a -> h :| xs) -> f a -> Comp [] h :* xs
- hlookup :: Membership xs x -> (h :* xs) -> h x
- hindex :: (h :* xs) -> Membership xs x -> h x
- class Generate (xs :: [k]) where
- henumerate :: (forall x. Membership xs x -> r -> r) -> r -> r
- hcount :: proxy xs -> Int
- hgenerateList :: Applicative f => (forall x. Membership xs x -> f (h x)) -> f (HList h xs)
- hgenerate :: (Generate xs, Applicative f) => (forall x. Membership xs x -> f (h x)) -> f (h :* xs)
- htabulate :: Generate xs => (forall x. Membership xs x -> h x) -> h :* xs
- hrepeat :: Generate xs => (forall x. h x) -> h :* xs
- hcollect :: (Functor f, Generate xs) => (a -> h :* xs) -> f a -> Comp f h :* xs
- hdistribute :: (Functor f, Generate xs) => f (h :* xs) -> Comp f h :* xs
- fromHList :: HList h xs -> h :* xs
- toHList :: forall h xs. (h :* xs) -> HList h xs
- class (ForallF c xs, Generate xs) => Forall (c :: k -> Constraint) (xs :: [k]) where
- henumerateFor :: proxy c -> proxy' xs -> (forall x. c x => Membership xs x -> r -> r) -> r -> r
- hgenerateListFor :: Applicative f => proxy c -> (forall x. c x => Membership xs x -> f (h x)) -> f (HList h xs)
- hgenerateFor :: (Forall c xs, Applicative f) => proxy c -> (forall x. c x => Membership xs x -> f (h x)) -> f (h :* xs)
- htabulateFor :: Forall c xs => proxy c -> (forall x. c x => Membership xs x -> h x) -> h :* xs
- hrepeatFor :: Forall c xs => proxy c -> (forall x. c x => h x) -> h :* xs
Basic operations
data (h :: k -> *) :* (s :: [k]) Source #
The type of extensible products.
(:*) :: (k -> *) -> [k] -> *
Instances
(<:) :: h x -> (h :* xs) -> h :* (x ': xs) infixr 0 Source #
O(n) Prepend an element onto a product.
Expressions like a <: b <: c <: nil
are transformed to a single fromHList
.
type family (xs :: [k]) ++ (ys :: [k]) :: [k] where ... infixr 5 Source #
Concatenate type level lists
hmapWithIndex :: (forall x. Membership xs x -> g x -> h x) -> (g :* xs) -> h :* xs Source #
Map a function to every element of a product.
hmapWithIndexFor :: Forall c xs => proxy c -> (forall x. c x => Membership xs x -> g x -> h x) -> (g :* xs) -> h :* xs Source #
Map a function to every element of a product.
hzipWith :: (forall x. f x -> g x -> h x) -> (f :* xs) -> (g :* xs) -> h :* xs Source #
zipWith
for heterogeneous product
hzipWith3 :: (forall x. f x -> g x -> h x -> i x) -> (f :* xs) -> (g :* xs) -> (h :* xs) -> i :* xs Source #
zipWith3
for heterogeneous product
hfoldMapWithIndex :: Monoid a => (forall x. Membership xs x -> g x -> a) -> (g :* xs) -> a Source #
hfoldMap
with the membership of elements.
hfoldrWithIndex :: (forall x. Membership xs x -> h x -> r -> r) -> r -> (h :* xs) -> r Source #
Right-associative fold of a product.
hfoldlWithIndex :: (forall x. Membership xs x -> r -> h x -> r) -> r -> (h :* xs) -> r Source #
Perform a strict left fold over the elements.
htraverse :: Applicative f => (forall x. g x -> f (h x)) -> (g :* xs) -> f (h :* xs) Source #
Traverse all elements and combine the result sequentially.
htraverse (fmap f . g) ≡ fmap (hmap f) . htraverse g
htraverse pure ≡ pure
htraverse (Comp . fmap g . f) ≡ Comp . fmap (htraverse g) . htraverse f
htraverseWithIndex :: Applicative f => (forall x. Membership xs x -> g x -> f (h x)) -> (g :* xs) -> f (h :* xs) Source #
htraverse
with Membership
s.
hsequence :: Applicative f => (Comp f h :* xs) -> f (h :* xs) Source #
sequence
analog for extensible products
Constrained fold
hfoldMapFor :: (Forall c xs, Monoid a) => proxy c -> (forall x. c x => h x -> a) -> (h :* xs) -> a Source #
Constrained hfoldMap
hfoldMapWithIndexFor :: (Forall c xs, Monoid a) => proxy c -> (forall x. c x => Membership xs x -> h x -> a) -> (h :* xs) -> a Source #
hfoldMapWithIndex
with a constraint for each element.
hfoldrWithIndexFor :: Forall c xs => proxy c -> (forall x. c x => Membership xs x -> h x -> r -> r) -> r -> (h :* xs) -> r Source #
hfoldrWithIndex
with a constraint for each element.
hfoldlWithIndexFor :: Forall c xs => proxy c -> (forall x. c x => Membership xs x -> r -> h x -> r) -> r -> (h :* xs) -> r Source #
Constrained hfoldlWithIndex
Evaluating
Update
haccumMap :: Foldable f => (a -> g :| xs) -> (forall x. Membership xs x -> g x -> h x -> h x) -> (h :* xs) -> f a -> h :* xs Source #
Accumulate sums on a product.
haccum :: Foldable f => (forall x. Membership xs x -> g x -> h x -> h x) -> (h :* xs) -> f (g :| xs) -> h :* xs Source #
hpartition :: (Foldable f, Generate xs) => (a -> h :| xs) -> f a -> Comp [] h :* xs Source #
Group sums by type.
Lookup
hlookup :: Membership xs x -> (h :* xs) -> h x Source #
Get an element in a product.
Generation
class Generate (xs :: [k]) where Source #
Every type-level list is an instance of Generate
.
henumerate :: (forall x. Membership xs x -> r -> r) -> r -> r Source #
Enumerate all possible Membership
s of xs
.
hcount :: proxy xs -> Int Source #
Count the number of memberships.
hgenerateList :: Applicative f => (forall x. Membership xs x -> f (h x)) -> f (HList h xs) Source #
Enumerate Membership
s and construct an HList
.
Instances
Generate ([] :: [k]) Source # | |
Defined in Data.Extensible.Class henumerate :: (forall (x :: k0). Membership [] x -> r -> r) -> r -> r Source # hcount :: proxy [] -> Int Source # hgenerateList :: Applicative f => (forall (x :: k0). Membership [] x -> f (h x)) -> f (HList h []) Source # | |
Generate xs => Generate (x ': xs :: [k]) Source # | |
Defined in Data.Extensible.Class henumerate :: (forall (x0 :: k0). Membership (x ': xs) x0 -> r -> r) -> r -> r Source # hcount :: proxy (x ': xs) -> Int Source # hgenerateList :: Applicative f => (forall (x0 :: k0). Membership (x ': xs) x0 -> f (h x0)) -> f (HList h (x ': xs)) Source # |
hgenerate :: (Generate xs, Applicative f) => (forall x. Membership xs x -> f (h x)) -> f (h :* xs) Source #
Applicative
version of htabulate
.
hrepeat :: Generate xs => (forall x. h x) -> h :* xs Source #
A product filled with the specified value.
hcollect :: (Functor f, Generate xs) => (a -> h :* xs) -> f a -> Comp f h :* xs Source #
The dual of htraverse
hdistribute :: (Functor f, Generate xs) => f (h :* xs) -> Comp f h :* xs Source #
The dual of hsequence
class (ForallF c xs, Generate xs) => Forall (c :: k -> Constraint) (xs :: [k]) where Source #
Every element in xs
satisfies c
henumerateFor :: proxy c -> proxy' xs -> (forall x. c x => Membership xs x -> r -> r) -> r -> r Source #
Enumerate all possible Membership
s of xs
with an additional context.
hgenerateListFor :: Applicative f => proxy c -> (forall x. c x => Membership xs x -> f (h x)) -> f (HList h xs) Source #
Instances
Forall (c :: k -> Constraint) ([] :: [k]) Source # | |
Defined in Data.Extensible.Class henumerateFor :: proxy c -> proxy' [] -> (forall (x :: k0). c x => Membership [] x -> r -> r) -> r -> r Source # hgenerateListFor :: Applicative f => proxy c -> (forall (x :: k0). c x => Membership [] x -> f (h x)) -> f (HList h []) Source # | |
(c x, Forall c xs) => Forall (c :: a -> Constraint) (x ': xs :: [a]) Source # | |
Defined in Data.Extensible.Class henumerateFor :: proxy c -> proxy' (x ': xs) -> (forall (x0 :: k). c x0 => Membership (x ': xs) x0 -> r -> r) -> r -> r Source # hgenerateListFor :: Applicative f => proxy c -> (forall (x0 :: k). c x0 => Membership (x ': xs) x0 -> f (h x0)) -> f (HList h (x ': xs)) Source # |
hgenerateFor :: (Forall c xs, Applicative f) => proxy c -> (forall x. c x => Membership xs x -> f (h x)) -> f (h :* xs) Source #
Applicative
version of htabulateFor
.
htabulateFor :: Forall c xs => proxy c -> (forall x. c x => Membership xs x -> h x) -> h :* xs Source #
Pure version of hgenerateFor
.
hrepeatFor :: Forall c xs => proxy c -> (forall x. c x => h x) -> h :* xs Source #
A product filled with the specified value.