fixed-vector-hetero-0.6.1.1: Library for working with product types generically
Safe HaskellNone
LanguageHaskell2010

Data.Vector.HFixed.Cont

Description

CPS encoded heterogeneous vectors.

Synopsis

CPS-encoded vector

Type classes

type family Fn (f :: α -> *) (as :: [α]) b where ... Source #

Type family for N-ary function. Types of function parameters are encoded as the list of types.

Equations

Fn f '[] b = b 
Fn f (a ': as) b = f a -> Fn f as b 

type Fun = TFun Identity Source #

Newtype wrapper to work around of type families' lack of injectivity.

newtype TFun f as b Source #

Newtype wrapper for function where all type parameters have same type constructor. This type is required for writing function which works with monads, appicatives etc.

Constructors

TFun 

Fields

Instances

Instances details
Arity xs => Monad (TFun f xs) Source # 
Instance details

Defined in Data.Vector.HFixed.Class

Methods

(>>=) :: TFun f xs a -> (a -> TFun f xs b) -> TFun f xs b #

(>>) :: TFun f xs a -> TFun f xs b -> TFun f xs b #

return :: a -> TFun f xs a #

Arity xs => Functor (TFun f xs) Source # 
Instance details

Defined in Data.Vector.HFixed.Class

Methods

fmap :: (a -> b) -> TFun f xs a -> TFun f xs b #

(<$) :: a -> TFun f xs b -> TFun f xs a #

Arity xs => Applicative (TFun f xs) Source # 
Instance details

Defined in Data.Vector.HFixed.Class

Methods

pure :: a -> TFun f xs a #

(<*>) :: TFun f xs (a -> b) -> TFun f xs a -> TFun f xs b #

liftA2 :: (a -> b -> c) -> TFun f xs a -> TFun f xs b -> TFun f xs c #

(*>) :: TFun f xs a -> TFun f xs b -> TFun f xs b #

(<*) :: TFun f xs a -> TFun f xs b -> TFun f xs a #

class Arity (xs :: [α]) where 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.

Methods

accum Source #

Arguments

:: (forall a as. t (a ': as) -> f a -> t as)

Step function. Applies element to accumulator.

-> (t '[] -> b)

Extract value from accumulator.

-> t xs

Initial state.

-> TFun f xs b 

Fold over N elements exposed as N-ary function.

apply Source #

Arguments

:: (forall a as. t (a ': as) -> (f a, t as))

Extract value to be applied to function.

-> t xs

Initial state.

-> ContVecF xs f 

Apply values to N-ary function

arity :: p xs -> Int Source #

Size of type list as integer.

Instances

Instances details
Arity ('[] :: [α]) Source # 
Instance details

Defined in Data.Vector.HFixed.Class

Methods

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

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

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

Arity xs => Arity (x ': xs :: [α]) Source # 
Instance details

Defined in Data.Vector.HFixed.Class

Methods

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

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

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

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

Type class for product type. Any product type could have instance of this type. Its methods describe how to construct and deconstruct data type. For example instance for simple data type with two fields could be written as:

data A a = A Int a

instance HVector (A a) where
  type Elems (A a) = '[Int,a]
  construct = TFun $ \i a -> A i a
  inspect (A i a) (TFun f) = f i a

Another equivalent description of this type class is descibes isomorphism between data type and ContVec, where constuct implements ContVec → a (see vector) and inspect implements a → ContVec (see cvec)

Istances should satisfy one law:

inspect v construct = v

Default implementation which uses Generic is provided.

Minimal complete definition

Nothing

Associated Types

type Elems v :: [*] Source #

type Elems v = GElems (Rep v)

Methods

construct :: Fun (Elems v) v Source #

Function for constructing vector

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

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

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

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

Instances

Instances details
HVector () Source #

Unit is empty heterogeneous vector

Instance details

Defined in Data.Vector.HFixed.Class

Associated Types

type Elems () :: [Type] Source #

Methods

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

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

HVector (Complex a) Source # 
Instance details

Defined in Data.Vector.HFixed.Class

Associated Types

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

Methods

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

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

Arity xs => HVector (VecList xs) Source # 
Instance details

Defined in Data.Vector.HFixed.Cont

Associated Types

type Elems (VecList xs) :: [Type] 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 # 
Instance details

Defined in Data.Vector.HFixed.HVec

Associated Types

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

Methods

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

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

HVector (a, b) Source # 
Instance details

Defined in Data.Vector.HFixed.Class

Associated Types

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

Methods

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

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

(Unbox n a, HomArity (Peano n) a, KnownNat n, Peano (n + 1) ~ 'S (Peano n)) => HVector (Vec n a) Source # 
Instance details

Defined in Data.Vector.HFixed.Class

Associated Types

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

Methods

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

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

(Storable a, HomArity (Peano n) a, KnownNat n, Peano (n + 1) ~ 'S (Peano n)) => HVector (Vec n a) Source # 
Instance details

Defined in Data.Vector.HFixed.Class

Associated Types

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

Methods

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

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

(Prim a, HomArity (Peano n) a, KnownNat n, Peano (n + 1) ~ 'S (Peano n)) => HVector (Vec n a) Source # 
Instance details

Defined in Data.Vector.HFixed.Class

Associated Types

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

Methods

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

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

(HomArity (Peano n) a, KnownNat n, Peano (n + 1) ~ 'S (Peano n)) => HVector (Vec n a) Source # 
Instance details

Defined in Data.Vector.HFixed.Class

Associated Types

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

Methods

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

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

HVector (a, b, c) Source # 
Instance details

Defined in Data.Vector.HFixed.Class

Associated Types

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

Methods

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

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

Arity xs => HVector (ContVecF xs Identity) Source # 
Instance details

Defined in Data.Vector.HFixed.Class

Associated Types

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

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

Defined in Data.Vector.HFixed.Class

Associated Types

type Elems (a, b, c, d) :: [Type] 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)) a0 -> a0 Source #

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

Defined in Data.Vector.HFixed.Class

Associated Types

type Elems (a, b, c, d, e) :: [Type] 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)) a0 -> a0 Source #

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

Defined in Data.Vector.HFixed.Class

Associated Types

type Elems (a, b, c, d, e, f) :: [Type] 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)) a0 -> a0 Source #

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

Defined in Data.Vector.HFixed.Class

Associated Types

type Elems (a, b, c, d, e, f, g) :: [Type] 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)) a0 -> a0 Source #

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

Defined in Data.Vector.HFixed.Class

Associated Types

type Elems (a, b, c, d, e, f, g, h) :: [Type] 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)) a0 -> a0 Source #

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

Defined in Data.Vector.HFixed.Class

Associated Types

type Elems (a, b, c, d, e, f, g, h, i) :: [Type] 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)) a0 -> a0 Source #

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

