hmatrix-0.11.0.4: Linear algebra and numerical computation

Stabilityprovisional
MaintainerAlberto Ruiz <[email protected]>

Data.Packed.Vector

Description

1D arrays suitable for numeric computations using external libraries.

This module provides basic functions for manipulation of structure.

Synopsis

Documentation

fromList :: Storable a => [a] -> Vector aSource

creates a Vector from a list:

> fromList [2,3,5,7]
4 |> [2.0,3.0,5.0,7.0]

(|>) :: Storable a => Int -> [a] -> Vector aSource

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 aSource

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]

dim :: Storable t => Vector t -> IntSource

Number of elements

(@>) :: Storable t => Vector t -> Int -> tSource

Reads a vector position:

> fromList [0..9] @> 7
7.0

subVectorSource

Arguments

:: 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 tSource

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]

mapVector :: (Storable a, Storable b) => (a -> b) -> Vector a -> Vector bSource

map on Vectors

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 cSource

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

foldLoop :: (Int -> t -> t) -> t -> Int -> tSource

foldVector :: Storable a => (a -> b -> b) -> b -> Vector a -> bSource

foldVectorG :: Storable t1 => (Int -> (Int -> t1) -> t -> t) -> t -> Vector t1 -> tSource

foldVectorWithIndex :: Storable a => (Int -> a -> b -> b) -> b -> Vector a -> bSource