Copyright | (c) Alberto Ruiz 2007-10 |
---|---|
License | GPL |
Maintainer | Alberto Ruiz <aruiz@um.es> |
Stability | provisional |
Safe Haskell | None |
Language | Haskell98 |
1D arrays suitable for numeric computations using external libraries.
This module provides basic functions for manipulation of structure.
- data Vector a :: * -> *
- fromList :: Storable a => [a] -> Vector a
- (|>) :: Storable a => Int -> [a] -> Vector a
- toList :: Storable a => Vector a -> [a]
- buildVector :: Storable a => Int -> (Int -> a) -> Vector a
- dim :: Storable t => Vector t -> Int
- (@>) :: Storable t => Vector t -> Int -> t
- subVector :: Storable t => Int -> Int -> Vector t -> Vector t
- takesV :: Storable t => [Int] -> Vector t -> [Vector t]
- join :: Storable t => [Vector t] -> Vector t
- mapVector :: (Storable a, Storable b) => (a -> b) -> Vector a -> Vector b
- mapVectorWithIndex :: (Storable a, Storable b) => (Int -> a -> b) -> Vector a -> Vector b
- zipVector :: (Storable a, Storable b, Storable (a, b)) => Vector a -> Vector b -> Vector (a, b)
- zipVectorWith :: (Storable a, Storable b, Storable c) => (a -> b -> c) -> Vector a -> Vector b -> Vector c
- unzipVector :: (Storable a, Storable b, Storable (a, b)) => Vector (a, b) -> (Vector a, Vector b)
- unzipVectorWith :: (Storable (a, b), Storable c, Storable d) => ((a, b) -> (c, d)) -> Vector (a, b) -> (Vector c, Vector d)
- mapVectorM :: (Storable a, Storable b, Monad m) => (a -> m b) -> Vector a -> m (Vector b)
- mapVectorM_ :: (Storable a, Monad m) => (a -> m ()) -> Vector a -> m ()
- mapVectorWithIndexM :: (Storable a, Storable b, Monad m) => (Int -> a -> m b) -> Vector a -> m (Vector b)
- mapVectorWithIndexM_ :: (Storable a, Monad m) => (Int -> a -> m ()) -> Vector a -> m ()
- foldLoop :: (Int -> t -> t) -> t -> Int -> t
- foldVector :: Storable a => (a -> b -> b) -> b -> Vector a -> b
- foldVectorG :: Storable t1 => (Int -> (Int -> t1) -> t -> t) -> t -> Vector t1 -> t
- foldVectorWithIndex :: Storable a => (Int -> a -> b -> b) -> b -> Vector a -> b
Documentation
data Vector a :: * -> *
Storable
-based vectors
(|>) :: Storable a => Int -> [a] -> Vector a infixl 9 Source
An alternative to fromList
with explicit dimension. The input
list is explicitly truncated if it is too long, so it may safely
be used, for instance, with infinite lists.
This is the format used in the instances for Show (Vector a).
toList :: Storable a => Vector a -> [a] Source
extracts the Vector elements to a list
> toList (linspace 5 (1,10)) [1.0,3.25,5.5,7.75,10.0]
buildVector :: Storable a => Int -> (Int -> a) -> Vector a Source
creates a Vector of the specified length using the supplied function to to map the index to the value at that index.
> buildVector 4 fromIntegral 4 |> [0.0,1.0,2.0,3.0]
(@>) :: Storable t => Vector t -> Int -> t infixl 9 Source
Reads a vector position:
> fromList [0..9] @> 7 7.0
:: Storable t | |
=> Int | index of the starting element |
-> Int | number of elements to extract |
-> Vector t | source |
-> Vector t | result |
takes a number of consecutive elements from a Vector
> subVector 2 3 (fromList [1..10]) 3 |> [3.0,4.0,5.0]
takesV :: Storable t => [Int] -> Vector t -> [Vector t] Source
Extract consecutive subvectors of the given sizes.
> takesV [3,4] (linspace 10 (1,10)) [3 |> [1.0,2.0,3.0],4 |> [4.0,5.0,6.0,7.0]]
join :: Storable t => [Vector t] -> Vector t Source
creates a new Vector by joining a list of Vectors
> join [fromList [1..5], constant 1 3] 8 |> [1.0,2.0,3.0,4.0,5.0,1.0,1.0,1.0]
zipVector :: (Storable a, Storable b, Storable (a, b)) => Vector a -> Vector b -> Vector (a, b) Source
zip for Vectors
zipVectorWith :: (Storable a, Storable b, Storable c) => (a -> b -> c) -> Vector a -> Vector b -> Vector c Source
zipWith for Vectors
unzipVector :: (Storable a, Storable b, Storable (a, b)) => Vector (a, b) -> (Vector a, Vector b) Source
unzip for Vectors
unzipVectorWith :: (Storable (a, b), Storable c, Storable d) => ((a, b) -> (c, d)) -> Vector (a, b) -> (Vector c, Vector d) Source
unzipWith for Vectors
mapVectorM :: (Storable a, Storable b, Monad m) => (a -> m b) -> Vector a -> m (Vector b) Source
monadic map over Vectors
the monad m
must be strict
mapVectorM_ :: (Storable a, Monad m) => (a -> m ()) -> Vector a -> m () Source
monadic map over Vectors
mapVectorWithIndexM :: (Storable a, Storable b, Monad m) => (Int -> a -> m b) -> Vector a -> m (Vector b) Source
monadic map over Vectors with the zero-indexed index passed to the mapping function
the monad m
must be strict
mapVectorWithIndexM_ :: (Storable a, Monad m) => (Int -> a -> m ()) -> Vector a -> m () Source
monadic map over Vectors with the zero-indexed index passed to the mapping function
foldVector :: Storable a => (a -> b -> b) -> b -> Vector a -> b Source
foldVectorWithIndex :: Storable a => (Int -> a -> b -> b) -> b -> Vector a -> b Source