Defined in Data.Vector.HFixed.Class

Associated Types

type Elems (a, b, c, d, e, f, g, h, i, j) :: [Type] 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)) a0 -> a0 Source #

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

Defined in Data.Vector.HFixed.Class

Associated Types

type Elems (a, b, c, d, e, f, g, h, i, j, k) :: [Type] 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)) a0 -> a0 Source #

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

Defined in Data.Vector.HFixed.Class

Associated Types

type Elems (a, b, c, d, e, f, g, h, i, j, k, l) :: [Type] 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)) a0 -> a0 Source #

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

Defined in Data.Vector.HFixed.Class

Associated Types

type Elems (a, b, c, d, e, f, g, h, i, j, k, l, m) :: [Type] 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)) a0 -> a0 Source #

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

Defined in Data.Vector.HFixed.Class

Associated Types

type Elems (a, b, c, d, e, f, g, h, i, j, k, l, m, n) :: [Type] 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)) a0 -> a0 Source #

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

Defined in Data.Vector.HFixed.Class

Associated Types

type Elems (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) :: [Type] 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)) a0 -> a0 Source #

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

Defined in Data.Vector.HFixed.Class

Associated Types

type Elems (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p) :: [Type] 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)) a0 -> a0 Source #

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

Defined in Data.Vector.HFixed.Class

