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
- class Arity (Dim v) => Vector v a where
- class Arity n
- length :: forall v a. Arity (Dim v) => v a -> Int
- 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
- (!) :: 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 ()
- 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
- 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
- izipWith :: (Vector v a, Vector v b, Vector v c) => (Int -> a -> b -> c) -> v a -> v b -> 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
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 |
Type class for handling n-ary functions.
length :: forall v a. Arity (Dim v) => v a -> IntSource
Length of vector. Function doesn't evaluate its argument.
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.
Folding
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
fromList :: forall v a. Vector v a => [a] -> v aSource
Create vector form list. List must have same length as the vector.