extensible-0.2.9: Extensible, efficient, lens-friendly data types

Copyright(c) Fumiaki Kinoshita 2015
LicenseBSD3
MaintainerFumiaki Kinoshita <fumiexcel@gmail.com>
Stabilityexperimental
Portabilitynon-portable
Safe HaskellNone
LanguageHaskell2010

Data.Extensible.Product

Contents

Description

 

Synopsis

Basic operations

data h :* s where Source

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) 

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

O(log n) Add an element to a product.

(<:*) :: forall h x xs. h x -> (h :* xs) -> h :* (x : xs) infixr 0 Source

An alias for (<:).

(*++*) :: (h :* xs) -> (h :* ys) -> h :* (xs ++ ys) infixr 0 Source

Combine products.

hhead :: (h :* (x : xs)) -> h x Source

O(1) Extract the head element.

htail :: (h :* (x : xs)) -> h :* xs Source

O(n) Extract the tail of the product. FIXME: unsafeCoerce

huncons :: forall h x xs. (h :* (x : xs)) -> (h x, h :* xs) Source

Split a product to the head and the tail.

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

Transform every elements in a product, preserving the order.

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

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

Combine all elements.

htraverse :: Applicative f => (forall x. h x -> f (h x)) -> (h :* xs) -> f (h :* xs) Source

Traverse all elements.

htabulate :: forall g h xs. (forall x. Membership xs x -> g x -> h x) -> (g :* xs) -> h :* xs Source

hmap with its indices.

Lookup

hlookup :: Membership xs x -> (h :* xs) -> h x Source

O(log n) Pick up an elemtnt.

sector :: 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

generateA :: Applicative f => (forall x. Membership xs x -> f (h x)) -> f (h :* xs) Source

O(n) generates a product with the given function.

Instances

Generate k ([] k) 
(Generate k (Half k xs), Generate k (Half k (Tail k xs))) => Generate k ((:) k x xs) 

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

Pure version of generateA.

class Forall c xs where Source

Guarantees the all elements satisfies the predicate.

Methods

generateForA :: Applicative f => proxy c -> (forall x. c x => Membership xs x -> f (h x)) -> f (h :* xs) Source

O(n) Analogous to generate, but it also supplies a context c x for every elements in xs.

Instances

Forall k c ([] k) 
(c x, Forall k c (Half k xs), Forall k c (Half k (Tail k xs))) => Forall k c ((:) k x xs) 

generateFor :: Forall c xs => proxy c -> (forall x. c x => Membership xs x -> h x) -> h :* xs Source

Pure version of generateForA.

HList

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

Build a product from HList.

toHList :: (h :* xs) -> HList h xs Source

Turn a product into HList.