type-unary-0.3.0: Type-level and typed unary natural numbers, inequality proofs, vectors

Copyright(c) Conal Elliott 2009
LicenseBSD3
Maintainerconal@conal.net
Stabilityexperimental
Safe HaskellNone
LanguageHaskell98

TypeUnary.Vec

Contents

Description

Experiment in length-typed vectors

Synopsis

Documentation

Vectors

data Vec :: * -> * -> * where Source

Vectors with type-determined length, having empty vector (ZVec) and vector cons ('(:<)').

Constructors

ZVec :: Vec Z a 
(:<) :: a -> Vec n a -> Vec (S n) a infixr 5 

Instances

IsNat n => Monad (Vec n) Source 
Functor (Vec n) Source 
IsNat n => Applicative (Vec n) Source 
Foldable (Vec n) Source 
Traversable (Vec n) Source 
(IsNat n, Enum applicative_arg) => Enum (Vec n applicative_arg) 
Eq a => Eq (Vec n a) Source 
(IsNat n, Floating applicative_arg) => Floating (Vec n applicative_arg) 
(IsNat n, Fractional applicative_arg) => Fractional (Vec n applicative_arg) 
(IsNat n, Integral applicative_arg) => Integral (Vec n applicative_arg) 
(IsNat n, Num applicative_arg) => Num (Vec n applicative_arg) 
Ord a => Ord (Vec n a) Source 
(IsNat n, Num applicative_arg, Ord applicative_arg) => Real (Vec n applicative_arg) 
(IsNat n, RealFloat applicative_arg) => RealFloat (Vec n applicative_arg) 
(IsNat n, RealFrac applicative_arg) => RealFrac (Vec n applicative_arg) 
Show a => Show (Vec n a) Source 
(IsNat n, Storable a) => Storable (Vec n a) Source 
(IsNat n, Monoid a) => Monoid (Vec n a) Source 
(IsNat n, Num a) => VectorSpace (Vec n a) Source 
(IsNat n, Num a) => InnerSpace (Vec n a) Source 
(IsNat n, Num a) => AdditiveGroup (Vec n a) Source 
Newtype (Vec Z a) () Source 
ToVec (Vec n a) n a Source 
Newtype (Vec (S n) a) (a, Vec n a) Source 
type Scalar (Vec n a) = Vec1 a Source 

unConsV :: Vec (S n) a -> (a, Vec n a) Source

Type-safe un-cons for vectors

headV :: Vec (S n) a -> a Source

Type-safe head for vectors

tailV :: Vec (S n) a -> Vec n a Source

Type-safe tail for vectors

joinV :: Vec n (Vec n a) -> Vec n a Source

Equivalent to monad join for vectors

(<+>) :: Vec m a -> Vec n a -> Vec (m :+: n) a infixl 1 Source

Concatenation of vectors

indices :: IsNat n => Vec n (Index n) Source

Indices under n: index0 :< index1 :< ...

iota :: (IsNat n, Num a, Enum a) => Vec n a Source

Vector of ints from 0 to n-1. Named for APL iota operation (but 0 based).

type Vec0 = Vec N0 Source

type Vec1 = Vec N1 Source

type Vec2 = Vec N2 Source

type Vec3 = Vec N3 Source

type Vec4 = Vec N4 Source

type Vec5 = Vec N5 Source

type Vec6 = Vec N6 Source

type Vec7 = Vec N7 Source

type Vec8 = Vec N8 Source

type Vec9 = Vec N9 Source

vec1 :: a -> Vec1 a Source

vec2 :: a -> a -> Vec2 a Source

vec3 :: a -> a -> a -> Vec3 a Source

vec4 :: a -> a -> a -> a -> Vec4 a Source

vec5 :: a -> a -> a -> a -> a -> Vec5 a Source

vec6 :: a -> a -> a -> a -> a -> a -> Vec6 a Source

vec7 :: a -> a -> a -> a -> a -> a -> a -> Vec7 a Source

vec8 :: a -> a -> a -> a -> a -> a -> a -> a -> Vec8 a Source

un1 :: Vec1 a -> a Source

Extract element

un2 :: Vec2 a -> (a, a) Source

Extract elements

