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

Data.Vector.HFixed

Description

This module provides function for working with product types and comes in two variants. First works with plain product, types like (a,b) or data Prod = Prod A B, etc. Second one is for parameterized products (it seems there's no standard name for them), that is types like: data ProdF f = ProdF (f Int) (f Char).

Most examples in this module use tuple but library is not limited to them in any way. They're just in base and convenient to work with.

Synopsis

HVector type classes

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

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 #

Plain product types

Construction

Simple constructor

Functions below allow to construct products up to 5 elements. Here are example for product types from base:

>>> mk0 :: ()
()
>>> mk3 12 'x' "xyz" :: (Int,Char,String)
(12,'x',"xyz")
>>> mk2 0 1 :: Complex Double
0.0 :+ 1.0

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 #

Unfoldr & replicate

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

Unfold vector.

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.

>>> replicate (Proxy :: Proxy Monoid) mempty :: ((),String)
((),"")

Or a bit contrived example which illustrate what how to call function that require multiple type class constraints:

>>> replicate (Proxy @(Monoid :&&: Num)) (mempty * 10) :: (Product Int, Sum Int)
(Product {getProduct = 10},Sum {getSum = 0})

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. Example below is a bit awkward does convey what's

>>> :{
  Prelude.mapM_ print
    (replicateM (Proxy @(Monoid :&&: Num)) [mempty+1, mempty * 10] :: [(Product Int, Sum Int)])
:}
(Product {getProduct = 2},Sum {getSum = 1})
(Product {getProduct = 2},Sum {getSum = 0})
(Product {getProduct = 10},Sum {getSum = 1})
(Product {getProduct = 10},Sum {getSum = 0})

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.

>>> convert (1 :+ 2) :: (Double,Double)
(1.0,2.0)

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

Head of the vector

>>> head ('a',"ABC")
'a'

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

Tail of the vector. Note that in the example we only tell GHC that resulting value is 2-tuple via pattern matching and let typechecker figure out the rest.

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

>>> cons 'c' ('d','e') :: (Char,Char,Char)
('c','d','e')

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

Concatenate two vectors

>>> concat ('c','d') ('e','f') :: (Char,Char,Char,Char)
('c','d','e','f')

Indexing

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 #

index Source #

Arguments

:: forall n v proxy. (Index (Peano n) (Elems v), HVector v) 
=> proxy n

Type level index

-> v

Vector to index

-> ValueAt (Peano n) (Elems v) 

Index heterogeneous vector.

>>> index (Proxy @0) ('c',"str")
'c'
>>> index (Proxy @1) ('c',"str")
"str"

set Source #

Arguments

:: forall n v proxy. (Index (Peano n) (Elems v), HVector v) 
=> proxy n

Type level index

-> ValueAt (Peano n) (Elems v)

New value at index

-> v 
-> v 

Set element in the vector

>>> set (Proxy @0) 'X' ('_',"str")
('X',"str")

element Source #

Arguments

:: forall n v proxy. (Index (Peano n) (Elems v), HVector v) 
=> proxy n

Type level index

-> Lens' v (ValueAt (Peano n) (Elems v)) 

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

elementCh Source #

Arguments

:: forall n v w a b proxy. (Index (Peano n) (Elems v), ValueAt (Peano n) (Elems v) ~ a, HVector v, HVector w, Elems w ~ NewElems (Peano n) (Elems v) b) 
=> proxy n

Type level index

-> Lens v w a b 

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

tyLookup :: (HVector v, TyLookup a (Elems v)) => v -> a Source #

Lookup field from product by its type. Product must contain one and only one field of type a

>>> tyLookup ('c',"str") :: Char
'c'
>>> tyLookup ('c',"str") :: Int
...
    • Cannot find type:
      Int
    • In the expression: tyLookup ('c', "str") :: Int
      In an equation for ‘it’: it = tyLookup ('c', "str") :: Int
>>> tyLookup ('c','c') :: Char
...
    • Duplicate type found:
      Char
    • In the expression: tyLookup ('c', 'c') :: Char
      In an equation for ‘it’: it = tyLookup ('c', 'c') :: Char

tyLookupF :: (HVectorF v, TyLookup a (ElemsF v)) => v f -> f a Source #

Analog of tyLookup for HVectorF

Folds & unfolds

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

>>> foldr (Proxy @Show) (\x str -> show x : str) [] (12,'c')
["12","'c'"]

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

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

Monoidal fold over heterogeneuous vector

>>> foldMap (Proxy @Show) show (12,'c',"str")
"12'c'\"str\""

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

Zips

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

Zip two heterogeneous vectors

>>> zipWith (Proxy @Num) (+) (0, 1.2) (1, 10) :: (Int,Double)
(1,11.2)

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

Zip two heterogeneous vectors and immediately fold resulting value.

>>> zipFold (Proxy @Show) (\a b -> show (a,b)) ((),'c',10) ((),'D',1)
"((),())('c','D')(10,1)"

Specializations

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

Generic equality for heterogeneous vectors

>>> data A = A Int Char deriving Generic
>>> instance HVector A
>>> eq (A 1 'c') (A 2 'c')
False

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

Generic comparison for heterogeneous vectors. It works same way as Ord instance for tuples.

>>> data A = A Int Char deriving Generic
>>> instance HVector A
>>> compare (A 1 'c') (A 2 'c')
LT

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

Reduce vector to normal form

Parametrized products

Construction

Simple constructors

Construction function for parametrized products are fully analogous to plain products:

>>> mk2F (Identity 'c') (Identity 1) :: HVecF '[Char, Int] Identity
[Identity 'c',Identity 1]
>>> mk2F (Nothing) (Just 1) :: HVecF '[Char, Int] Maybe
[Nothing,Just 1]

mk0F :: forall f v. (HVectorF v, ElemsF v ~ '[]) => v f Source #

mk1F :: forall f v a. (HVectorF v, ElemsF v ~ '[a]) => f a -> v f Source #

mk2F :: forall f v a b. (HVectorF v, ElemsF v ~ '[a, b]) => f a -> f b -> v f Source #

mk3F :: forall f v a b c. (HVectorF v, ElemsF v ~ '[a, b, c]) => f a -> f b -> f c -> v f Source #

mk4F :: forall f v a b c d. (HVectorF v, ElemsF v ~ '[a, b, c, d]) => f a -> f b -> f c -> f d -> v f Source #

mk5F :: forall f v a b c d e. (HVectorF v, ElemsF v ~ '[a, b, c, d, e]) => f a -> f b -> f c -> f d -> f e -> v f Source #

Unfoldr & replicate

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

Unfold vector.

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

Replicate polymorphic value n times:

>>> replicateF (Proxy @Num) (Just 0) :: HVecF '[Double,Int] Maybe
[Just 0.0,Just 0]

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

Replicate value f a which is valid for every type a n times.

>>> replicateNatF Nothing :: HVecF '[Char,Int] Maybe
[Nothing,Nothing]

Conversion to/from products

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.

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

Functor/Applicative like

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

Apply function to every value of parametrized product.

>>> map (Proxy @Num) (Identity . fromMaybe 0) (mk2F (Just 12) Nothing :: HVecF '[Double, Int] Maybe)
[Identity 12.0,Identity 0]

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

Apply natural transformation to every element of the tuple.

>>> mapNat (Just . runIdentity) (mk2F (pure 'c') (pure 1) :: HVecF '[Char, Int] Identity)
[Just 'c',Just 1]

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 (mk2F [1,2] "ab" :: HVecF '[Int,Char] []) :: [(Int,Char)]
[(1,'a'),(1,'b'),(2,'a'),(2,'b')]

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

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.

Folds and unfolds

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

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

Monoidal fold over heterogeneous vector

>>> foldMapF (Proxy @Show) show (mk2F (Just 1) Nothing :: HVecF '[Int,Char] Maybe)
"Just 1Nothing"

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

foldMapNatF :: (HVectorF v, Monoid m) => (forall a. f a -> m) -> v f -> m Source #

Monoidal fold over heterogeneous vector

>>> foldMapNatF (Sum . getConst) (mk2F (Const 1) (Const 2) :: HVecF '[Char,String] (Const Int))
Sum {getSum = 3}

Zips

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

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 #

Reexports

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

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 xs => ArityC c xs Source #

Minimal complete definition

accumC, applyC

Instances

Instances details
ArityC (c :: α -> Constraint) ('[] :: [α]) Source # 
Instance details

Defined in Data.Vector.HFixed.Class

Methods

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

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

(c x, ArityC c xs) => ArityC (c :: a -> Constraint) (x ': xs :: [a]) Source # 
Instance details

Defined in Data.Vector.HFixed.Class

Methods

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

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

data Proxy (t :: k) #

Proxy is a type that holds no data, but has a phantom parameter of arbitrary type (or even kind). Its use is to provide type information, even though there is no value available of that type (or it may be too costly to create one).

Historically, Proxy :: Proxy a is a safer alternative to the undefined :: a idiom.

>>> Proxy :: Proxy (Void, Int -> Int)
Proxy

Proxy can even hold types of higher kinds,

>>> Proxy :: Proxy Either
Proxy
>>> Proxy :: Proxy Functor
Proxy
>>> Proxy :: Proxy complicatedStructure
Proxy

Constructors

Proxy 

Instances

Instances details
Generic1 (Proxy :: k -> Type)

Since: base-4.6.0.0

Instance details

Defined in GHC.Generics

Associated Types

type Rep1 Proxy :: k -> Type #

Methods

from1 :: forall (a :: k0). Proxy a -> Rep1 Proxy a #

to1 :: forall (a :: k0). Rep1 Proxy a -> Proxy a #

Monad (Proxy :: Type -> Type)

Since: base-4.7.0.0

Instance details

Defined in Data.Proxy

Methods

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

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

return :: a -> Proxy a #

Functor (Proxy :: Type -> Type)

Since: base-4.7.0.0

Instance details

Defined in Data.Proxy

Methods

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

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

Applicative (Proxy :: Type -> Type)

Since: base-4.7.0.0

Instance details

Defined in Data.Proxy

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 :: Type -> Type)

Since: base-4.7.0.0

Instance details

Defined in Data.Foldable

Methods

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

foldMap :: Monoid m => (a -> m) -> Proxy a -> 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 #

Traversable (Proxy :: Type -> Type)

Since: base-4.7.0.0

Instance details

Defined in Data.Traversable

Methods

traverse :: Applicative f => (a -> f b) -> Proxy a -> f (Proxy b) #

sequenceA :: Applicative f => Proxy (f a) -> f (Proxy a) #

mapM :: Monad m => (a -> m b) -> Proxy a -> m (Proxy b) #

sequence :: Monad m => Proxy (m a) -> m (Proxy a) #

Eq1 (Proxy :: Type -> Type)

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Classes

Methods

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

Ord1 (Proxy :: Type -> Type)

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Classes

Methods

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

Read1 (Proxy :: Type -> Type)

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Classes

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 :: Type -> Type)

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Classes

Methods

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

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

Alternative (Proxy :: Type -> Type)

Since: base-4.9.0.0

Instance details

Defined in Data.Proxy

Methods

empty :: Proxy a #

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

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

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

MonadPlus (Proxy :: Type -> Type)

Since: base-4.9.0.0

Instance details

Defined in Data.Proxy

Methods

mzero :: Proxy a #

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

NFData1 (Proxy :: Type -> Type)

Since: deepseq-1.4.3.0

Instance details

Defined in Control.DeepSeq

Methods

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

Vector (Proxy :: Type -> Type) a 
Instance details

Defined in Data.Vector.Fixed.Cont

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 t)

Since: base-4.7.0.0

Instance details

Defined in Data.Proxy

Methods

minBound :: Proxy t #

maxBound :: Proxy t #

Enum (Proxy s)

Since: base-4.7.0.0

Instance details

Defined in Data.Proxy

Methods

succ :: Proxy s -> Proxy s #

pred :: Proxy s -> Proxy s #

toEnum :: Int -> Proxy s #

fromEnum :: Proxy s -> Int #

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

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

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

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

Eq (Proxy s)

Since: base-4.7.0.0

Instance details

Defined in Data.Proxy

Methods

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

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

Ord (Proxy s)

Since: base-4.7.0.0

Instance details

Defined in Data.Proxy

Methods

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

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

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

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

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

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

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

Read (Proxy t)

Since: base-4.7.0.0

Instance details

Defined in Data.Proxy

Show (Proxy s)

Since: base-4.7.0.0

Instance details

Defined in Data.Proxy

Methods

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

show :: Proxy s -> String #

showList :: [Proxy s] -> ShowS #

Ix (Proxy s)

Since: base-4.7.0.0

Instance details

Defined in Data.Proxy

Methods

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

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

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

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

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

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

Generic (Proxy t)

Since: base-4.6.0.0

Instance details

Defined in GHC.Generics

Associated Types

type Rep (Proxy t) :: Type -> Type #

Methods

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

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

Semigroup (Proxy s)

Since: base-4.9.0.0

Instance details

Defined in Data.Proxy

Methods

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

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

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

Monoid (Proxy s)

Since: base-4.7.0.0

Instance details

Defined in Data.Proxy

Methods

mempty :: Proxy s #

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

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

NFData (Proxy a)

Since: deepseq-1.4.0.0

Instance details

Defined in Control.DeepSeq

Methods

rnf :: Proxy a -> () #

type Rep1 (Proxy :: k -> Type) 
Instance details

Defined in GHC.Generics

type Rep1 (Proxy :: k -> Type) = D1 ('MetaData "Proxy" "Data.Proxy" "base" 'False) (C1 ('MetaCons "Proxy" 'PrefixI 'False) (U1 :: k -> Type))
type Dim (Proxy :: Type -> Type) 
Instance details

Defined in Data.Vector.Fixed.Cont

type Dim (Proxy :: Type -> Type) = 0
type Rep (Proxy t) 
Instance details

Defined in GHC.Generics

type Rep (Proxy t) = D1 ('MetaData "Proxy" "Data.Proxy" "base" 'False) (C1 ('MetaCons "Proxy" 'PrefixI 'False) (U1 :: Type -> Type))