extensible-0.4.7.1: Extensible, efficient, optics-friendly data types and effects

Copyright(c) Fumiaki Kinoshita 2017
LicenseBSD3
MaintainerFumiaki Kinoshita <fumiexcel@gmail.com>
Safe HaskellTrustworthy
LanguageHaskell2010

Data.Extensible.Product

Contents

Description

 

Synopsis

Basic operations

data (h :: k -> *) :* (s :: [k]) Source #

The type of extensible products.

(:*) :: (k -> *) -> [k] -> *

Instances

(Corepresentable p, Comonad (Corep p), Functor f) => Extensible k f p ((:*) k) Source # 

Associated Types

type ExtensibleConstr f (t :: (f -> *) -> [f] -> *) (h :: f -> *) (xs :: [f]) (x :: f) :: Constraint Source #

Methods

pieceAt :: ExtensibleConstr f t h xs x => Membership f xs x -> Optic' * * ((:*) k) p (t h xs) (h x) Source #

type ExtensibleConstr k ((:*) k) h xs x Source # 
type ExtensibleConstr k ((:*) k) h xs x = ()
data MVector s ((:*) k h xs) # 
data MVector s ((:*) k h xs) = MV_Product ((:*) k (Comp * k (MVector s) h) xs)
data Vector ((:*) k h xs) # 
data Vector ((:*) k h xs) = V_Product ((:*) k (Comp * k Vector h) xs)

nil :: h :* '[] Source #

An empty product.

(<:) :: 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.

(<!) :: h x -> (h :* xs) -> h :* (x ': xs) infixr 0 Source #

Strict version of (<:).

hlength :: (h :* xs) -> Int Source #

The size of a product.

type family (xs :: [k]) ++ (ys :: [k]) :: [k] where ... infixr 5 Source #

Equations

'[] ++ ys = ys 
(x ': xs) ++ ys = x ': (xs ++ ys) 

happend :: (h :* xs) -> (h :* ys) -> h :* (xs ++ ys) Source #

Combine products.

hmap :: (forall x. g x -> h x) -> (g :* xs) -> h :* xs Source #

Transform every element in a product, preserving the order.

hmap idid
hmap (f . g) ≡ hmap f . hmap g

hmapWithIndex :: (forall 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

hfoldMap :: Monoid a => (forall x. h x -> a) -> (h :* xs) -> a Source #

Map elements to a monoid and combine the results.

hfoldMap f . hmap g ≡ hfoldMap (f . g)

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 #

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 #

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 #

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 #

Evaluating

hforce :: (h :* xs) -> h :* xs Source #

Evaluate every element in a product.

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 #

haccum = haccumMap id

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.

hindex :: (h :* xs) -> Membership xs x -> h x Source #

Flipped hlookup

Generation

class Generate (xs :: [k]) where Source #

Every type-level list is an instance of Generate.

Minimal complete definition

henumerate, hcount, hgenerateList

Methods

henumerate :: (forall x. Membership xs x -> r -> r) -> r -> r Source #

Enumerate all possible Memberships 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 Memberships and construct an HList.

Instances

Generate k ([] k) Source # 

Methods

henumerate :: (forall (x :: [k]). Membership [k] xs x -> r -> r) -> r -> r Source #

hcount :: proxy xs -> Int Source #

hgenerateList :: Applicative f => (forall (x :: [k]). Membership [k] xs x -> f (h x)) -> f (HList [k] h xs) Source #

Generate k xs => Generate k ((:) k x xs) Source # 

Methods

henumerate :: (forall (a :: (k ': x) xs). Membership ((k ': x) xs) xs a -> r -> r) -> r -> r Source #

hcount :: proxy xs -> Int Source #

hgenerateList :: Applicative f => (forall (a :: (k ': x) xs). Membership ((k ': x) xs) xs a -> f (h a)) -> f (HList ((k ': x) xs) h xs) Source #

hgenerate :: (Generate xs, Applicative f) => (forall x. Membership xs x -> f (h x)) -> f (h :* xs) Source #

htabulate :: Generate xs => (forall x. Membership xs x -> h x) -> h :* xs Source #

Construct a product using a function which takes a Membership.

hmap f (htabulate g) ≡ htabulate (f . g)
htabulate (hindex m) ≡ m
hindex (htabulate k) ≡ k

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

fromHList :: HList h xs -> h :* xs Source #

Convert HList into a product.

toHList :: forall h xs. (h :* xs) -> HList h xs Source #

Convert a product into an HList.

class (ForallF c xs, Generate xs) => Forall (c :: k -> Constraint) (xs :: [k]) where Source #

Every element in xs satisfies c

Minimal complete definition

henumerateFor, hgenerateListFor

Methods

henumerateFor :: proxy c -> proxy' xs -> (forall x. c x => Membership xs x -> r -> r) -> r -> r Source #

Enumerate all possible Memberships 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 k c ([] k) Source # 

Methods

henumerateFor :: proxy [k] -> proxy' xs -> (forall (x :: c). [k] x => Membership c xs x -> r -> r) -> r -> r Source #

hgenerateListFor :: Applicative f => proxy [k] -> (forall (x :: c). [k] x => Membership c xs x -> f (h x)) -> f (HList c h xs) Source #

(c x, Forall a c xs) => Forall a c ((:) a x xs) Source # 

Methods

henumerateFor :: proxy ((a ': x) xs) -> proxy' xs -> (forall (b :: c). (a ': x) xs b => Membership c xs b -> r -> r) -> r -> r Source #

hgenerateListFor :: Applicative f => proxy ((a ': x) xs) -> (forall (b :: c). (a ': x) xs b => Membership c xs b -> f (h b)) -> f (HList c h xs) Source #

hgenerateFor :: (Forall c xs, Applicative f) => proxy c -> (forall x. c x => Membership xs x -> f (h x)) -> f (h :* xs) Source #

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.