un3 :: Vec3 a -> (a, a, a) Source

Extract elements

un4 :: Vec4 a -> (a, a, a, a) Source

Extract elements

get :: Index n -> Vec n a -> a Source

Extract a vector element, taking a proof that the index is within bounds.

get0 Source

Arguments

:: Vec (N1 :+: n) a 
-> a

Get first element

get1 Source

Arguments

:: Vec (N2 :+: n) a 
-> a

Get second element

get2 Source

Arguments

:: Vec (N3 :+: n) a 
-> a

Get third element

get3 Source

Arguments

:: Vec (N4 :+: n) a 
-> a

Get fourth element

update :: Index n -> (a -> a) -> Vec n a -> Vec n a Source

Update a vector element, taking a proof that the index is within bounds.

set :: Index n -> a -> Vec n a -> Vec n a Source

Replace a vector element, taking a proof that the index is within bounds.

set0 Source

Arguments

:: a 
-> Vec (N1 :+: n) a 
-> Vec (N1 :+: n) a

Set first element

set1 Source

Arguments

:: a 
-> Vec (N2 :+: n) a 
-> Vec (N2 :+: n) a

Set second element

set2 Source

Arguments

:: a 
-> Vec (N3 :+: n) a 
-> Vec (N3 :+: n) a

Set third element

set3 Source

Arguments

:: a 
-> Vec (N4 :+: n) a 
-> Vec (N4 :+: n) a

Set fourth element

getI :: (IsNat n, Show i, Integral i) => i -> Vec n a -> a Source

Variant of get in which the index size is checked at run-time instead of compile-time.

setI :: (IsNat n, Show i, Integral i) => i -> a -> Vec n a -> Vec n a Source

Variant of set in which the index size is checked at run-time instead of compile-time.

flattenV :: IsNat n => Vec n (Vec m a) -> Vec (n :*: m) a Source

Flatten a vector of vectors (a 2D array) into a vector

chunkV :: (IsNat n, IsNat m) => Vec (n :*: m) a -> Vec n (Vec m a) Source

Chunk a vector into a vector of vectors (a 2D array)

swizzle :: Vec n (Index m) -> Vec m a -> Vec n a Source

Swizzling. Extract multiple elements simultaneously.

split :: IsNat n => Vec (n :+: m) a -> (Vec n a, Vec m a) Source

Split a vector

deleteV :: Eq a => a -> Vec (S n) a -> Vec n a Source

Delete exactly one occurrence of an element from a vector, raising an error if the element isn't present.

elemsV :: IsNat n => [a] -> Vec n a Source

Convert a list into a vector. Error if the list is too short or too long

zipV :: Vec n a -> Vec n b -> Vec n (a, b) Source

Zip two vectors into one. Like liftA2 '(,)', but the former requires IsNat n.

zipWithV :: (a -> b -> c) -> Vec n a -> Vec n b -> Vec n c Source

Unzip one vector into two. Like liftA2, but the former requires IsNat n.

unzipV :: Vec n (a, b) -> (Vec n a, Vec n b) Source

Unzip a vector of pairs into a pair of vectors

zipV3 :: Vec n a -> Vec n b -> Vec n c -> Vec n (a, b, c) Source

Zip three vectors into one. Like liftA3 '(,)', but the former requires IsNat n.

zipWithV3 :: (a -> b -> c -> d) -> Vec n a -> Vec n b -> Vec n c -> Vec n d Source

Unzip one vector into two. Like liftA2, but the former requires IsNat n.

unzipV3 :: Vec n (a, b, c) -> (Vec n a, Vec n b, Vec n c) Source

Unzip a vector of pairs into a pair of vectors

transpose :: IsNat n => Vec m (Vec n a) -> Vec n (Vec m a) Source

Matrix transposition. Specialization of sequenceA.

cross :: Vec m a -> Vec n b -> Vec m (Vec n (a, b)) Source

Cross-product of two vectors, in the set-theory sense, not the geometric sense. You can flattenV the resulting vector of vectors.

class ToVec c n a where Source

Methods

toVec :: c -> Vec n a Source

Instances

IsNat n => ToVec [a] n a Source 
ToVec (Vec n a) n a Source