fixed-vector-0.4.0.0: Generic vectors with statically known size.

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. Instance should provide two functions: one to create vector and another for vector deconstruction. They must obey following law:

 inspect v construct = v

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.

basicIndex :: v a -> Int -> aSource

Optional more efficient implementation of indexing. Shouldn't be used directly, use ! instead.

Instances

RealFloat a => Vector Complex a 
~ * b a => Vector ((,) b) a 
Arity n => Vector (VecList n) a 
Arity n => Vector (Vec n) a 
(Arity n, Prim a) => Vector (Vec n) a 
Unbox n a => Vector (Vec n) a 
(Arity n, Storable a) => Vector (Vec n) a 
(~ * b a, ~ * c a) => Vector ((,,) b c) a 
(~ * b a, ~ * c a, ~ * d a) => Vector ((,,,) b c d) a 
(~ * b a, ~ * c a, ~ * d a, ~ * e a) => Vector ((,,,,) b c d e) a 
(~ * b a, ~ * c a, ~ * d a, ~ * e a, ~ * f a) => Vector ((,,,,,) b c d e f) a 
(~ * b a, ~ * c a, ~ * d a, ~ * e a, ~ * f a, ~ * g a) => Vector ((,,,,,,) b c d e f g) a 

class (Vector (v n) a, Dim (v n) ~ n) => VectorN v n a Source

Vector parametrized by length. In ideal world it should be:

 forall n. (Arity n, Vector (v n) a, Dim (v n) ~ n) => VectorN v a

Alas polymorphic constraints aren't allowed in haskell.

Instances

Arity n => VectorN VecList n a 
Arity n => VectorN Vec n a 
(Arity n, Prim a) => VectorN Vec n a 
Unbox n a => VectorN Vec n a 
(Arity n, Storable a) => VectorN 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.

Constructors

In addition to functions list above it's possible to use tuples in conjunction with convert function to create vectors. For example:

v = convert (x,y,z)

It will work on if type of v is know from elsewhere. Same trick could be used to pattern match on the vector with opaque representation using view patterns

 function :: Vec N3 Double -> ...
 function (convert -> (x,y,z)) = ...

mk1 :: (Vector v a, Dim v ~ N1) => a -> v aSource

mk2 :: (Vector v a, Dim v ~ N2) => a -> a -> v aSource

mk3 :: (Vector v a, Dim v ~ N3) => a -> a -> a -> v aSource

mk4 :: (Vector v a, Dim v ~ N4) => a -> a -> a -> a -> v aSource

mk5 :: (Vector v a, Dim v ~ N5) => a -> a -> a -> a -> a -> v aSource

Generic constructor

data New n v a Source

Generic function for construction of arbitrary vectors. It represents partially constructed vector where n is number of uninitialized elements, v is type of vector and a element type.

Uninitialized vector could be obtained from con and vector elements could be added from left to right using |> operator. Finally it could be converted to vector using vec function.

Construction of complex number which could be seen as 2-element vector:

>>> import Data.Complex
>>> vec $ con |> 1 |> 3 :: Complex Double
1.0 :+ 3.0

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

Functions

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

Replicate value n times.

Examples:

>>> import Data.Vector.Fixed.Boxed (Vec2)
>>> replicate 1 :: Vec2 Int
fromList [1,1]
>>> replicate 2 :: (Double,Double,Double)
(2.0,2.0,2.0)
>>> import Data.Vector.Fixed.Boxed (Vec)
>>> replicate "foo" :: Vec N5 String
fromList ["foo","foo","foo","foo","foo"]

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

Execute monadic action for every element of vector.

Examples:

>>> import Data.Vector.Fixed.Boxed (Vec2,Vec3)
>>> replicateM (Just 3) :: Maybe (Vec3 Int)
Just fromList [3,3,3]
>>> replicateM (putStrLn "Hi!") :: IO (Vec2 ())
Hi!
Hi!
fromList [(),()]

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

Generate vector from function which maps element's index to its value.

Examples:

>>> import Data.Vector.Fixed.Unboxed (Vec)
>>> generate (^2) :: Vec N4 Int
fromList [0,1,4,9]

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

Generate vector from monadic function which maps element's index to its value.

unfoldr :: Vector v a => (b -> (a, b)) -> b -> v aSource

Unfold vector.

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

Unit vector along Nth axis. If index is larger than vector dimensions returns zero vector.

Examples:

