fixed-vector-hetero-0.5.0.0: Generic heterogeneous vectors

Safe HaskellNone
LanguageHaskell98

Data.Vector.HFixed

Contents

Description

Heterogeneous vectors.

Synopsis

HVector type classes

class 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.

Minimal complete definition

accum, apply, arity

Instances

Arity α ([] α) Source # 

Methods

accum :: (forall (a :: [α]) (as :: [[α]]). t (([α] ': a) as) -> f a -> t as) -> (t [[α]] -> b) -> t xs -> TFun [α] f xs b Source #

apply :: (forall (a :: [α]) (as :: [[α]]). t (([α] ': a) as) -> (f a, t as)) -> t xs -> ContVecF [α] xs f Source #

arity :: p xs -> Int Source #

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

Methods

accum :: (forall (a :: (α ': x) xs) (as :: [(α ': x) xs]). t (((α ': x) xs ': a) as) -> f a -> t as) -> (t [(α ': x) xs] -> b) -> t xs -> TFun ((α ': x) xs) f xs b Source #

apply :: (forall (a :: (α ': x) xs) (as :: [(α ': x) xs]). t (((α ': x) xs ': a) as) -> (f a, t as)) -> t xs -> ContVecF ((α ': x) xs) xs f Source #

arity :: p xs -> Int Source #

class Arity xs => ArityC c xs Source #

Minimal complete definition

accumC, applyC

Instances

ArityC α c ([] α) Source # 

Methods

accumC :: proxy [α] -> (forall (a :: c) (as :: [c]). [α] a => t ((c ': a) as) -> f a -> t as) -> (t [c] -> b) -> t xs -> TFun c f xs b Source #

applyC :: proxy [α] -> (forall (a :: c) (as :: [c]). [α] a => t ((c ': a) as) -> (f a, t as)) -> t xs -> ContVecF c xs f Source #

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

Methods

accumC :: proxy ((a ': x) xs) -> (forall (b :: c) (as :: [c]). (a ': x) xs b => t ((c ': b) as) -> f b -> t as) -> (t [c] -> b) -> t xs -> TFun c f xs b Source #

applyC :: proxy ((a ': x) xs) -> (forall (b :: c) (as :: [c]). (a ': x) xs b => t ((c ': b) as) -> (f b, t as)) -> t xs -> ContVecF c xs f 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 (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 (Peano n) a, KnownNat n, (~) PeanoNum (Peano ((+) n 1)) (S (Peano n))) => 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 (Peano n) a, KnownNat n, (~) PeanoNum (Peano ((+) n 1)) (S (Peano n))) => 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 (Peano n) a, KnownNat n, (~) PeanoNum (Peano ((+) n 1)) (S (Peano n))) => 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 (Peano n) a, KnownNat n, (~) PeanoNum (Peano ((+) n 1)) (S (Peano n))) => 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 #

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 #

Arity * xs => HVector (ContVecF * xs Identity) Source # 

Associated Types

type Elems (ContVecF * xs Identity) :: [*] 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 #

tupleSize :: forall v proxy. HVector v => proxy v -> Int Source #

Number of elements in tuple

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 * (HVecF xs) Source # 

Associated Types

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

Methods

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

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

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

Associated Types

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

Methods

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

constructF :: TFun (ContVecF α xs) f (ElemsF (ContVecF α xs) v) (v f) Source #

Arity α xs => HVectorF α (VecListF α xs) Source # 

Associated Types

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

Methods

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

constructF :: TFun (VecListF α xs) f (ElemsF (VecListF α xs) v) (v f) Source #

tupleSizeF :: forall v f proxy. HVectorF v => proxy (v f) -> Int Source #

Number of elements in tuple

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

A concrete, poly-kinded proxy type

Constructors

Proxy 

Instances

Generic1 k (Proxy k) 

Associated Types

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

Methods

from1 :: f a -> Rep1 (Proxy k) f a #

to1 :: Rep1 (Proxy k) f a -> f a #

Monad (Proxy *)

Since: 4.7.0.0

Methods

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

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

return :: a -> Proxy * a #

fail :: String -> Proxy * a #

Functor (Proxy *)

Since: 4.7.0.0

Methods

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

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

Applicative (Proxy *)

Since: 4.7.0.0

Methods

pure :: a -> Proxy * a #

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

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

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

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

Foldable (Proxy *)

Since: 4.7.0.0

Methods

fold :: Monoid m => Proxy * m -> m #

foldMap :: Monoid m => (a -> m) -> Proxy * a -> m #

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

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

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

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

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

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

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

null :: Proxy * a -> Bool #

length :: Proxy * a -> Int #

elem :: Eq a => a -> Proxy * a -> Bool #

maximum :: Ord a => Proxy * a -> a #

minimum :: Ord a => Proxy * a -> a #

sum :: Num a => Proxy * a -> a #

product :: Num a => Proxy * a -> a #

Eq1 (Proxy *)

Since: 4.9.0.0

Methods

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

Ord1 (Proxy *)

Since: 4.9.0.0

Methods

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

Read1 (Proxy *)

Since: 4.9.0.0

Methods

liftReadsPrec :: (Int -> ReadS a) -> ReadS [a] -> Int -> ReadS (Proxy * a) #

liftReadList :: (Int -> ReadS a) -> ReadS [a] -> ReadS [Proxy * a] #

liftReadPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec (Proxy * a) #

liftReadListPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec [Proxy * a] #

Show1 (Proxy *)

Since: 4.9.0.0

Methods

liftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> Proxy * a -> ShowS #

liftShowList :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> [Proxy * a] -> ShowS #

Alternative (Proxy *)

Since: 4.9.0.0

Methods

empty :: Proxy * a #

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

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

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

MonadPlus (Proxy *)

Since: 4.9.0.0

Methods

mzero :: Proxy * a #

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

NFData1 (Proxy *)

Since: 1.4.3.0

Methods

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

Vector (Proxy *) a 

Methods

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

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

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

Bounded (Proxy k t) 

Methods

minBound :: Proxy k t #

maxBound :: Proxy k t #

Enum (Proxy k s)

Since: 4.7.0.0

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)

Since: 4.7.0.0

Methods

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

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

Ord (Proxy k s)

Since: 4.7.0.0

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)

Since: 4.7.0.0

Show (Proxy k s)

Since: 4.7.0.0

Methods

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

show :: Proxy k s -> String #

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

Ix (Proxy k s)

Since: 4.7.0.0

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)

Since: 4.9.0.0

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)

Since: 4.7.0.0

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 k (Proxy k) 
type Rep1 k (Proxy k) = D1 k (MetaData "Proxy" "Data.Proxy" "base" False) (C1 k (MetaCons "Proxy" PrefixI False) (U1 k))
type Dim (Proxy *) 
type Dim (Proxy *) = 0
type Rep (Proxy k t) 
type Rep (Proxy k t) = D1 * (MetaData "Proxy" "Data.Proxy" "base" False) (C1 * (MetaCons "Proxy" PrefixI False) (U1 *))

type ContVec xs = ContVecF xs Identity Source #

CPS-encoded heterogeneous vector.

newtype ContVecF (xs :: [α]) (f :: α -> *) Source #

CPS-encoded partially heterogeneous vector.

Constructors

ContVecF 

Fields

Instances

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

Associated Types

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

Methods

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

constructF :: TFun (ContVecF α xs) f (ElemsF (ContVecF α xs) v) (v f) Source #

Arity * xs => HVector (ContVecF * xs Identity) Source # 

Associated Types

type Elems (ContVecF * xs Identity) :: [*] Source #

type ElemsF α (ContVecF α xs) Source # 
type ElemsF α (ContVecF α xs) = xs
type Elems (ContVecF * xs Identity) Source # 
type Elems (ContVecF * xs Identity) = 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

asCVecF :: ContVecF f xs -> ContVecF f xs Source #

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 ArityPeano n => Index (n :: PeanoNum) (xs :: [*]) Source #

Indexing of vectors

Minimal complete definition

getF, putF, lensF, lensChF

Associated Types

type ValueAt n xs :: * Source #

Type at position n

Instances

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

Associated Types

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

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

Methods

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

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

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

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

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

Associated Types

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

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

Methods

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

putF :: proxy (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))) => proxy (S n) -> (v -> f v) -> Fun ((* ': x) xs) r -> Fun ((* ': x) xs) (f r) Source #

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

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

Index heterogeneous vector

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

Set element in the vector

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

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

elementCh :: forall n v w a b f proxy. (Index (Peano n) (Elems v), ValueAt (Peano n) (Elems v) ~ a, HVector v, HVector w, Elems w ~ NewElems (Peano 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 :: forall v. (HVector v, Elems v ~ '[]) => v Source #

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

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

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

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

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

Folds and unfolds

fold :: HVector v => v -> Fn Identity (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

foldrF :: (HVectorF v, ArityC c (ElemsF v)) => Proxy c -> (forall a. c a => f a -> b -> b) -> b -> v f -> b Source #

Right fold over heterogeneous vector

foldlF :: (HVectorF v, ArityC c (ElemsF v)) => Proxy c -> (forall a. c a => b -> f a -> b) -> b -> v f -> b Source #

Left fold over heterogeneous vector

foldrNatF :: HVectorF v => (forall a. f a -> b -> b) -> b -> v f -> b Source #

Right fold over heterogeneous vector

foldlNatF :: HVectorF v => (forall a. b -> f a -> b) -> b -> v f -> b Source #

Left fold over heterogeneous vector

mapM_ :: (HVector v, ArityC c (Elems v), Applicative f) => Proxy c -> (forall a. c a => a -> f ()) -> v -> f () 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.

unfoldrF :: (HVectorF v, ArityC c (ElemsF v)) => Proxy c -> (forall a. c a => b -> (f a, b)) -> b -> v f Source #

Unfold vector.

Replicate variants

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, Applicative f, ArityC c (Elems v)) => Proxy c -> (forall a. c a => f a) -> f 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, ArityC c (ElemsF v)) => Proxy c -> (forall a. c a => f a) -> v f Source #

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

Zip variants

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

Zip two heterogeneous vectors

zipWithF :: (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

zipWithNatF :: HVectorF v => (forall 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 #

zipFoldF :: (HVectorF v, ArityC c (ElemsF v), Monoid m) => Proxy c -> (forall a. c a => f a -> f a -> m) -> v f -> v f -> m Source #

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

Convert heterogeneous vector to homogeneous

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

Convert heterogeneous vector to homogeneous

Tuples parametrized with type constructor

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

Apply natural transformation to every element of the tuple.

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

Sequence effects for every element in the vector

sequence_ :: (Applicative f, HVectorF v) => v f -> f () Source #

Sequence effects for every element in the vector

sequenceF :: (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