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

Safe HaskellNone
LanguageHaskell98

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.

Common pitfalls

Library provide instances for tuples. But there's a catch. Tuples are monomorphic in element type. Let consider 2-tuple (Int,Int). Vector type v is (,) Int and only allowed element type is Int. Because of that we cannot change element type and following code will fail:

>>> map (== 1) ((1,2) :: (Int,Int))

<interactive>:3:1:
    Couldn't match type `Int' with `Bool'
    In the expression: F.map (== 1) ((1, 2) :: (Int, Int))
    In an equation for `it': it = map (== 1) ((1, 2) :: (Int, Int))

To make it work we need to change vector type as well. Functions from module Data.Vector.Fixed.Generic provide this functionality.

>>> map (== 1) ((1,2) :: (Int,Int)) :: (Bool,Bool)
(True,False)

Synopsis

Vector type class

Vector size

type family Dim v Source

Size of vector expressed as type-level natural.

Instances

type Dim Complex = N2 
type Dim Empty = Z 
type Dim Only = S Z 
type Dim ((,) a) = N2 
type Dim (Proxy *) = Z 
type Dim (ContVec n) = n 
type Dim (VecList n) = n 
type Dim (Vec n) = n 
type Dim (Vec n) = n 
type Dim (Vec n) = n 
type Dim (Vec n) = n 
type Dim ((,,) a b) = N3 
type Dim ((,,,) a b c) = N4 
type Dim ((,,,,) a b c d) = N5 
type Dim ((,,,,,) a b c d e) = N6 
type Dim ((,,,,,,) a b c d e f) = S N6 

data Z Source

Type level zero

Instances

Arity Z 
Typeable * Z 
NatIso Z 0 
Arity n => Index Z (S n) 
type Add Z n = n 
type Fn Z a b = b 

data S n Source

Successor of n

Instances

Arity n => Index Z (S n) 
Arity n => Arity (S n) 
(NatIso k ((-) n 1), (~) * (ToPeano ((-) n 1)) k, (~) * (ToPeano n) (S k), (~) Nat n ((+) 1 ((-) n 1))) => NatIso (S k) n 
Index k n => Index (S k) (S n) 
Typeable (* -> *) S 
type Add (S n) k = S (Add n k) 
type Fn (S n) a b = a -> Fn n a b 

Synonyms for small numerals

type N1 = S Z Source

type N2 = S N1 Source

type N3 = S N2 Source

type N4 = S N3 Source

type N5 = S N4 Source

type N6 = S N5 Source

Type class

class Arity (Dim v) => Vector v a where Source

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

Minimal complete definition

construct, inspect

Methods

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

N-ary function for creation of vectors.

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

Deconstruction of vector.

basicIndex :: v a -> Int -> a Source

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

Instances

RealFloat a => Vector Complex a 
Vector Empty a 
Vector Only a 
(~) * b a => Vector ((,) b) a

Note this instance (and other instances for tuples) is essentially monomorphic in element type. Vector type v of 2 element tuple (Int,Int) is (,) Int so it will only work with elements of type Int.

Vector (Proxy *) a 
Arity n => Vector (ContVec n) 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 ContVec n a 
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.

Minimal complete definition

accum, applyFun, applyFunM, arity, reverseF, gunfoldF, witSum

Instances

Arity Z 
Arity n => Arity (S n) 

newtype Fun n a b Source

Newtype wrapper which is used to make Fn injective. It's also a reader monad.

Constructors

Fun 

Fields

unFun :: Fn n a b
 

Instances

Arity n => Monad (Fun n a) 
Arity n => Functor (Fun n a) 
Arity n => Applicative (Fun n a) 

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

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

Constructors

There are several ways to construct fixed vectors except using their constructor if it's available. For small ones it's possible to use functions mk1, mk2, etc.

>>> mk3 'a' 'b' 'c' :: (Char,Char,Char)
('a','b','c')

Another option is to create tuple and convert it to desired vector type. 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)) = ...

Third way is to use variadic function mkN. It works similarly to printf except it produces result of type ContVec which should be converted to vector of desired type by vector:

>>> vector $ mkN 'a' 'b' 'c' :: (Char,Char,Char)
('a','b','c')

Probably most generic way is to cons values to the ContVec and convert it vector of desired type using vector:

>>> vector $ 'a' <| 'b' <| 'c' <| empty :: (Char,Char,Char)
('a','b','c')

mk0 :: (Vector v a, Dim v ~ Z) => v a Source

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

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

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

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

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

Consing

data ContVec n a Source

Vector represented as continuation. Alternative wording: it's Church encoded N-element vector.

Instances

Arity n => VectorN ContVec n a 
Arity n => Make n a (ContVec n a) 
Arity n => Functor (ContVec n) 
Arity n => Applicative (ContVec n) 
Arity n => Foldable (ContVec n) 
Arity n => Traversable (ContVec n) 
Arity n => Vector (ContVec n) a 
type Dim (ContVec n) = n 

empty :: ContVec Z a Source

Create empty vector.

vector :: (Vector v a, Dim v ~ n) => ContVec n a -> v a Source

Convert continuation to the vector.

