hmatrix-static-0.2: hmatrix with vector and matrix sizes encoded in typesSource codeContentsIndex
Data.Packed.Static.Vector
Portabilityportable
Stabilityexperimental
MaintainerReiner Pope <reiner.pope@gmail.com>
Contents
Shaping
To/from lists
Manipulation
Description
Statically-dimensioned 1D vectors.
Synopsis
data Vector n t
refineVec :: forall m t a. Vector m t -> (forall n. PositiveT n => Vector n t -> a) -> a
atDim :: (forall n. PositiveT n => Vector n t) -> Int -> Vector Unknown t
atShape :: a s t -> s -> a s t
fromListU :: Storable a => [a] -> Vector Unknown a
toList :: Storable a => Vector n a -> [a]
dim :: Vector n t -> Int
(@>) :: Storable t => Vector n t -> Int -> t
subVectorU :: Storable t => Int -> Int -> Vector n t -> Vector Unknown t
joinU :: Storable t => [Vector Unknown t] -> Vector Unknown t
constant :: (Element t, PositiveT n) => t -> Vector n t
linspace :: PositiveT n => (Double, Double) -> Vector n Double
vectorMin :: Vector n Double -> Double
vectorMax :: Vector n Double -> Double
vectorMinIndex :: Vector n Double -> Int
vectorMaxIndex :: Vector n Double -> Int
liftVector :: (Storable a, Storable b) => (a -> b) -> Vector n a -> Vector n b
liftVector2 :: (Storable a, Storable b, Storable c) => (a -> b -> c) -> Vector n a -> Vector n b -> Vector n c
Documentation
data Vector n t Source

A vector with elements of type t and length n. The type n encodes the vector's length, and will usually either be Unknown or will satisfy PositiveT.

Operations which return vectors of length Unknown will return vectors whose lengths are determined at runtime. All operations which mention Unknown lengths will have names ending in an uppercase U, for example fromListU, subVectorU.

The use of Unknown facilitates manipulation of dynamically-lengthed vectors without using continuations for each operation, since most operations work equally well for lengthed as well as unlengthed vectors. When vectors of Unknown length are used, runtime length mismatches may arise, and the system is as safe as hmatrix.

When the length of every vector is known, if the code typechecks, then there will be no runtime vector length mismatches. Equivalently, there will be no runtime vector length mismatches if:

  • no unsafe functions are used; and
  • no functions mentioning Unknown are used, i.e. no functions with suffix U are used.
show/hide Instances
ShapedContainer Vector
JoinableH (Matrix ((,) m n)) (Vector m)
JoinableH (Vector m) (Vector m)
JoinableH (Vector m) (Matrix ((,) m n))
JoinableV (Matrix ((,) m n)) (Vector n)
JoinableV (Vector n) (Vector n)
JoinableV (Vector n) (Matrix ((,) m n))
n ~ n' => Mul (Matrix ((,) m n)) (Vector n')
m ~ m' => Mul (Vector m) (Matrix ((,) m' n))
(Storable e, Show e) => Show (Vector n e)
Shaping
Functions manipulating a vector's (static) shape.
refineVec :: forall m t a. Vector m t -> (forall n. PositiveT n => Vector n t -> a) -> aSource

"Reifies" a Vector's length in types. Useful when vectors of length Unknown need to be used for a statically-sized operations. For instance, if v :: Vector Unknown Double, then we can write

refineVec v (v -> forgetSize $ v + constant 5)

to add a constant vector of 5s with the appropriate size.

atDim :: (forall n. PositiveT n => Vector n t) -> Int -> Vector Unknown tSource

Sets an arbitrary-length vector to a specific value.

> constant 1 atDim 5
[$vec| 1.0, 1.0, 1.0, 1.0, 1.0 |]
atShape :: a s t -> s -> a s tSource

For type hints.

> constant (5::Double) atShape d4
 [$vec| 5.0, 5.0, 5.0, 5.0 |] :: Vector D4 Double

Implementation:

atShape = const.

To/from lists
fromListU :: Storable a => [a] -> Vector Unknown aSource

Constructs a vector from all the elements of a list.

> fromListU [1,2,3,4,5]
[$vec| 1.0, 2.0, 3.0, 4.0, 5.0 |]
toList :: Storable a => Vector n a -> [a]Source

Converts to a list of elements.

> toList [$vec|1,2,3|]
[1.0,2.0,3.0]
Manipulation
dim :: Vector n t -> IntSource

Vector's length.

> dim [$vec|1::Double,2,3|]
3
(@>) :: Storable t => Vector n t -> Int -> tSource

Indexes a vector.

> [$vec|1,2,3|] @> 1
2.0
subVectorUSource
:: Storable t
=> IntInitial index
-> IntLength of resultant vector
-> Vector n t
-> Vector Unknown t

Extracts a subvector.

> subVectorU 2 3 [$vec|1,2,3,4,5|]
[$vec| 3.0, 4.0, 5.0 |]
joinU :: Storable t => [Vector Unknown t] -> Vector Unknown tSource

Joins each vector in the list.

> joinU [[$vecU|1,2,3|], [$vecU|4,5|]]
[$vec| 1.0, 2.0, 3.0, 4.0, 5.0 |]
constant :: (Element t, PositiveT n) => t -> Vector n tSource

Creates a constant vector of any length. The length is determined by the type.

> [$vec|1,2,3|] + constant 2
[$vec| 3.0, 4.0, 5.0 |]
linspace :: PositiveT n => (Double, Double) -> Vector n DoubleSource

Creates a vector of arbitrary length whose components range linearly from a to b. The vector's length is determined by its type.

> linspace (1,5) atShape d4
[$vec| 1.0, 2.333333333333333, 3.6666666666666665, 5.0 |]
vectorMin :: Vector n Double -> DoubleSource

Gives the vector's minimum entry.

> vectorMin [$vec|1,2,3|]
1.0
vectorMax :: Vector n Double -> DoubleSource

Gives the vector's maximum entry.

> vectorMax [$vec|1,2,3|]
3.0
vectorMinIndex :: Vector n Double -> IntSource
Gives the index of a vector's minimum entry. > vectorMinIndex [$vec|1,2,3|] 0
vectorMaxIndex :: Vector n Double -> IntSource

Gives the index of a vector's maximum entry.

> vectorMaxIndex [$vec|1,2,3|]
2
liftVector :: (Storable a, Storable b) => (a -> b) -> Vector n a -> Vector n bSource

map for vectors.

> (*2) liftVector [$vec|1,2,3|]
[$vec| 2.0, 4.0, 6.0 |]
liftVector2 :: (Storable a, Storable b, Storable c) => (a -> b -> c) -> Vector n a -> Vector n b -> Vector n cSource

zipWith for vectors.

> liftVector2 (+) [$vec|1,2,3|] (constant 3)
[$vec| 4.0, 5.0, 6.0 |]
Produced by Haddock version 2.4.2