Associated Types

type Elems (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q) :: [Type] 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)) a0 -> a0 Source #

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

Defined in Data.Vector.HFixed.Class

Associated Types

type Elems (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r) :: [Type] 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)) a0 -> a0 Source #

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

Defined in Data.Vector.HFixed.Class

Associated Types

type Elems (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s) :: [Type] 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)) a0 -> a0 Source #

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

Defined in Data.Vector.HFixed.Class

Associated Types

type Elems (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t) :: [Type] 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)) a0 -> a0 Source #

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

Defined in Data.Vector.HFixed.Class

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) :: [Type] 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)) a0 -> a0 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 # 
Instance details

Defined in Data.Vector.HFixed.Class

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) :: [Type] 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)) a0 -> a0 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 # 
Instance details

Defined in Data.Vector.HFixed.Class

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) :: [Type] 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)) a0 -> a0 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 # 
Instance details

Defined in Data.Vector.HFixed.Class

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) :: [Type] 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)) a0 -> a0 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 # 
Instance details

Defined in Data.Vector.HFixed.Class

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) :: [Type] 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)) a0 -> a0 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 # 
Instance details

Defined in Data.Vector.HFixed.Class

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) :: [Type] 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)) a0 -> a0 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 # 
Instance details

Defined in Data.Vector.HFixed.Class

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') :: [Type] 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')) a0 -> a0 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 # 
Instance details

Defined in Data.Vector.HFixed.Class

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') :: [Type] 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')) a0 -> a0 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 # 
Instance details

Defined in Data.Vector.HFixed.Class

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') :: [Type] 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')) a0 -> a0 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 # 
Instance details

Defined in Data.Vector.HFixed.Class

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') :: [Type] 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')) a0 -> a0 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 # 
Instance details

Defined in Data.Vector.HFixed.Class

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') :: [Type] 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')) a0 -> a0 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 # 
Instance details

Defined in Data.Vector.HFixed.Class

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') :: [Type] 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')) a0 -> a0 Source #

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

Number of elements in product type

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

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

Instances details
Arity xs => HVectorF (ContVecF xs :: (α -> Type) -> Type) Source # 
Instance details

Defined in Data.Vector.HFixed.Class

Associated Types

type ElemsF (ContVecF xs) :: [α] Source #

Methods

inspectF :: forall (f :: α0 -> Type) a. ContVecF xs f -> TFun f (ElemsF (ContVecF xs)) a -> a Source #

constructF :: forall (f :: α0 -> Type). TFun f (ElemsF (ContVecF xs)) (ContVecF xs f) Source #

Arity xs => HVectorF (VecListF xs :: (α -> Type) -> Type) Source # 
Instance details

Defined in Data.Vector.HFixed.Cont

Associated Types

type ElemsF (VecListF xs) :: [α] Source #

Methods

inspectF :: forall (f :: α0 -> Type) a. VecListF xs f -> TFun f (ElemsF (VecListF xs)) a -> a Source #

constructF :: forall (f :: α0 -> Type). TFun f (ElemsF (VecListF xs)) (VecListF xs f) Source #

Arity xs => HVectorF (HVecF xs :: (Type -> Type) -> Type) Source # 
Instance details

Defined in Data.Vector.HFixed.HVec

Associated Types

type ElemsF (HVecF xs) :: [α] Source #

Methods

inspectF :: forall (f :: α -> Type) a. HVecF xs f -> TFun f (ElemsF (HVecF xs)) a -> a Source #

constructF :: forall (f :: α -> Type). TFun f (ElemsF (HVecF xs)) (HVecF xs f) Source #

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

Number of elements in parametrized product type

type family ValueAt n xs :: * Source #

Type at position n

Instances