(<|) :: a -> ContVec n a -> ContVec (S n) a infixr 1 Source

Cons value to continuation based vector.

Variadic function

class Make n a r Source

Type class for variadic vector constructors.

Minimal complete definition

make

Instances

Arity n => Make n a (ContVec n a) 
((~) * a' a, Make (S n) a r) => Make n a' (a -> r) 

mkN :: Make (S Z) a r => a -> r Source

Variadic vector constructor. Resulting vector should be converted from ContVec using vector function. For example:

>>> vector $ mkN 'a' 'b' 'c' :: (Char,Char,Char)
('a','b','c')

Functions

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

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 (Vec4)
>>> replicate "foo" :: Vec4 String
fromList ["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 a Source

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

Examples:

>>> import Data.Vector.Fixed.Unboxed (Vec4)
>>> generate (^2) :: Vec4 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 a Source

Unfold vector.

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

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

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

Tail of vector.

Examples:

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

cons :: (Vector v a, Vector w a, S (Dim v) ~ Dim w) => a -> v a -> w a Source

Cons element to the vector

snoc :: (Vector v a, Vector w a, S (Dim v) ~ Dim w) => a -> v a -> w a Source

Append element to the vector

concat :: (Vector v a, Vector u a, Vector w a, Add (Dim v) (Dim u) ~ Dim w) => v a -> u a -> w a Source

reverse :: Vector v a => v a -> v a Source

Reverse order of elements in the vector

Indexing & lenses

class Index k n Source

Type class for indexing of vector when index value is known at compile time.

Minimal complete definition

getF, putF, lensF

Instances

Arity n => Index Z (S n) 
Index k n => Index (S k) (S n) 

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

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

index :: (Vector v a, Index k (Dim v)) => v a -> k -> a Source

Get element from vector at statically known index

set :: (Vector v a, Index k (Dim v)) => k -> a -> v a -> v a Source

Set n'th element in the vector

element :: (Vector v a, Functor f) => Int -> (a -> f a) -> v a -> f (v a) Source

Twan van Laarhoven's lens for element of vector

elementTy :: (Vector v a, Index k (Dim v), Functor f) => k -> (a -> f a) -> v a -> f (v a) Source

Twan van Laarhoven's lens for element of vector with statically known index.

Comparison

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

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

ord :: (Vector v a, Ord a) => v a -> v a -> Ordering Source

Lexicographic ordering of two vectors.

Maps

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

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

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.

scanl :: (Vector v a, Vector w b, Dim w ~ S (Dim v)) => (b -> a -> b) -> b -> v a -> w b Source

Left scan over vector

scanl1 :: Vector v a => (a -> a -> a) -> v a -> v a Source

Left scan over vector

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.

distribute :: (Vector v a, Vector v (f a), Functor f) => f (v a) -> v (f a) Source

collect :: (Vector v a, Vector v b, Vector v (f b), Functor f) => (a -> v b) -> f a -> v (f b) Source

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

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

Folding

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

Left fold over vector

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

Right fold over vector

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

Left fold over vector

fold :: (Vector v m, Monoid m) => v m -> m Source

Combine the elements of a structure using a monoid. Similar to fold

foldMap :: (Vector v a, Monoid m) => (a -> m) -> v a -> m Source

Map each element of the structure to a monoid, and combine the results. Similar to foldMap

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

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

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

Right fold over vector

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

Monadic fold over vector.

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

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

Special folds

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

Sum all elements in the vector.

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

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

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

Conjunction of all elements of a vector.

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

Disjunction of all elements of a vector.

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

Determines whether all elements of vector satisfy predicate.

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

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

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

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

Convert between different vector types

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

Convert vector to the list

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

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

fromList' :: Vector v a => [a] -> v a Source

Create vector form list. Will throw error if list has different length from resulting vector.

fromListM :: Vector v a => [a] -> Maybe (v a) Source

Create vector form list. Will return Nothing if list has different length from resulting vector.

fromFoldable :: (Vector v a, Foldable f) => f a -> Maybe (v a) Source

Create vector from Foldable data type. Will return Nothing if data type different number of elements that resulting vector.

Data types

data VecList n a where Source

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

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) 
(Ord a, Arity n) => Ord (VecList n a) 
(Show a, Arity n) => Show (VecList n a) 
(Arity n, Monoid a) => Monoid (VecList n a) 
Typeable (* -> * -> *) VecList 
type Dim (VecList n) = n 

newtype Only a Source

Single-element tuple.

Constructors

Only a 

Instances

Functor Only 
Foldable Only 
Traversable Only 
Vector Only a 
Eq a => Eq (Only a) 
Data a => Data (Only a) 
Ord a => Ord (Only a) 
Show a => Show (Only a) 
Monoid a => Monoid (Only a) 
Typeable (* -> *) Only 
type Dim Only = S Z 

data Empty a Source

Empty tuple.

Constructors

Empty 

Instances

Tuple synonyms

type Tuple2 a = (a, a) Source

type Tuple3 a = (a, a, a) Source

type Tuple4 a = (a, a, a, a) Source

type Tuple5 a = (a, a, a, a, a) Source