>>> import Data.Vector.Fixed.Boxed (Vec3)
>>> basis 0 :: Vec3 Int
fromList [1,0,0]
>>> basis 1 :: Vec3 Int
fromList [0,1,0]
>>> basis 3 :: Vec3 Int
fromList [0,0,0]

Modifying vectors

Transformations

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

First element of vector.

Examples:

>>> import Data.Vector.Fixed.Boxed (Vec3)
>>> let x = mk3 1 2 3 :: Vec3 Int
>>> head x
1

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

Tail of vector.

Examples:

>>> import Data.Complex
>>> tail (1,2,3) :: Complex Double
2.0 :+ 3.0

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

Retrieve vector's element at index. Generic implementation is O(n) but more efficient one is used when possible.

Comparison

eq :: (Vector v a, Eq a) => v a -> v a -> BoolSource

Test two vectors for equality.

Examples:

>>> import Data.Vector.Fixed.Boxed (Vec2)
>>> let v0 = basis 0 :: Vec2 Int
>>> let v1 = basis 1 :: Vec2 Int
>>> v0 `eq` v0
True
>>> v0 `eq` v1
False

Maps

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.

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

Apply function to every element of the vector and its index.

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

Apply monadic function to every element of the vector and its index.

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

Apply monadic function to every element of the vector and its index and discard result.

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

Evaluate every action in the vector from left to right.

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

Evaluate every action in the vector from left to right and ignore result

sequenceA :: (Vector v a, Vector v (f a), Applicative f) => v (f a) -> f (v a)Source

Analog of sequenceA from Traversable.

traverse :: (Vector v a, Vector v b, Applicative f) => (a -> f b) -> v a -> f (v b)Source

Analog of traverse from Traversable.

Folding

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

Left fold over vector

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

Right fold over vector

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

Left fold over vector

ifoldl :: Vector v a => (b -> Int -> a -> b) -> b -> v a -> bSource

Left fold over vector. Function is applied to each element and its index.

ifoldr :: Vector v a => (Int -> a -> b -> b) -> b -> v a -> bSource

Left fold over vector

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

Monadic fold over vector.

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

Left monadic fold over vector. Function is applied to each element and its index.

Special folds

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

Maximal element of vector.

Examples:

>>> import Data.Vector.Fixed.Boxed (Vec3)
>>> let x = mk3 1 2 3 :: Vec3 Int
>>> maximum x
3

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

Minimal element of vector.

Examples:

>>> import Data.Vector.Fixed.Boxed (Vec3)
>>> let x = mk3 1 2 3 :: Vec3 Int
>>> minimum x
1

and :: Vector v Bool => v Bool -> BoolSource

Conjunction of all elements of a vector.

or :: Vector v Bool => v Bool -> BoolSource

Disjunction of all elements of a vector.

all :: Vector v a => (a -> Bool) -> v a -> BoolSource

Determines whether all elements of vector satisfy predicate.

any :: Vector v a => (a -> Bool) -> v a -> BoolSource

Determines whether any of element of vector satisfy predicate.

Zips

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

Zip two vector together using function.

Examples:

>>> import Data.Vector.Fixed.Boxed (Vec3)
>>> let b0 = basis 0 :: Vec3 Int
>>> let b1 = basis 1 :: Vec3 Int
>>> let b2 = basis 2 :: Vec3 Int
>>> let vplus x y = zipWith (+) x y
>>> vplus b0 b1
fromList [1,1,0]
>>> vplus b0 b2
fromList [1,0,1]
>>> vplus b1 b2
fromList [0,1,1]

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

Zip two vector together using monadic function.

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

Zip two vector together using function which takes element index as well.

izipWithM :: (Vector v a, Vector v b, Vector v c, Monad m) => (Int -> a -> b -> m c) -> v a -> v b -> m (v c)Source

Zip two vector together using monadic function which takes element index as well..

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 :: Vector v a => [a] -> v aSource

Create vector form list. Will throw error if list is shorter than resulting vector.

Data types

data VecList n a whereSource

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

Constructors

Nil :: VecList Z a 
Cons :: a -> VecList n a -> VecList (S n) a 

Instances

Typeable2 VecList 
Arity n => VectorN VecList n a 
Arity n => Functor (VecList n) 
Arity n => Applicative (VecList n) 
Arity n => Foldable (VecList n) 
Arity n => Traversable (VecList n) 
Arity n => Vector (VecList n) a 
(Eq a, Arity n) => Eq (VecList n a) 
(Show a, Arity n) => Show (VecList n a)