Instances details
type ValueAt 'Z (x ': xs) Source # 
Instance details

Defined in Data.Vector.HFixed.Class

type ValueAt 'Z (x ': xs) = x
type ValueAt ('S n) (x ': xs) Source # 
Instance details

Defined in Data.Vector.HFixed.Class

type ValueAt ('S n) (x ': xs) = ValueAt n xs

class ArityPeano n => Index (n :: PeanoNum) (xs :: [*]) Source #

Indexing of vectors

Minimal complete definition

getF, putF, lensF, lensChF

Instances

Instances details
Arity xs => Index 'Z (x ': xs) Source # 
Instance details

Defined in Data.Vector.HFixed.Class

Associated Types

type ValueAt 'Z (x ': xs) Source #

type NewElems 'Z (x ': xs) a :: [Type] 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 # 
Instance details

Defined in Data.Vector.HFixed.Class

Associated Types

type ValueAt ('S n) (x ': xs) Source #

type NewElems ('S n) (x ': xs) a :: [Type] 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 #

CPS-encoded vector

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

Instances details
Arity xs => HVectorF (ContVecF xs :: (α -> Type) -> Type) Source # 
Instance details

Defined in Data.Vector.HFixed.Class

Associated Types

type ElemsF (ContVecF xs) :: [α] Source #

Methods

inspectF :: forall (f :: α0 -> Type) a. ContVecF xs f -> TFun f (ElemsF (ContVecF xs)) a -> a Source #

constructF :: forall (f :: α0 -> Type). TFun f (ElemsF (ContVecF xs)) (ContVecF xs f) Source #

Arity xs => HVector (ContVecF xs Identity) Source # 
Instance details

Defined in Data.Vector.HFixed.Class

Associated Types

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

type ElemsF (ContVecF xs :: (α -> Type) -> Type) Source # 
Instance details

Defined in Data.Vector.HFixed.Class

type ElemsF (ContVecF xs :: (α -> Type) -> Type) = xs
type Elems (ContVecF xs Identity) Source # 
Instance details

Defined in Data.Vector.HFixed.Class

type Elems (ContVecF xs Identity) = xs

Other data types

data VecList :: [*] -> * where Source #

List like heterogeneous vector.

Constructors

