goal-core-0.20: Common, non-geometric tools for use with Goal
Safe HaskellNone
LanguageHaskell2010

Goal.Core.Vector.Storable

Description

Vectors and Matrices with statically typed dimensions based on storable vectors and using HMatrix where possible.

Synopsis

Vector

Construction

doubleton :: Storable x => x -> x -> Vector 2 x Source #

Collect two values into a length 2 Vector.

range :: (KnownNat n, Fractional x, Storable x) => x -> x -> Vector n x Source #

Uniform partition of an interval into a Vector.

Deconstruction

concat :: (KnownNat n, Storable x) => Vector m (Vector n x) -> Vector (m * n) x Source #

Concatenates a vector of vectors into a single vector.

breakEvery :: forall n k a. (KnownNat n, KnownNat k, Storable a) => Vector (n * k) a -> Vector n (Vector k a) Source #

Breaks a Vector into a Vector of Vectors.

toPair :: Storable x => Vector 2 x -> (x, x) Source #

Reshapes a length 2 Vector into a pair of values.

Computation

average :: (Numeric x, Fractional x) => Vector n x -> x Source #

The average of a Vector of elements.

zipFold :: (KnownNat n, Storable x, Storable y) => (z -> x -> y -> z) -> z -> Vector n x -> Vector n y -> z Source #

A fold over pairs of elements of Vectors of equal length.

Matrix

type Matrix = Matrix Vector Source #

Matrices with static dimensions (storable).

nRows :: forall m n a. KnownNat m => Matrix m n a -> Int Source #

The number of rows in the Matrix.

nColumns :: forall m n a. KnownNat n => Matrix m n a -> Int Source #

The columns of columns in the Matrix.

Construction

fromRows :: (KnownNat n, Storable x) => Vector m (Vector n x) -> Matrix m n x Source #

Create a Matrix from a Vector of Vectors which represent the rows.

fromColumns :: (KnownNat m, KnownNat n, Numeric x) => Vector n (Vector m x) -> Matrix m n x Source #

Create a Matrix from a Vector of Vectors which represent the columns.

matrixIdentity :: forall n x. (KnownNat n, Numeric x, Num x) => Matrix n n x Source #

The identity Matrix.

outerProduct :: (KnownNat m, KnownNat n, Numeric x) => Vector m x -> Vector n x -> Matrix m n x Source #

The outer product of two Vectors.

sumOuterProduct :: (KnownNat m, KnownNat n, Fractional x, Numeric x) => [(Vector m x, Vector n x)] -> Matrix m n x Source #

The summed outer product of two lists of Vectors.

averageOuterProduct :: (KnownNat m, KnownNat n, Fractional x, Numeric x) => [(Vector m x, Vector n x)] -> Matrix m n x Source #

The average outer product of two lists of Vectors.

weightedAverageOuterProduct :: (KnownNat m, KnownNat n, Fractional x, Numeric x) => [(x, Vector m x, Vector n x)] -> Matrix m n x Source #

The average outer product of two lists of Vectors.

diagonalMatrix :: forall n x. (KnownNat n, Field x) => Vector n x -> Matrix n n x Source #

The determinant of a Matrix.

fromLowerTriangular :: forall n x. (Storable x, KnownNat n) => Vector (Triangular n) x -> Matrix n n x Source #

Constructs a Matrix from a lower triangular part.

Deconstruction

toRows :: (KnownNat m, KnownNat n, Storable x) => Matrix m n x -> Vector m (Vector n x) Source #

Convert a Matrix into a Vector of Vectors of rows.

toColumns :: (KnownNat m, KnownNat n, Numeric x) => Matrix m n x -> Vector n (Vector m x) Source #

Convert a Matrix into a Vector of Vectors of columns.

lowerTriangular :: forall n x. (Storable x, Element x, KnownNat n) => Matrix n n x -> Vector (Triangular n) x Source #

Returns the lower triangular part of a square matrix.

takeDiagonal :: (KnownNat n, Field x) => Matrix n n x -> Vector n x Source #

The determinant of a Matrix.

Manipulation

