Safe Haskell | None |
---|
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.
- type family Dim v
- data Z
- data S n
- type N1 = S Z
- type N2 = S N1
- type N3 = S N2
- type N4 = S N3
- type N5 = S N4
- type N6 = S N5
- class Arity (Dim v) => Vector v a where
- class (Vector (v n) a, Dim (v n) ~ n) => VectorN v n a
- class Arity n
- newtype Fun n a b = Fun (Fn n a b)
- length :: forall v a. Arity (Dim v) => v a -> Int
- convertContinuation :: forall n a r. Arity n => (forall v. (Dim v ~ n, Vector v a) => v a -> r) -> Fun n a r
- data New n v a
- vec :: New Z v a -> v a
- con :: Vector v a => New (Dim v) v a
- (|>) :: New (S n) v a -> a -> New n v a
- replicate :: Vector v a => a -> v a
- replicateM :: (Vector v a, Monad m) => m a -> m (v a)
- basis :: forall v a. (Vector v a, Num a) => Int -> v a
- generate :: forall v a. Vector v a => (Int -> a) -> v a
- generateM :: forall m v a. (Monad m, Vector v a) => (Int -> m a) -> m (v a)
- head :: (Vector v a, Dim v ~ S n) => v a -> a
- tail :: (Vector v a, Vector w a, Dim v ~ S (Dim w)) => v a -> w a
- tailWith :: (Arity n, Vector v a, Dim v ~ S n) => (forall w. (Vector w a, Dim w ~ n) => w a -> r) -> v a -> r
- (!) :: Vector v a => v a -> Int -> a
- map :: (Vector v a, Vector v b) => (a -> b) -> v a -> v b
- mapM :: (Vector v a, Vector v b, Monad m) => (a -> m b) -> v a -> m (v b)
- mapM_ :: (Vector v a, Monad m) => (a -> m b) -> v a -> m ()
- imap :: (Vector v a, Vector v b, Monad m) => (Int -> a -> b) -> v a -> v b
- imapM :: (Vector v a, Vector v b, Monad m) => (Int -> a -> m b) -> v a -> m (v b)
- imapM_ :: (Vector v a, Monad m) => (Int -> a -> m b) -> v a -> m ()
- sequence :: (Vector v a, Vector v (m a), Monad m) => v (m a) -> m (v a)
- sequence_ :: (Vector v (m a), Monad m) => v (m a) -> m ()
- foldl :: Vector v a => (b -> a -> b) -> b -> v a -> b
- foldl1 :: (Vector v a, Dim v ~ S n) => (a -> a -> a) -> v a -> a
- foldM :: (Vector v a, Monad m) => (b -> a -> m b) -> b -> v a -> m b
- ifoldl :: Vector v a => (b -> Int -> a -> b) -> b -> v a -> b
- ifoldM :: (Vector v a, Monad m) => (b -> Int -> a -> m b) -> b -> v a -> m b
- sum :: (Vector v a, Num a) => v a -> a
- maximum :: (Vector v a, Dim v ~ S n, Ord a) => v a -> a
- minimum :: (Vector v a, Dim v ~ S n, Ord a) => v a -> a
- zipWith :: (Vector v a, Vector v b, Vector v c) => (a -> b -> c) -> v a -> v b -> v c
- zipWithM :: (Vector v a, Vector v b, Vector v c, Monad m) => (a -> b -> m c) -> v a -> v b -> m (v c)
- izipWith :: (Vector v a, Vector v b, Vector v c) => (Int -> a -> b -> c) -> v a -> v b -> v c
- izipWithM :: (Vector v a, Vector v b, Vector v c, Monad m) => (Int -> a -> b -> m c) -> v a -> v b -> m (v c)
- convert :: (Vector v a, Vector w a, Dim v ~ Dim w) => v a -> w a
- toList :: Vector v a => v a -> [a]
- fromList :: forall v a. Vector v a => [a] -> v a
- newtype VecList n a = VecList [a]
Vector type class
Vector size
Synonyms for small numerals
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 (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
(Vector (VecList n) a, ~ * (Dim (VecList n)) n, Arity n) => VectorN VecList n a | |
(Vector (Vec n) a, ~ * (Dim (Vec n)) n, Arity n) => VectorN Vec n a | |
(Vector (Vec n) a, ~ * (Dim (Vec n)) n, Arity n, Prim a) => VectorN Vec n a | |
(Vector (Vec n) a, ~ * (Dim (Vec n)) n, Unbox n a) => VectorN Vec n a | |
(Vector (Vec n) a, ~ * (Dim (Vec n)) n, Arity n, Storable a) => VectorN Vec n a |
Type class for handling n-ary functions.
Newtype wrapper which is used to make Fn
injective.
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
Newtype wrapper for partially constructed vectors. n is number of uninitialized elements.
Example of use:
>>>
vec $ con |> 1 |> 3 :: Complex Double
> 1 :+ 3
Construction
replicateM :: (Vector v a, Monad m) => m a -> m (v a)Source
Execute monadic action for every element of vector.
Element access
Map
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, Monad m) => (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
Folding
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.
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
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.
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
fromList :: forall v a. Vector v a => [a] -> v aSource
Create vector form list. List must have same length as the vector.
Special types
Vector based on the lists. Not very useful by itself but is necessary for implementation.
Constructors
VecList [a] |