| Copyright | (c) Fumiaki Kinoshita 2015 | 
|---|---|
| License | BSD3 | 
| Maintainer | Fumiaki Kinoshita <fumiexcel@gmail.com> | 
| Stability | experimental | 
| Portability | non-portable | 
| Safe Haskell | None | 
| Language | Haskell2010 | 
Data.Extensible.Product
Contents
Description
- data h :* s where
- (<:) :: h x -> (h :* xs) -> h :* (x : xs)
- (<:*) :: forall h x xs. h x -> (h :* xs) -> h :* (x : xs)
- (*++*) :: (h :* xs) -> (h :* ys) -> h :* (xs ++ ys)
- hhead :: (h :* (x : xs)) -> h x
- htail :: (h :* (x : xs)) -> h :* xs
- huncons :: forall h x xs. (h :* (x : xs)) -> (h x, h :* xs)
- hmap :: (forall x. g x -> h x) -> (g :* xs) -> h :* xs
- hmapWithIndex :: forall g h xs. (forall x. Membership xs x -> g x -> h x) -> (g :* xs) -> h :* xs
- htrans :: (forall x. g x -> h (t x)) -> (g :* xs) -> h :* Map t 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
- htraverse :: Applicative f => (forall x. g x -> f (h x)) -> (g :* xs) -> f (h :* xs)
- hsequence :: Applicative f => (Comp f h :* xs) -> f (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
- hlookup :: Membership xs x -> (h :* xs) -> h x
- hindex :: (h :* xs) -> Membership xs x -> h x
- sector :: forall h x xs. x ∈ xs => Lens' (h :* xs) (h x)
- sectorAt :: forall f h x xs. Functor f => Membership xs x -> (h x -> f (h x)) -> (h :* xs) -> f (h :* xs)
- class Generate xs where- hgenerate :: 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
- class Forall c xs where- hgenerateFor :: 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
Basic operations
The extensible product type
Constructors
| Nil :: h :* [] | |
| Tree :: !(h x) -> (h :* Half xs) -> (h :* Half (Tail xs)) -> h :* (x : xs) | 
Instances
| Typeable ((k -> *) -> [k] -> *) ((:*) k) | |
| WrapForall k * Eq h xs => Eq ((:*) k h xs) | |
| (Eq ((:*) k h xs), WrapForall k * Ord h xs) => Ord ((:*) k h xs) | |
| WrapForall k * Show h xs => Show ((:*) k h xs) | |
| WrapForall k * Monoid h xs => Monoid ((:*) k h xs) | |
| WrapForall k * Binary h xs => Binary ((:*) k h xs) | 
huncons :: forall h x xs. (h :* (x : xs)) -> (h x, h :* xs) Source
Split a product to the head and the tail.
hmapWithIndex :: forall g h xs. (forall x. Membership xs x -> g x -> h x) -> (g :* xs) -> h :* xs Source
hmap with its indices.
htrans :: (forall x. g x -> h (t x)) -> (g :* xs) -> h :* Map t xs Source
Transform every elements in a product, preserving the order.
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
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
 
hsequence :: Applicative f => (Comp f h :* xs) -> f (h :* xs) Source
sequence analog for extensible products
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
Lookup
hlookup :: Membership xs x -> (h :* xs) -> h x Source
O(log n) Pick up an elemtnt.
hindex :: (h :* xs) -> Membership xs x -> h x Source
Flipped hlookup
sector :: forall h x xs. x ∈ xs => Lens' (h :* xs) (h x) Source
O(log n) A lens for a specific element.
sectorAt :: forall f h x xs. Functor f => Membership xs x -> (h x -> f (h x)) -> (h :* xs) -> f (h :* xs) Source
O(log n) A lens for a value in a known position.
Generation
class Generate xs where Source
Given a function that maps types to values, we can "collect" entities all you want.
Methods
hgenerate :: Applicative f => (forall x. Membership xs x -> f (h x)) -> f (h :* xs) Source
O(n) htabulates a product with the given function.
htabulate :: Generate xs => (forall x. Membership xs x -> h x) -> h :* xs Source
class Forall c xs where Source
Guarantees the all elements satisfies the predicate.
Methods
hgenerateFor :: Applicative f => proxy c -> (forall x. c x => Membership xs x -> f (h x)) -> f (h :* xs) Source
O(n) Analogous to htabulate, but it also supplies a context c x for every elements in xs.
htabulateFor :: Forall c xs => proxy c -> (forall x. c x => Membership xs x -> h x) -> h :* xs Source
Pure version of hgenerateFor.