columnVector :: Vector n a -> Matrix n 1 a Source #

Turn a Vector into a single column Matrix.

rowVector :: Vector n a -> Matrix 1 n a Source #

Turn a Vector into a single row Matrix.

combineTriangles Source #

Arguments

:: (KnownNat k, Storable x) 
=> Vector k x

Diagonal

-> Matrix k k x

Lower triangular source

-> Matrix k k x

Upper triangular source

-> Matrix k k x 

Build a matrix with the given diagonal, lower triangular part given by the first matrix, and upper triangular part given by the second matrix.

diagonalConcat :: (KnownNat n, KnownNat m, KnownNat o, KnownNat p, Numeric x) => Matrix n m x -> Matrix o p x -> Matrix (n + o) (m + p) x Source #

Diagonally concatenate two matrices, padding the gaps with zeroes.

horizontalConcat :: (KnownNat n, KnownNat m, KnownNat o, Numeric x) => Matrix n m x -> Matrix n o x -> Matrix n (m + o) x Source #

Diagonally concatenate two matrices, padding the gaps with zeroes.

verticalConcat :: (KnownNat n, KnownNat m, KnownNat o, Numeric x) => Matrix n o x -> Matrix m o x -> Matrix (n + m) o x Source #

Diagonally concatenate two matrices, padding the gaps with zeroes.

Computation

trace :: (KnownNat n, Field x) => Matrix n n x -> x Source #

The determinant of a Matrix.

withMatrix :: (Vector (n * m) x -> Vector (n * m) x) -> Matrix n m x -> Matrix n m x Source #

Apply a Vector operation to a Matrix.

BLAS

scale :: Numeric x => x -> Vector n x -> Vector n x Source #

Scalar multiplication of a Vector.

add :: Numeric x => Vector n x -> Vector n x -> Vector n x Source #

The sum of two Vectors.

dotProduct :: Numeric x => Vector n x -> Vector n x -> x Source #

The dot product of two numerical Vectors.

dotMap :: (KnownNat n, Numeric x) => Vector n x -> [Vector n x] -> [x] Source #

The dot products of one vector with a list of vectors.

matrixVectorMultiply :: (KnownNat m, KnownNat n, Numeric x) => Matrix m n x -> Vector n x -> Vector m x Source #

Apply a linear transformation to a Vector.

matrixMatrixMultiply :: (KnownNat m, KnownNat n, KnownNat o, Numeric x) => Matrix m n x -> Matrix n o x -> Matrix m o x Source #

Multiply a Matrix with a second Matrix.

matrixMap :: (KnownNat m, KnownNat n, Numeric x) => Matrix m n x -> [Vector n x] -> [Vector m x] Source #

Map a linear transformation over a list of Vectors.

eigens :: (KnownNat n, Field x) => Matrix n n x -> (Vector n (Complex Double), Vector n (Vector n (Complex Double))) Source #

Returns the eigenvalues and eigenvectors Matrix.

isSemiPositiveDefinite :: (KnownNat n, Field x) => Matrix n n x -> Bool Source #

Test if the matrix is semi-positive definite.

determinant :: (KnownNat n, Field x) => Matrix n n x -> x Source #

The determinant of a Matrix.

inverseLogDeterminant :: (KnownNat n, Field x) => Matrix n n x -> (Matrix n n x, x, x) Source #

Returns the inverse, the logarithm of the absolute value of the determinant, and the sign of the determinant of a given matrix.

inverse :: forall n x. (KnownNat n, Field x) => Matrix n n x -> Matrix n n x Source #

Invert a Matrix.

pseudoInverse :: forall n x. (KnownNat n, Field x) => Matrix n n x -> Matrix n n x Source #

Pseudo-Invert a Matrix.

matrixRoot :: forall n x. (KnownNat n, Field x) => Matrix n n x -> Matrix n n x Source #

Square root of a Matrix.

transpose :: forall m n x. (KnownNat m, KnownNat n, Numeric x) => Matrix m n x -> Matrix n m x Source #

Transpose a Matrix.

Least Squares

linearLeastSquares Source #

Arguments