Nil :: VecList '[] 
Cons :: x -> VecList xs -> VecList (x ': xs) 

Instances

Instances details
Arity xs => HVector (VecList xs) Source # 
Instance details

Defined in Data.Vector.HFixed.Cont

Associated Types

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

Methods

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

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

type Elems (VecList xs) Source # 
Instance details

Defined in Data.Vector.HFixed.Cont

type Elems (VecList xs) = xs

data VecListF (xs :: [α]) (f :: α -> *) where Source #

List-like vector

Constructors

NilF :: VecListF '[] f 
ConsF :: f x -> VecListF xs f -> VecListF (x ': xs) f 

Instances

Instances details
Arity xs => HVectorF (VecListF xs :: (α -> Type) -> Type) Source # 
Instance details

Defined in Data.Vector.HFixed.Cont

Associated Types

type ElemsF (VecListF xs) :: [α] Source #

Methods

inspectF :: forall (f :: α0 -> Type) a. VecListF xs f -> TFun f (ElemsF (VecListF xs)) a -> a Source #

constructF :: forall (f :: α0 -> Type). TFun f (ElemsF (VecListF xs)) (VecListF xs f) Source #

type ElemsF (VecListF xs :: (α -> Type) -> Type) Source # 
Instance details

Defined in Data.Vector.HFixed.Cont

type ElemsF (VecListF xs :: (α -> Type) -> Type) = xs

Conversion to/from vector

cvec :: (HVector v, Elems v ~ xs) => v -> ContVec xs Source #

Convert heterogeneous vector to CPS form

vector :: (HVector v, Elems v ~ xs) => ContVec xs -> v Source #

Convert CPS-vector to heterogeneous vector

cvecF :: HVectorF v => v f -> ContVecF (ElemsF v) f Source #

vectorF :: HVectorF v => ContVecF (ElemsF v) f -> v f Source #

Generic API for tuples

Position based functions

head :: Arity xs => ContVec (x ': xs) -> x Source #

Head of vector

tail :: ContVec (x ': xs) -> ContVec xs Source #

Tail of CPS-encoded vector

cons :: x -> ContVec xs -> ContVec (x ': xs) Source #

Cons element to the vector

consF :: f x -> ContVecF xs f -> ContVecF (x ': xs) f Source #

Cons element to the vector

concat :: Arity xs => ContVec xs -> ContVec ys -> ContVec (xs ++ ys) Source #

Concatenate two vectors

Indexing

index :: Index n xs => ContVec xs -> proxy n -> ValueAt n xs Source #

Get value at nth position.

set :: Index n xs => proxy n -> ValueAt n xs -> ContVec xs -> ContVec xs Source #

Set value on nth position.

tyLookup :: TyLookup a xs => ContVec xs -> a Source #

Lookup value by its type

tyLookupF :: TyLookup a xs => ContVecF xs f -> f a Source #

Lookup value by its type

Folds and unfolds

foldlF :: ArityC c xs => Proxy c -> (forall a. c a => b -> f a -> b) -> b -> ContVecF xs f -> b Source #

Left fold over vector

foldrF :: ArityC c xs => Proxy c -> (forall a. c a => f a -> b -> b) -> b -> ContVecF xs f -> b Source #

Right fold over vector

foldMapF :: (Monoid m, ArityC c xs) => Proxy c -> (forall a. c a => f a -> m) -> ContVecF xs f -> m Source #

Monoidal fold over vector

foldlNatF :: Arity xs => (forall a. b -> f a -> b) -> b -> ContVecF xs f -> b Source #

Left fold over vector

foldrNatF :: Arity xs => (forall a. f a -> b -> b) -> b -> ContVecF xs f -> b Source #

Right fold over vector

foldMapNatF :: (Monoid m, Arity xs) => (forall a. f a -> m) -> ContVecF xs f -> m Source #

Monoidal fold over vector

unfoldrF :: ArityC c xs => Proxy c -> (forall a. c a => b -> (f a, b)) -> b -> ContVecF xs f Source #

Unfold vector.

Replicate variants

replicateF :: ArityC c xs => Proxy c -> (forall a. c a => f a) -> ContVecF xs f Source #

replicateNatF :: Arity xs => (forall a. f a) -> ContVecF xs f Source #

Zip variants

zipWithF :: ArityC c xs => Proxy c -> (forall a. c a => f a -> g a -> h a) -> ContVecF xs f -> ContVecF xs g -> ContVecF xs h Source #

Zip two heterogeneous vectors

zipWithNatF :: Arity xs => (forall a. f a -> g a -> h a) -> ContVecF xs f -> ContVecF xs g -> ContVecF xs h Source #

Zip two heterogeneous vectors

zipFoldF :: forall xs c m f. (ArityC c xs, Monoid m) => Proxy c -> (forall a. c a => f a -> f a -> m) -> ContVecF xs f -> ContVecF xs f -> m Source #

Zip vector and fold result using monoid

Monomorphization of vectors

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

Convert heterogeneous vector to homogeneous

Manipulation with type constructor

map :: ArityC c xs => Proxy c -> (forall a. c a => f a -> g a) -> ContVecF xs f -> ContVecF xs g Source #

Apply transformation to every element of the tuple.

mapNat :: Arity xs => (forall a. f a -> g a) -> ContVecF xs f -> ContVecF xs g Source #

Apply natural transformation to every element of the tuple.

sequenceF :: (Arity xs, Applicative f) => ContVecF xs (f `Compose` g) -> f (ContVecF xs g) Source #

Apply sequence to outer level of parametrized tuple elements.

distributeF :: forall f g xs. (Arity xs, Functor f) => f (ContVecF xs g) -> ContVecF xs (f `Compose` g) Source #