fixed-vector-0.1.1: Generic vectors with fixed length

Safe HaskellNone

Data.Vector.Fixed

Contents

Description

Generic API for vectors with fixed length.

For encoding of vector size library uses Peano naturals defined in the library. At come point in the future it would make sense to switch to new GHC type level numerals.

Synopsis

Vector type class

Vector size

type family Dim v Source

Size of vector expressed as type-level natural.

data Z Source

Type level zero

Instances

data S n Source

Successor of n

Instances

Arity n => Arity (S n) 

Synonyms for small numerals

type N1 = S ZSource

type N2 = S N1Source

type N3 = S N2Source

type N4 = S N3Source

type N5 = S N4Source

type N6 = S N5Source

Type class

class Arity (Dim v) => Vector v a whereSource

Type class for vectors with fixed length.

Methods

construct :: Fun (Dim v) a (v a)Source

N-ary function for creation of vectors.

inspect :: v a -> Fun (Dim v) a b -> bSource

Deconstruction of vector.

Instances

(Arity (Dim Complex), RealFloat a) => Vector Complex a 
(Arity (Dim (VecList n)), Arity n) => Vector (VecList n) a 
(Arity (Dim (Vec n)), Arity n) => Vector (Vec n) a 
(Arity (Dim (Vec n)), Arity n, Prim a) => Vector (Vec n) a 
(Arity (Dim (Vec n)), Unbox n a) => Vector (Vec n) a 
(Arity (Dim (Vec n)), Arity n, Storable a) => Vector (Vec n) a 

class Arity n Source

Type class for handling n-ary functions.

Instances

Arity Z 
Arity n => Arity (S n) 

newtype Fun n a b Source

Newtype wrapper which is used to make Fn injective.

Constructors

Fun (Fn n a b) 

Instances

Arity n => Functor (Fun n a) 

length :: forall v a. Arity (Dim v) => v a -> IntSource

Length of vector. Function doesn't evaluate its argument.

convertContinuation :: forall n a r. Arity n => (forall v. (Dim v ~ n, Vector v a) => v a -> r) -> Fun n a rSource

Change continuation type.

Generic functions

Literal vectors

data New n v a Source

Newtype wrapper for partially constructed vectors. n is number of uninitialized elements.

Example of use:

>>> vec $ con |> 1 |> 3 :: Complex Double
> 1 :+ 3

vec :: New Z v a -> v aSource

Convert fully applied constructor to vector

con :: Vector v a => New (Dim v) v aSource

Seed constructor

(|>) :: New (S n) v a -> a -> New n v aSource

Apply another element to vector

Construction

replicate :: Vector v a => a -> v aSource

Replicate value n times.

replicateM :: (Vector v a, Monad m) => m a -> m (v a)Source

Execute monadic action for every element of vector.

basis :: forall v a. (Vector v a, Num a) => Int -> v aSource

Unit vector along Nth axis,

generate :: forall v a. Vector v a => (Int -> a) -> v aSource

Generate vector.

generateM :: forall m v a. (Monad m, Vector v a) => (Int -> m a) -> m (v a)Source

Monadic generation

Element access

head :: (Vector v a, Dim v ~ S n) => v a -> aSource

First element of vector.

tail :: (Vector v a, Vector w a, Dim v ~ S (Dim w)) => v a -> w aSource

Tail of vector.

tailWithSource

Arguments

:: (Arity n, Vector v a, Dim v ~ S n) 
=> (forall w. (Vector w a, Dim w ~ n) => w a -> r)

Continuation

-> v a

Vector

-> r 

Continuation variant of tail. It should be used when tail of vector is immediately deconstructed with polymorphic function. For example sum . tail will fail with unhelpful error message because return value of tail is polymorphic. But tailWith sum works just fine.

(!) :: Vector v a => v a -> Int -> aSource

O(n) Get vector's element at index i.

Map

map :: (Vector v a, Vector v b) => (a -> b) -> v a -> v bSource

Map over vector

mapM :: (Vector v a, Vector v b, Monad m) => (a -> m b) -> v a -> m (v b)Source

Monadic map over vector.

mapM_ :: (Vector v a, Monad m) => (a -> m b) -> v a -> m ()Source

Apply monadic action to each element of vector and ignore result.

Folding

foldl :: Vector v a => (b -> a -> b) -> b -> v a -> bSource

Left fold over vector

foldl1 :: (Vector v a, Dim v ~ S n) => (a -> a -> a) -> v a -> aSource

Left fold over vector

foldM :: (Vector v a, Monad m) => (b -> a -> m b) -> b -> v a -> m bSource

Monadic fold over vector.

sum :: (Vector v a, Num a) => v a -> aSource

Sum all elements in the vector

maximum :: (Vector v a, Dim v ~ S n, Ord a) => v a -> aSource

Maximum element of vector

minimum :: (Vector v a, Dim v ~ S n, Ord a) => v a -> aSource

Minimum element of vector

Zips

zipWith :: (Vector v a, Vector v b, Vector v c) => (a -> b -> c) -> v a -> v b -> v cSource

Zip two vector together.

izipWith :: (Vector v a, Vector v b, Vector v c) => (Int -> a -> b -> c) -> v a -> v b -> v cSource

Zip two vector together.

Conversion

convert :: (Vector v a, Vector w a, Dim v ~ Dim w) => v a -> w aSource

Convert between different vector types

toList :: Vector v a => v a -> [a]Source

Convert vector to the list

fromList :: forall v a. Vector v a => [a] -> v aSource

Create vector form list. List must have same length as the vector.

Special types

newtype VecList n a Source

Vector based on the lists. Not very useful by itself but is necessary for implementation.

Constructors

VecList [a] 

Instances

(Arity (Dim (VecList n)), Arity n) => Vector (VecList n) a 
Eq a => Eq (VecList n a) 
Show a => Show (VecList n a)