:: KnownNat l 
=> [Vector l Double]

Independent variable observations

-> [Double]

Dependent variable observations

-> Vector l Double

Parameter estimates

Solves the linear least squares problem.

meanSquaredError :: KnownNat k => Vector k Double -> Vector k Double -> Double Source #

The Mean Squared difference between two vectors.

rSquared Source #

Arguments

:: KnownNat k 
=> Vector k Double

Dependent variable observations

-> Vector k Double

Predicted Values

-> Double

R-squared

Computes the coefficient of determintation for the given outputs and model predictions.

l2Norm :: KnownNat k => Vector k Double -> Double Source #

L2 length of a vector.

unsafeCholesky :: (KnownNat n, Field x, Storable x) => Matrix n n x -> Matrix n n x Source #

Convolutions

crossCorrelate2d Source #

Arguments

:: forall nk rdkr rdkc mr mc md x. (KnownNat rdkr, KnownNat rdkc, KnownNat md, KnownNat mr, KnownNat mc, KnownNat nk, Numeric x, Storable x) 
=> Proxy rdkr

Number of Kernel rows

-> Proxy rdkc

Number of Kernel columns

-> Proxy mr

Number of Matrix/Image rows

-> Proxy mc

Number of Kernel/Image columns

-> Matrix nk ((md * ((2 * rdkr) + 1)) * ((2 * rdkc) + 1)) x

Kernels (nk is their number)

-> Matrix md (mr * mc) x

Image (md is the depth)

-> Matrix nk (mr * mc) x

Cross-correlated image

2d cross-correlation of a kernel over a matrix of values.

convolve2d Source #

Arguments

:: forall nk rdkr rdkc md mr mc x. (KnownNat rdkr, KnownNat rdkc, KnownNat mr, KnownNat mc, KnownNat md, KnownNat nk, Numeric x, Storable x) 
=> Proxy rdkr

Number of Kernel rows

-> Proxy rdkc

Number of Kernel columns

-> Proxy mr

Number of Matrix/Image rows

-> Proxy mc

Number of Kernel/Image columns

-> Matrix nk ((md * ((2 * rdkr) + 1)) * ((2 * rdkc) + 1)) x

Kernels (nk is their number)

-> Matrix nk (mr * mc) x

Dual image (nk is its depth)

-> Matrix md (mr * mc) x

Convolved image

2d convolution of a kernel over a matrix of values. This is the adjoint of crossCorrelate2d.

kernelOuterProduct Source #

Arguments

:: forall nk rdkr rdkc md mr mc x. (KnownNat rdkr, KnownNat rdkc, KnownNat mr, KnownNat mc, KnownNat md, KnownNat nk, Numeric x, Storable x) 
=> Proxy rdkr

Number of Kernel rows

-> Proxy rdkc

Number of Kernel columns

-> Proxy mr

Number of Matrix/Image rows

-> Proxy mc

Number of Kernel/Image columns

-> Matrix nk (mr * mc) x

Dual image (nk is its depth)

-> Matrix md (mr * mc) x

Image (md is the depth)

-> Matrix nk ((md * ((2 * rdkr) + 1)) * ((2 * rdkc) + 1)) x

Kernels

The outer product of an image and a dual image to produce a convolutional kernel.

kernelTranspose Source #

Arguments

:: (KnownNat nk, KnownNat md, KnownNat rdkr, KnownNat rdkc, Numeric x, Storable x) 
=> Proxy nk 
-> Proxy md 
-> Proxy rdkr 
-> Proxy rdkc 
-> Matrix nk ((md * ((2 * rdkr) + 1)) * ((2 * rdkc) + 1)) x

Kernels (nk is their number)

-> Matrix md ((nk * ((2 * rdkr) + 1)) * ((2 * rdkc) + 1)) x

Kernels (nk is their number)

The transpose of a convolutional kernel.

Miscellaneous

prettyPrintMatrix :: (KnownNat m, KnownNat n, Numeric a, Show a) => Matrix m n a -> IO () Source #

Pretty print the values of a Matrix (for extremely simple values of pretty).