fixed-vector-hetero-0.3.1.2: Generic heterogeneous vectors

Safe HaskellNone
LanguageHaskell98

Data.Vector.HFixed

Contents

Description

Heterogeneous vectors.

Synopsis

HVector type classes

class Arity (Len xs) => Arity xs Source #

Type class for dealing with N-ary function in generic way. Both accum and apply work with accumulator data types which are polymorphic. So it's only possible to write functions which rearrange elements in vector using plain ADT. It's possible to get around it by using GADT as accumulator (See ArityC and function which use it)

This is also somewhat a kitchen sink module. It contains witnesses which could be used to prove type equalities or to bring instance in scope.

Instances

Arity ([] *) Source # 

Methods

accum :: (forall a as. t ((* ': a) as) -> a -> t as) -> (t [*] -> b) -> t [*] -> Fn [*] b Source #

apply :: (forall a as. t ((* ': a) as) -> (a, t as)) -> t [*] -> ContVec [*] Source #

applyM :: Monad m => (forall a as. t ((* ': a) as) -> m (a, t as)) -> t [*] -> m (ContVec [*]) Source #

accumTy :: (forall a as. t ((* ': a) as) -> f a -> t as) -> (t [*] -> b) -> t [*] -> Fn (Wrap * * f [*]) b Source #

applyTy :: (forall a as. t ((* ': a) as) -> (f a, t as)) -> t [*] -> ContVecF * [*] f Source #

arity :: p [*] -> Int Source #

witWrapped :: WitWrapped f [*] Source #

witConcat :: Arity ys => WitConcat [*] ys Source #

witNestedFun :: WitNestedFun [*] ys r Source #

witLenWrap :: WitLenWrap f [*] Source #

Arity xs => Arity ((:) * x xs) Source # 

Methods

accum :: (forall a as. t ((* ': a) as) -> a -> t as) -> (t [*] -> b) -> t ((* ': x) xs) -> Fn ((* ': x) xs) b Source #

apply :: (forall a as. t ((* ': a) as) -> (a, t as)) -> t ((* ': x) xs) -> ContVec ((* ': x) xs) Source #

applyM :: Monad m => (forall a as. t ((* ': a) as) -> m (a, t as)) -> t ((* ': x) xs) -> m (ContVec ((* ': x) xs)) Source #

accumTy :: (forall a as. t ((* ': a) as) -> f a -> t as) -> (t [*] -> b) -> t ((* ': x) xs) -> Fn (Wrap * * f ((* ': x) xs)) b Source #

applyTy :: (forall a as. t ((* ': a) as) -> (f a, t as)) -> t ((* ': x) xs) -> ContVecF * ((* ': x) xs) f Source #

arity :: p ((* ': x) xs) -> Int Source #

witWrapped :: WitWrapped f ((* ': x) xs) Source #

witConcat :: Arity ys => WitConcat ((* ': x) xs) ys Source #

witNestedFun :: WitNestedFun ((* ': x) xs) ys r Source #

witLenWrap :: WitLenWrap f ((* ': x) xs) Source #

class Arity xs => ArityC c xs Source #

Declares that every type in list satisfy constraint c

Minimal complete definition

witAllInstances

Instances

ArityC c ([] *) Source # 
(c x, ArityC c xs) => ArityC c ((:) * x xs) Source # 

Methods

witAllInstances :: WitAllInstances * c ((* ': x) xs) Source #

class Arity (Elems v) => HVector v where Source #

Type class for heterogeneous vectors. Instance should specify way to construct and deconstruct itself

Note that this type class is extremely generic. Almost any single constructor data type could be made instance. It could be monomorphic, it could be polymorphic in some or all fields it doesn't matter. Only law instance should obey is:

inspect v construct = v

Default implementation which uses Generic is provided.

Associated Types

type Elems v :: [*] Source #

Methods

construct :: Fun (Elems v) v Source #

Function for constructing vector

construct :: (Generic v, GHVector (Rep v), GElems (Rep v) ~ Elems v) => Fun (Elems v) v Source #

Function for constructing vector

inspect :: v -> Fun (Elems v) a -> a Source #

Function for deconstruction of vector. It applies vector's elements to N-ary function.

inspect :: (Generic v, GHVector (Rep v), GElems (Rep v) ~ Elems v) => v -> Fun (Elems v) a -> a Source #

Function for deconstruction of vector. It applies vector's elements to N-ary function.

Instances

HVector () Source #

Unit is empty heterogeneous vector

Associated Types

type Elems () :: [*] Source #

Methods

construct :: Fun (Elems ()) () Source #

inspect :: () -> Fun (Elems ()) a -> a Source #

HVector (Complex a) Source # 

Associated Types

type Elems (Complex a) :: [*] Source #

Methods

construct :: Fun (Elems (Complex a)) (Complex a) Source #

inspect :: Complex a -> Fun (Elems (Complex a)) a -> a Source #

Arity xs => HVector (ContVec xs) Source # 

Associated Types

type Elems (ContVec xs) :: [*] Source #

Methods

construct :: Fun (Elems (ContVec xs)) (ContVec xs) Source #

inspect :: ContVec xs -> Fun (Elems (ContVec xs)) a -> a Source #

Arity xs => HVector (VecList xs) Source # 

Associated Types

type Elems (VecList xs) :: [*] Source #

Methods

construct :: Fun (Elems (VecList xs)) (VecList xs) Source #

inspect :: VecList xs -> Fun (Elems (VecList xs)) a -> a Source #

Arity xs => HVector (HVec xs) Source # 

Associated Types

type Elems (HVec xs) :: [*] Source #

Methods

construct :: Fun (Elems (HVec xs)) (HVec xs) Source #

inspect :: HVec xs -> Fun (Elems (HVec xs)) a -> a Source #

HVector (a, b) Source # 

Associated Types

type Elems (a, b) :: [*] Source #

Methods

construct :: Fun (Elems (a, b)) (a, b) Source #

inspect :: (a, b) -> Fun (Elems (a, b)) a -> a Source #

(Unbox n a, HomArity n a) => HVector (Vec n a) Source # 

Associated Types

type Elems (Vec n a) :: [*] Source #

Methods

construct :: Fun (Elems (Vec n a)) (Vec n a) Source #

inspect :: Vec n a -> Fun (Elems (Vec n a)) a -> a Source #

(Storable a, HomArity n a) => HVector (Vec n a) Source # 

Associated Types

type Elems (Vec n a) :: [*] Source #

Methods

construct :: Fun (Elems (Vec n a)) (Vec n a) Source #

inspect :: Vec n a -> Fun (Elems (Vec n a)) a -> a Source #

(Prim a, HomArity n a) => HVector (Vec n a) Source # 

Associated Types

type Elems (Vec n a) :: [*] Source #

Methods

construct :: Fun (Elems (Vec n a)) (Vec n a) Source #

inspect :: Vec n a -> Fun (Elems (Vec n a)) a -> a Source #

HomArity n a => HVector (Vec n a) Source # 

Associated Types

type Elems (Vec n a) :: [*] Source #

Methods

construct :: Fun (Elems (Vec n a)) (Vec n a) Source #

inspect :: Vec n a -> Fun (Elems (Vec n a)) a -> a Source #

(Arity (Wrap * * f xs), Arity xs) => HVector (HVecF xs f) Source #

It's not possible to remove constrain Arity (Wrap f xs) because it's required by superclass and we cannot prove it for all f. witWrapped allow to generate proofs for terms

Associated Types

type Elems (HVecF xs f) :: [*] Source #

Methods

construct :: Fun (Elems (HVecF xs f)) (HVecF xs f) Source #

inspect :: HVecF xs f -> Fun (Elems (HVecF xs f)) a -> a Source #

HVector (a, b, c) Source # 

Associated Types

type Elems (a, b, c) :: [*] Source #

Methods

construct :: Fun (Elems (a, b, c)) (a, b, c) Source #

inspect :: (a, b, c) -> Fun (Elems (a, b, c)) a -> a Source #

HVector (a, b, c, d) Source # 

Associated Types

type Elems (a, b, c, d) :: [*] Source #

Methods

construct :: Fun (Elems (a, b, c, d)) (a, b, c, d) Source #

inspect :: (a, b, c, d) -> Fun (Elems (a, b, c, d)) a -> a Source #

HVector (a, b, c, d, e) Source # 

Associated Types

type Elems (a, b, c, d, e) :: [*] Source #

Methods

construct :: Fun (Elems (a, b, c, d, e)) (a, b, c, d, e) Source #

inspect :: (a, b, c, d, e) -> Fun (Elems (a, b, c, d, e)) a -> a Source #

HVector (a, b, c, d, e, f) Source # 

Associated Types

type Elems (a, b, c, d, e, f) :: [*] Source #

Methods

construct :: Fun (Elems (a, b, c, d, e, f)) (a, b, c, d, e, f) Source #

inspect :: (a, b, c, d, e, f) -> Fun (Elems (a, b, c, d, e, f)) a -> a Source #

HVector (a, b, c, d, e, f, g) Source # 

Associated Types

type Elems (a, b, c, d, e, f, g) :: [*] Source #

Methods

construct :: Fun (Elems (a, b, c, d, e, f, g)) (a, b, c, d, e, f, g) Source #

inspect :: (a, b, c, d, e, f, g) -> Fun (Elems (a, b, c, d, e, f, g)) a -> a Source #

HVector (a, b, c, d, e, f, g, h) Source # 

Associated Types

type Elems (a, b, c, d, e, f, g, h) :: [*] Source #

Methods

construct :: Fun (Elems (a, b, c, d, e, f, g, h)) (a, b, c, d, e, f, g, h) Source #

inspect :: (a, b, c, d, e, f, g, h) -> Fun (Elems (a, b, c, d, e, f, g, h)) a -> a Source #

HVector (a, b, c, d, e, f, g, h, i) Source # 

Associated Types

type Elems (a, b, c, d, e, f, g, h, i) :: [*] Source #

Methods

construct :: Fun (Elems (a, b, c, d, e, f, g, h, i)) (a, b, c, d, e, f, g, h, i) Source #

inspect :: (a, b, c, d, e, f, g, h, i) -> Fun (Elems (a, b, c, d, e, f, g, h, i)) a -> a Source #

HVector (a, b, c, d, e, f, g, h, i, j) Source # 

Associated Types

type Elems (a, b, c, d, e, f, g, h, i, j) :: [*] Source #

Methods

construct :: Fun (Elems (a, b, c, d, e, f, g, h, i, j)) (a, b, c, d, e, f, g, h, i, j) Source #

inspect :: (a, b, c, d, e, f, g, h, i, j) -> Fun (Elems (a, b, c, d, e, f, g, h, i, j)) a -> a Source #

HVector (a, b, c, d, e, f, g, h, i, j, k) Source # 

Associated Types

type Elems (a, b, c, d, e, f, g, h, i, j, k) :: [*] Source #

Methods

construct :: Fun (Elems (a, b, c, d, e, f, g, h, i, j, k)) (a, b, c, d, e, f, g, h, i, j, k) Source #

inspect :: (a, b, c, d, e, f, g, h, i, j, k) -> Fun (Elems (a, b, c, d, e, f, g, h, i, j, k)) a -> a Source #

HVector (a, b, c, d, e, f, g, h, i, j, k, l) Source # 

Associated Types

type Elems (a, b, c, d, e, f, g, h, i, j, k, l) :: [*] Source #

Methods

construct :: Fun (Elems (a, b, c, d, e, f, g, h, i, j, k, l)) (a, b, c, d, e, f, g, h, i, j, k, l) Source #

inspect :: (a, b, c, d, e, f, g, h, i, j, k, l) -> Fun (Elems (a, b, c, d, e, f, g, h, i, j, k, l)) a -> a Source #

HVector (a, b, c, d, e, f, g, h, i, j, k, l, m) Source # 

Associated Types

type Elems (a, b, c, d, e, f, g, h, i, j, k, l, m) :: [*] Source #

Methods

construct :: Fun (Elems (a, b, c, d, e, f, g, h, i, j, k, l, m)) (a, b, c, d, e, f, g, h, i, j, k, l, m) Source #

inspect :: (a, b, c, d, e, f, g, h, i, j, k, l, m) -> Fun (Elems (a, b, c, d, e, f, g, h, i, j, k, l, m)) a -> a Source #

HVector (a, b, c, d, e, f, g, h, i, j, k, l, m, n) Source # 

Associated Types

type Elems (a, b, c, d, e, f, g, h, i, j, k, l, m, n) :: [*] Source #

Methods

construct :: Fun (Elems (a, b, c, d, e, f, g, h, i, j, k, l, m, n)) (a, b, c, d, e, f, g, h, i, j, k, l, m, n) Source #

inspect :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n) -> Fun (Elems (a, b, c, d, e, f, g, h, i, j, k, l, m, n)) a -> a Source #

HVector (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) Source # 

Associated Types

type Elems (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) :: [*] Source #

Methods

construct :: Fun (Elems (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o)) (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) Source #

inspect :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) -> Fun (Elems (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o)) a -> a Source #

HVector (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p) Source # 

Associated Types

type Elems (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p) :: [*] Source #

Methods

construct :: Fun (Elems (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p)) (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p) Source #

inspect :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p) -> Fun (Elems (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p)) a -> a Source #

HVector (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q) Source # 

Associated Types

type Elems (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q) :: [*] Source #

Methods

construct :: Fun (Elems (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q)) (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q) Source #

inspect :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q) -> Fun (Elems (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q)) a -> a Source #

HVector (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r) Source # 

Associated Types

type Elems (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r) :: [*] Source #

Methods

construct :: Fun (Elems (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r)) (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r) Source #

inspect :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r) -> Fun (Elems (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r)) a -> a Source #

HVector (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s) Source # 

Associated Types

type Elems (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s) :: [*] Source #

Methods

construct :: Fun (Elems (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s)) (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s) Source #

inspect :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s) -> Fun (Elems (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s)) a -> a Source #

HVector (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t) Source # 

Associated Types

type Elems (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t) :: [*] Source #

Methods

construct :: Fun (Elems (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t)) (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t) Source #

inspect :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t) -> Fun (Elems (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t)) a -> a Source #

HVector (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u) Source # 

Associated Types

type Elems (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u) :: [*] Source #

Methods

construct :: Fun (Elems (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u)) (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u) Source #

inspect :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u) -> Fun (Elems (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u)) a -> a Source #

HVector (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v) Source # 

Associated Types

type Elems (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v) :: [*] Source #

Methods

construct :: Fun (Elems (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v)) (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v) Source #

inspect :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v) -> Fun (Elems (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v)) a -> a Source #

HVector (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w) Source # 

Associated Types

type Elems (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w) :: [*] Source #

Methods

construct :: Fun (Elems (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w)) (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w) Source #

inspect :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w) -> Fun (Elems (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w)) a -> a Source #

HVector (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x) Source # 

Associated Types

type Elems (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x) :: [*] Source #

Methods

construct :: Fun (Elems (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x)) (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x) Source #

inspect :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x) -> Fun (Elems (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x)) a -> a Source #

HVector (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y) Source # 

Associated Types

type Elems (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y) :: [*] Source #

Methods

construct :: Fun (Elems (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y)) (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y) Source #

inspect :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y) -> Fun (Elems (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y)) a -> a Source #

HVector (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z) Source # 

Associated Types

type Elems (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z) :: [*] Source #

Methods

construct :: Fun (Elems (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z)) (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z) Source #

inspect :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z) -> Fun (Elems (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z)) a -> a Source #

HVector (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a') Source # 

Associated Types

type Elems (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a') :: [*] Source #

Methods

construct :: Fun (Elems (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a')) (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a') Source #

inspect :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a') -> Fun (Elems (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a')) a -> a Source #

HVector (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a', b') Source # 

Associated Types

type Elems (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a', b') :: [*] Source #

Methods

construct :: Fun (Elems (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a', b')) (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a', b') Source #

inspect :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a', b') -> Fun (Elems (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a', b')) a -> a Source #

HVector (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a', b', c') Source # 

Associated Types

type Elems (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a', b', c') :: [*] Source #

Methods

construct :: Fun (Elems (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a', b', c')) (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a', b', c') Source #

inspect :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a', b', c') -> Fun (Elems (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a', b', c')) a -> a Source #

HVector (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a', b', c', d') Source # 

Associated Types

type Elems (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a', b', c', d') :: [*] Source #

Methods

construct :: Fun (Elems (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a', b', c', d')) (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a', b', c', d') Source #

inspect :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a', b', c', d') -> Fun (Elems (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a', b', c', d')) a -> a Source #

HVector (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a', b', c', d', e') Source # 

Associated Types

type Elems (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a', b', c', d', e') :: [*] Source #

Methods

construct :: Fun (Elems (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a', b', c', d', e')) (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a', b', c', d', e') Source #

inspect :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a', b', c', d', e') -> Fun (Elems (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a', b', c', d', e')) a -> a Source #

HVector (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a', b', c', d', e', f') Source # 

Associated Types

type Elems (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a', b', c', d', e', f') :: [*] Source #

Methods

construct :: Fun (Elems (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a', b', c', d', e', f')) (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a', b', c', d', e', f') Source #

inspect :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a', b', c', d', e', f') -> Fun (Elems (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a', b', c', d', e', f')) a -> a Source #

class Arity (ElemsF v) => HVectorF v where Source #

Type class for partially homogeneous vector where every element in the vector have same type constructor. Vector itself is parametrized by that constructor

Minimal complete definition

inspectF, constructF

Associated Types

type ElemsF v :: [*] Source #

Elements of the vector without type constructors

Methods

inspectF :: v f -> TFun f (ElemsF v) a -> a Source #

constructF :: TFun f (ElemsF v) (v f) Source #

Instances

Arity xs => HVectorF (VecListF xs) Source # 

Associated Types

type ElemsF (VecListF xs :: (* -> *) -> *) :: [*] Source #

Methods

inspectF :: VecListF xs f -> TFun * f (ElemsF (VecListF xs)) a -> a Source #

constructF :: TFun * f (ElemsF (VecListF xs)) (VecListF xs f) Source #

Arity xs => HVectorF (HVecF xs) Source # 

Associated Types

type ElemsF (HVecF xs :: (* -> *) -> *) :: [*] Source #

Methods

inspectF :: HVecF xs f -> TFun * f (ElemsF (HVecF xs)) a -> a Source #

constructF :: TFun * f (ElemsF (HVecF xs)) (HVecF xs f) Source #

Arity xs => HVectorF (ContVecF * xs) Source # 

Associated Types

type ElemsF (ContVecF * xs :: (* -> *) -> *) :: [*] Source #

Methods

inspectF :: ContVecF * xs f -> TFun * f (ElemsF (ContVecF * xs)) a -> a Source #

constructF :: TFun * f (ElemsF (ContVecF * xs)) (ContVecF * xs f) Source #

type family Wrap (f :: α -> β) (a :: [α]) :: [β] Source #

Wrap every element of list into type constructor

Instances

type Wrap β α f ([] α) Source # 
type Wrap β α f ([] α) = [] β
type Wrap β α f ((:) α x xs) Source # 
type Wrap β α f ((:) α x xs) = (:) β (f x) (Wrap β α f xs)

data Proxy k t :: forall k. k -> * #

A concrete, poly-kinded proxy type

Constructors

Proxy 

Instances

Monad (Proxy *) 

Methods

(>>=) :: Proxy * a -> (a -> Proxy * b) -> Proxy * b #

(>>) :: Proxy * a -> Proxy * b -> Proxy * b #

return :: a -> Proxy * a #

fail :: String -> Proxy * a #

Functor (Proxy *) 

Methods

fmap :: (a -> b) -> Proxy * a -> Proxy * b #

(<$) :: a -> Proxy * b -> Proxy * a #

Applicative (Proxy *) 

Methods

pure :: a -> Proxy * a #

(<*>) :: Proxy * (a -> b) -> Proxy * a -> Proxy * b #

(*>) :: Proxy * a -> Proxy * b -> Proxy * b #

(<*) :: Proxy * a -> Proxy * b -> Proxy * a #

Generic1 (Proxy *) 

Associated Types

type Rep1 (Proxy * :: * -> *) :: * -> * #

Methods

from1 :: Proxy * a -> Rep1 (Proxy *) a #

to1 :: Rep1 (Proxy *) a -> Proxy * a #

Alternative (Proxy *) 

Methods

empty :: Proxy * a #

(<|>) :: Proxy * a -> Proxy * a -> Proxy * a #

some :: Proxy * a -> Proxy * [a] #

many :: Proxy * a -> Proxy * [a] #

MonadPlus (Proxy *) 

Methods

mzero :: Proxy * a #

mplus :: Proxy * a -> Proxy * a -> Proxy * a #

Vector (Proxy *) a 

Methods

construct :: Fun (Dim (Proxy *)) a (Proxy * a) #

inspect :: Proxy * a -> Fun (Dim (Proxy *)) a b -> b #

basicIndex :: Proxy * a -> Int -> a #

Bounded (Proxy k s) 

Methods

minBound :: Proxy k s #

maxBound :: Proxy k s #

Enum (Proxy k s) 

Methods

succ :: Proxy k s -> Proxy k s #

pred :: Proxy k s -> Proxy k s #

toEnum :: Int -> Proxy k s #

fromEnum :: Proxy k s -> Int #

enumFrom :: Proxy k s -> [Proxy k s] #

enumFromThen :: Proxy k s -> Proxy k s -> [Proxy k s] #

enumFromTo :: Proxy k s -> Proxy k s -> [Proxy k s] #

enumFromThenTo :: Proxy k s -> Proxy k s -> Proxy k s -> [Proxy k s] #

Eq (Proxy k s) 

Methods

(==) :: Proxy k s -> Proxy k s -> Bool #

(/=) :: Proxy k s -> Proxy k s -> Bool #

Ord (Proxy k s) 

Methods

compare :: Proxy k s -> Proxy k s -> Ordering #

(<) :: Proxy k s -> Proxy k s -> Bool #

(<=) :: Proxy k s -> Proxy k s -> Bool #

(>) :: Proxy k s -> Proxy k s -> Bool #

(>=) :: Proxy k s -> Proxy k s -> Bool #

max :: Proxy k s -> Proxy k s -> Proxy k s #

min :: Proxy k s -> Proxy k s -> Proxy k s #

Read (Proxy k s) 
Show (Proxy k s) 

Methods

showsPrec :: Int -> Proxy k s -> ShowS #

show :: Proxy k s -> String #

showList :: [Proxy k s] -> ShowS #

Ix (Proxy k s) 

Methods

range :: (Proxy k s, Proxy k s) -> [Proxy k s] #

index :: (Proxy k s, Proxy k s) -> Proxy k s -> Int #

unsafeIndex :: (Proxy k s, Proxy k s) -> Proxy k s -> Int

inRange :: (Proxy k s, Proxy k s) -> Proxy k s -> Bool #

rangeSize :: (Proxy k s, Proxy k s) -> Int #

unsafeRangeSize :: (Proxy k s, Proxy k s) -> Int

Generic (Proxy k t) 

Associated Types

type Rep (Proxy k t) :: * -> * #

Methods

from :: Proxy k t -> Rep (Proxy k t) x #

to :: Rep (Proxy k t) x -> Proxy k t #

Semigroup (Proxy k s) 

Methods

(<>) :: Proxy k s -> Proxy k s -> Proxy k s #

sconcat :: NonEmpty (Proxy k s) -> Proxy k s #

stimes :: Integral b => b -> Proxy k s -> Proxy k s #

Monoid (Proxy k s) 

Methods

mempty :: Proxy k s #

mappend :: Proxy k s -> Proxy k s -> Proxy k s #

mconcat :: [Proxy k s] -> Proxy k s #

NFData (Proxy k a)

Since: 1.4.0.0

Methods

rnf :: Proxy k a -> () #

type Rep1 (Proxy *) 
type Rep1 (Proxy *) = D1 (MetaData "Proxy" "Data.Proxy" "base" False) (C1 (MetaCons "Proxy" PrefixI False) U1)
type Dim (Proxy *) 
type Dim (Proxy *) = Z
type Rep (Proxy k t) 
type Rep (Proxy k t) = D1 (MetaData "Proxy" "Data.Proxy" "base" False) (C1 (MetaCons "Proxy" PrefixI False) U1)

data ContVec xs Source #

CPS-encoded heterogeneous vector.

Instances

Arity xs => HVector (ContVec xs) Source # 

Associated Types

type Elems (ContVec xs) :: [*] Source #

Methods

construct :: Fun (Elems (ContVec xs)) (ContVec xs) Source #

inspect :: ContVec xs -> Fun (Elems (ContVec xs)) a -> a Source #

type Elems (ContVec xs) Source # 
type Elems (ContVec xs) = xs

asCVec :: ContVec xs -> ContVec xs Source #

Restrict type of vector to ContVec. This function is useful for resolving type ambiguity when composing functions. For example following code would not compile because intermediate type is ambiguous:

cons 'a' . tail

GHC cannot guess what type should be produced by tail. However we can fix type of intermediate vector with asCVec, so code below will work just fine:

cons 'a' . asCVec . tail

Position based functions

convert :: (HVector v, HVector w, Elems v ~ Elems w) => v -> w Source #

We can convert between any two vector which have same structure but different representations.

head :: (HVector v, Elems v ~ (a ': as), Arity as) => v -> a Source #

Head of the vector

tail :: (HVector v, HVector w, (a ': Elems w) ~ Elems v) => v -> w Source #

Tail of the vector

>>> case tail ('a',"aa",()) of x@(_,_) -> x
("aa",())

cons :: (HVector v, HVector w, Elems w ~ (a ': Elems v)) => a -> v -> w Source #

Prepend element to the list. Note that it changes type of vector so it either must be known from context of specified explicitly

concat :: (HVector v, HVector u, HVector w, Elems w ~ (Elems v ++ Elems u)) => v -> u -> w Source #

Concatenate two vectors

Indexing

class Arity n => Index n xs Source #

Indexing of vectors

Minimal complete definition

getF, putF, lensF, lensChF, witWrapIndex

Associated Types

type ValueAt n xs :: * Source #

Type at position n

Instances

Arity xs => Index Z ((:) * x xs) Source # 

Associated Types

type ValueAt Z ((:) * x xs :: [*]) :: * Source #

type NewElems Z ((:) * x xs :: [*]) a :: [*] Source #

Methods

getF :: Z -> Fun ((* ': x) xs) (ValueAt Z ((* ': x) xs)) Source #

putF :: Z -> ValueAt Z ((* ': x) xs) -> Fun ((* ': x) xs) r -> Fun ((* ': x) xs) r Source #

lensF :: (Functor f, (* ~ v) (ValueAt Z ((* ': x) xs))) => Z -> (v -> f v) -> Fun ((* ': x) xs) r -> Fun ((* ': x) xs) (f r) Source #

lensChF :: Functor f => Z -> (ValueAt Z ((* ': x) xs) -> f a) -> Fun (NewElems Z ((* ': x) xs) a) r -> Fun ((* ': x) xs) (f r) Source #

witWrapIndex :: WitWrapIndex f Z ((* ': x) xs) Source #

Index n xs => Index (S n) ((:) * x xs) Source # 

Associated Types

type ValueAt (S n) ((:) * x xs :: [*]) :: * Source #

type NewElems (S n) ((:) * x xs :: [*]) a :: [*] Source #

Methods

getF :: S n -> Fun ((* ': x) xs) (ValueAt (S n) ((* ': x) xs)) Source #

putF :: S n -> ValueAt (S n) ((* ': x) xs) -> Fun ((* ': x) xs) r -> Fun ((* ': x) xs) r Source #

lensF :: (Functor f, (* ~ v) (ValueAt (S n) ((* ': x) xs))) => S n -> (v -> f v) -> Fun ((* ': x) xs) r -> Fun ((* ': x) xs) (f r) Source #

lensChF :: Functor f => S n -> (ValueAt (S n) ((* ': x) xs) -> f a) -> Fun (NewElems (S n) ((* ': x) xs) a) r -> Fun ((* ': x) xs) (f r) Source #

witWrapIndex :: WitWrapIndex f (S n) ((* ': x) xs) Source #

index :: (Index n (Elems v), HVector v) => v -> n -> ValueAt n (Elems v) Source #

Index heterogeneous vector

set :: (Index n (Elems v), HVector v) => n -> ValueAt n (Elems v) -> v -> v Source #

Set element in the vector

element :: (Index n (Elems v), ValueAt n (Elems v) ~ a, HVector v, Functor f) => n -> (a -> f a) -> v -> f v Source #

Twan van Laarhoven's lens for i'th element.

elementCh :: (Index n (Elems v), a ~ ValueAt n (Elems v), HVector v, HVector w, Elems w ~ NewElems n (Elems v) b, Functor f) => n -> (a -> f b) -> v -> f w Source #

Type changing Twan van Laarhoven's lens for i'th element.

elementTy :: forall n a f v proxy. (Index (ToPeano n) (Elems v), ValueAt (ToPeano n) (Elems v) ~ a, NatIso (ToPeano n) n, HVector v, Functor f) => proxy n -> (a -> f a) -> v -> f v Source #

Twan van Laarhoven's lens for i'th element. GHC >= 7.8

elementChTy :: forall a b f n v w proxy. (Index (ToPeano n) (Elems v), a ~ ValueAt (ToPeano n) (Elems v), HVector v, HVector w, Elems w ~ NewElems (ToPeano n) (Elems v) b, Functor f) => proxy n -> (a -> f b) -> v -> f w Source #

Type changing Twan van Laarhoven's lens for i'th element.

Generic constructors

mk0 :: (HVector v, Elems v ~ '[]) => v Source #

mk1 :: (HVector v, Elems v ~ '[a]) => a -> v Source #

mk2 :: (HVector v, Elems v ~ '[a, b]) => a -> b -> v Source #

mk3 :: (HVector v, Elems v ~ '[a, b, c]) => a -> b -> c -> v Source #

mk4 :: (HVector v, Elems v ~ '[a, b, c, d]) => a -> b -> c -> d -> v Source #

mk5 :: (HVector v, Elems v ~ '[a, b, c, d, e]) => a -> b -> c -> d -> e -> v Source #

Folds and unfolds

fold :: HVector v => v -> Fn (Elems v) r -> r Source #

Most generic form of fold which doesn't constrain elements id use of inspect. Or in more convenient form below:

>>> fold (12::Int,"Str") (\a s -> show a ++ s)
"12Str"

foldr :: (HVector v, ArityC c (Elems v)) => Proxy c -> (forall a. c a => a -> b -> b) -> b -> v -> b Source #

Right fold over heterogeneous vector

foldl :: (HVector v, ArityC c (Elems v)) => Proxy c -> (forall a. c a => b -> a -> b) -> b -> v -> b Source #

Left fold over heterogeneous vector

mapM_ :: (HVector v, ArityC c (Elems v), Monad m) => Proxy c -> (forall a. c a => a -> m ()) -> v -> m () Source #

Apply monadic action to every element in the vector

unfoldr :: (HVector v, ArityC c (Elems v)) => Proxy c -> (forall a. c a => b -> (a, b)) -> b -> v Source #

Unfold vector.

Polymorphic values

replicate :: (HVector v, ArityC c (Elems v)) => Proxy c -> (forall x. c x => x) -> v Source #

Replicate polymorphic value n times. Concrete instance for every element is determined by their respective types.

>>> import Data.Vector.HFixed as H
>>> H.replicate (Proxy :: Proxy Monoid) mempty :: ((),String)
((),"")

replicateM :: (HVector v, Monad m, ArityC c (Elems v)) => Proxy c -> (forall x. c x => m x) -> m v Source #

Replicate monadic action n times.

>>> import Data.Vector.HFixed as H
>>> H.replicateM (Proxy :: Proxy Read) (fmap read getLine) :: IO (Int,Char)
> 12
> 'a'
(12,'a')

replicateF :: (HVectorF v, Arity (ElemsF v)) => (forall a. f a) -> v f Source #

zipMono :: (HVector v, ArityC c (Elems v)) => Proxy c -> (forall a. c a => a -> a -> a) -> v -> v -> v Source #

Zip two heterogeneous vectors

zipMonoF :: (HVectorF v, ArityC c (ElemsF v)) => Proxy c -> (forall a. c a => f a -> g a -> h a) -> v f -> v g -> v h Source #

Zip two heterogeneous vectors

zipFold :: (HVector v, ArityC c (Elems v), Monoid m) => Proxy c -> (forall a. c a => a -> a -> m) -> v -> v -> m Source #

monomorphize :: (HVector v, ArityC c (Elems v)) => Proxy c -> (forall a. c a => a -> x) -> v -> ContVec (Len (Elems v)) x Source #

Convert heterogeneous vector to homogeneous

monomorphizeF :: (HVectorF v, ArityC c (ElemsF v)) => Proxy c -> (forall a. c a => f a -> x) -> v f -> ContVec (Len (ElemsF v)) x Source #

Convert heterogeneous vector to homogeneous

Vector parametrized with type constructor

mapFunctor :: HVectorF v => (forall a. f a -> g a) -> v f -> v g Source #

sequence :: (Monad m, HVectorF v, HVector w, ElemsF v ~ Elems w) => v m -> m w Source #

Sequence effects for every element in the vector

sequenceA :: (Applicative f, HVectorF v, HVector w, ElemsF v ~ Elems w) => v f -> f w Source #

Sequence effects for every element in the vector

sequenceF :: (Monad m, HVectorF v) => v (m `Compose` f) -> m (v f) Source #

Sequence effects for every element in the vector

sequenceAF :: (Applicative f, HVectorF v) => v (f `Compose` g) -> f (v g) Source #

Sequence effects for every element in the vector

wrap :: (HVector v, HVectorF w, Elems v ~ ElemsF w) => (forall a. a -> f a) -> v -> w f Source #

Wrap every value in the vector into type constructor.

unwrap :: (HVectorF v, HVector w, ElemsF v ~ Elems w) => (forall a. f a -> a) -> v f -> w Source #

Unwrap every value in the vector from the type constructor.

distribute :: (Functor f, HVector v, HVectorF w, Elems v ~ ElemsF w) => f v -> w f Source #

Analog of distribute from Distributive type class.

distributeF :: (Functor f, HVectorF v) => f (v g) -> v (f `Compose` g) Source #

Analog of distribute from Distributive type class.

Specialized operations

eq :: (HVector v, ArityC Eq (Elems v)) => v -> v -> Bool Source #

Generic equality for heterogeneous vectors

compare :: (HVector v, ArityC Ord (Elems v)) => v -> v -> Ordering Source #

Generic comparison for heterogeneous vectors

rnf :: (HVector v, ArityC NFData (Elems v)) => v -> () Source #

Reduce vector to normal form