repa-linear-algebra-0.0.0.0: HMatrix operations for Repa.

Safe HaskellNone
LanguageHaskell2010

Numeric.LinearAlgebra.Repa

Contents

Synopsis

Documentation

class (Container Vector t, Container Matrix t, Konst t Int Vector, Konst t (Int, Int) Matrix, Product t) => Numeric t

class (Product t, Convert t, Container Vector t, Container Matrix t, Normed Matrix t, Normed Vector t, Floating t, (~) * (RealOf t) Double) => Field t

Minimal complete definition

svd', thinSVD', sv', luPacked', luSolve', mbLinearSolve', linearSolve', cholSolve', linearSolveSVD', linearSolveLS', eig', eigSH'', eigOnly, eigOnlySH, cholSH', mbCholSH', qr', qrgr', hess', schur'

class (Num e, Element e) => Product e

Minimal complete definition

multiply, absSum, norm1, norm2, normInf

data RandDist :: *

Constructors

Uniform 
Gaussian 

Instances

type Seed = Int

class HShape sh where Source

Shape-polymorphic conversion.

Associated Types

type HType sh :: * -> * Source

Methods

toRepa :: Numeric t => HType sh t -> Array F sh t Source

fromRepa :: Numeric t => Array F sh t -> HType sh t Source

fromRepaS :: Numeric t => Array D sh t -> HType sh t Source

fromRepaSIO :: Numeric t => Array D sh t -> IO (HType sh t) Source

fromRepaP :: (Numeric t, Monad m) => Array D sh t -> m (HType sh t) Source

fromRepaPIO :: Numeric t => Array D sh t -> IO (HType sh t) Source

class LSDiv c

Minimal complete definition

linSolve

Instances

LSDiv Vector 
LSDiv Matrix 

Dot product

dot :: Numeric t => Array F DIM1 t -> Array F DIM1 t -> t Source

Vector dot product.

dotS :: Numeric t => Array D DIM1 t -> Array D DIM1 t -> t Source

Vector dot product. Arguments computed sequentially.

dotSIO :: Numeric t => Array D DIM1 t -> Array D DIM1 t -> IO t Source

Vector dot product. Arguments computed sequentially inside the IO monad.

dotP :: (Numeric t, Monad m) => Array D DIM1 t -> Array D DIM1 t -> m t Source

Vector dot product. Arguments computed in parallel.

dotPIO :: Numeric t => Array D DIM1 t -> Array D DIM1 t -> IO t Source

Vector dot product. Arguments computed in parallel inside the IO monad.

Dense matrix-vector product.

app :: Numeric t => Array F DIM2 t -> Array F DIM1 t -> Array F DIM1 t Source

Dense matrix-vector product.

appS :: Numeric t => Array D DIM2 t -> Array D DIM1 t -> Array F DIM1 t Source

Dense matrix-vector product. Arguments computed sequentially.

appSIO :: Numeric t => Array D DIM2 t -> Array D DIM1 t -> IO (Array F DIM1 t) Source

Dense matrix-vector product. Arguments computed sequentially inside the IO monad.

appP :: (Numeric t, Monad m) => Array D DIM2 t -> Array D DIM1 t -> m (Array F DIM1 t) Source

Dense matrix-vector product. Arguments computed in parallel.

appPIO :: Numeric t => Array D DIM2 t -> Array D DIM1 t -> IO (Array F DIM1 t) Source

Dense matrix-vector product. Arguments computed in parallel inside the IO monad.

Dense matrix-matrix product.

mul :: Numeric t => Array F DIM2 t -> Array F DIM2 t -> Array F DIM2 t Source

Dense matrix-matrix product.

mulS :: Numeric t => Array D DIM2 t -> Array D DIM2 t -> Array F DIM2 t Source

Dense matrix-matrix product. Arguments computed sequentially.

mulSIO :: Numeric t => Array D DIM2 t -> Array D DIM2 t -> IO (Array F DIM2 t) Source

Dense matrix-matrix product. Arguments computed sequentially inside the IO monad

mulP :: (Numeric t, Monad m) => Array D DIM2 t -> Array D DIM2 t -> m (Array F DIM2 t) Source

Dense matrix-matrix product. Arguments computed in parallel.

mulPIO :: Numeric t => Array D DIM2 t -> Array D DIM2 t -> IO (Array F DIM2 t) Source

Dense matrix-matrix product. Arguments computed in parallel inside the IO monad

Vector outer product.

outer :: (Product t, Numeric t) => Array F DIM1 t -> Array F DIM1 t -> Array F DIM2 t Source

Outer product of two vectors.

outerS :: (Product t, Numeric t) => Array D DIM1 t -> Array D DIM1 t -> Array F DIM2 t Source

Outer product of two vectors. Arguments computed sequentially.

outerSIO :: (Product t, Numeric t) => Array D DIM1 t -> Array D DIM1 t -> IO (Array F DIM2 t) Source

Outer product of two vectors. Arguments computed sequentially inside the IO monad.

outerP :: (Product t, Numeric t, Monad m) => Array D DIM1 t -> Array D DIM1 t -> m (Array F DIM2 t) Source

Outer product of two vectors. Arguments computed in parallel.

outerPIO :: (Product t, Numeric t) => Array D DIM1 t -> Array D DIM1 t -> IO (Array F DIM2 t) Source

Outer product of two vectors. Arguments computed in parallel inside the IO monad.

Kronecker product.

kronecker :: (Product t, Numeric t) => Array F DIM2 t -> Array F DIM2 t -> Array F DIM2 t Source

Kronecker product of two matrices.

kroneckerS :: (Product t, Numeric t) => Array D DIM2 t -> Array D DIM2 t -> Array F DIM2 t Source

Kronecker product of two matrices. Arguments computed sequentially.

kroneckerSIO :: (Product t, Numeric t) => Array D DIM2 t -> Array D DIM2 t -> IO (Array F DIM2 t) Source

Kronecker product of two matrices. Arguments computed sequentially inside the IO monad.

kroneckerP :: (Product t, Numeric t, Monad m) => Array D DIM2 t -> Array D DIM2 t -> m (Array F DIM2 t) Source

Kronecker product of two matrices. Arguments computed in parallel.

kroneckerPIO :: (Product t, Numeric t) => Array D DIM2 t -> Array D DIM2 t -> IO (Array F DIM2 t) Source

Kronecker product of two matrices. Arguments computed in parallel inside the IO monad.

Cross product.

cross :: Array F DIM1 Double -> Array F DIM1 Double -> Array F DIM1 Double Source

Vector cross product.

crossS :: Array D DIM1 Double -> Array D DIM1 Double -> Array F DIM1 Double Source

Vector cross product. Arguments computed sequentially.

crossSIO :: Array D DIM1 Double -> Array D DIM1 Double -> IO (Array F DIM1 Double) Source

Vector cross product. Arguments computed sequentially inside the IO monad.

Sum of elements.

sumElements :: (Numeric t, HShape sh, Container (HType sh) t) => Array F sh t -> t Source

Sum elements of a matrix or a vector.

sumElementsS :: (Numeric t, HShape sh, Container (HType sh) t) => Array D sh t -> t Source

Sum elements of a matrix or a vector. Argument computed sequentially.

sumElementsSIO :: (Numeric t, HShape sh, Container (HType sh) t) => Array D sh t -> IO t Source

Sum elements of a matrix or a vector. Argument computed sequentially in the IO monad.

sumElementsP :: (Numeric t, HShape sh, Container (HType sh) t, Monad m) => Array D sh t -> m t Source

Sum elements of a matrix or a vector. Argument computed in parallel.

sumElementsPIO :: (Numeric t, HShape sh, Container (HType sh) t) => Array D sh t -> IO t Source

Sum elements of a matrix or a vector. Argument computed in parallel in the IO monad.

Product of elements.

prodElements :: (Numeric t, HShape sh, Container (HType sh) t) => Array F sh t -> t Source

Multiply elements of a matrix or a vector.

prodElementsS :: (Numeric t, HShape sh, Container (HType sh) t) => Array D sh t -> t Source

Multiply elements of a matrix or a vector. Argument computed sequentially.

prodElementsSIO :: (Numeric t, HShape sh, Container (HType sh) t) => Array D sh t -> IO t Source

Multiply elements of a matrix or a vector. Argument computed sequentially inside the IO monad.

prodElementsP :: (Numeric t, HShape sh, Container (HType sh) t, Monad m) => Array D sh t -> m t Source

Multiply elements of a matrix or a vector. Argument computed in parallel.

prodElementsPIO :: (Numeric t, HShape sh, Container (HType sh) t) => Array D sh t -> IO t Source

Multiply elements of a matrix or a vector. Argument computed in parallel inside the IO monad.

Linear systems.

(<\>) :: (Field t, Numeric t, HShape sh, LSDiv (HType sh)) => Array F DIM2 t -> Array F sh t -> Array F sh t Source

Infix alias for solve.

solve :: (Field t, Numeric t, HShape sh, LSDiv (HType sh)) => Array F DIM2 t -> Array F sh t -> Array F sh t Source

Least squares solution of a linear system, similar to the operator of Matlab/Octave (based on linearSolveSD).

solveS :: (Field t, Numeric t, HShape sh, LSDiv (HType sh)) => Array D DIM2 t -> Array D sh t -> Array F sh t Source

Least squares solution of a linear system, similar to the operator of Matlab/Octave (based on linearSolveSD). Arguments are computed sequentially.

solveSIO :: (Field t, Numeric t, HShape sh, LSDiv (HType sh)) => Array D DIM2 t -> Array D sh t -> IO (Array F sh t) Source

Least squares solution of a linear system, similar to the operator of Matlab/Octave (based on linearSolveSD). Arguments are computed sequentially inside the IO monad.

solveP :: (Field t, Numeric t, HShape sh, LSDiv (HType sh), Monad m) => Array D DIM2 t -> Array D sh t -> m (Array F sh t) Source

Least squares solution of a linear system, similar to the operator of Matlab/Octave (based on linearSolveSD). Arguments are computed in parallel.

solvePIO :: (Field t, Numeric t, HShape sh, LSDiv (HType sh)) => Array D DIM2 t -> Array D sh t -> IO (Array F sh t) Source

Least squares solution of a linear system, similar to the operator of Matlab/Octave (based on linearSolveSD). Arguments are computed in parallel inside the IO monad.

linearSolve :: (Field t, Numeric t) => Array F DIM2 t -> Array F DIM2 t -> Maybe (Array F DIM2 t) Source

Solve a linear system (for square coefficient matrix and several right hand sides) using the LU decomposition, returning Nothing for a singular system. For underconstrained or overconstrained systems use linearSolveLS or linearSolveSVD.

linearSolveS :: (Field t, Numeric t) => Array D DIM2 t -> Array D DIM2 t -> Maybe (Array F DIM2 t) Source

Solve a linear system using the LU decomposition. Arguments computed sequentially.

linearSolveSIO :: (Field t, Numeric t) => Array D DIM2 t -> Array D DIM2 t -> IO (Maybe (Array F DIM2 t)) Source

Solve a linear system using the LU decomposition. Arguments computed sequentially inside the IO monad.

linearSolveP :: (Field t, Numeric t, Monad m) => Array D DIM2 t -> Array D DIM2 t -> m (Maybe (Array F DIM2 t)) Source

Solve a linear system using the LU decomposition. Arguments computed in parallel.

linearSolvePIO :: (Field t, Numeric t) => Array D DIM2 t -> Array D DIM2 t -> IO (Maybe (Array F DIM2 t)) Source

Solve a linear system using the LU decomposition. Arguments computed in parallel inside the IO monad.

linearSolveLS :: (Field t, Numeric t) => Array F DIM2 t -> Array F DIM2 t -> Array F DIM2 t Source

Least squared error solution of an overcompensated system, or the minimum norm solution of an undercompensated system. For rank-deficient systems use linearSolveSVD.

linearSolveSVD :: (Field t, Numeric t) => Array F DIM2 t -> Array F DIM2 t -> Array F DIM2 t Source

Minimum norm solution of a general linear least squares problem Ax=b using the SVD. Admits rank-deficient systems but is slower than linearSolveLS. The effective rank of A is determined by treating as zero those singular values which are less than eps times the largest singular value.

luSolve :: (Field t, Numeric t) => PackedLU t -> Array F DIM2 t -> Array F DIM2 t Source

Solution of a linear system (for several right hand sides) from the precomputed LU factorization obtained by luPacked.

luSolveS :: (Field t, Numeric t) => PackedLU t -> Array D DIM2 t -> Array F DIM2 t Source

luSolveSIO :: (Field t, Numeric t) => PackedLU t -> Array D DIM2 t -> IO (Array F DIM2 t) Source

luSolveP :: (Field t, Numeric t, Monad m) => PackedLU t -> Array D DIM2 t -> m (Array F DIM2 t) Source

luSolvePIO :: (Field t, Numeric t) => PackedLU t -> Array D DIM2 t -> IO (Array F DIM2 t) Source

cholSolve :: (Field t, Numeric t) => Array F DIM2 t -> Array F DIM2 t -> Array F DIM2 t Source

Solve a symmetric or Herimitian positive definite linear system using a precomputed Cholesky decomposition obtained by chol.

cholSolveP :: (Field t, Numeric t, Monad m) => Array F DIM2 t -> Array D DIM2 t -> m (Array F DIM2 t) Source

Inverse and pseudoinverse

inv :: (Field t, Numeric t) => Array F DIM2 t -> Array F DIM2 t Source

Inverse of a square matrix.

invS :: (Field t, Numeric t) => Array D DIM2 t -> Array F DIM2 t Source

invSIO :: (Field t, Numeric t) => Array D DIM2 t -> IO (Array F DIM2 t) Source

invP :: (Field t, Numeric t, Monad m) => Array D DIM2 t -> m (Array F DIM2 t) Source

invPIO :: (Field t, Numeric t) => Array D DIM2 t -> IO (Array F DIM2 t) Source

pinv :: (Field t, Numeric t) => Array F DIM2 t -> Array F DIM2 t Source

Pseudoinverse of a general matrix, with default tolerance (pinvTol 1, similar to GNU-Octave)

pinvS :: (Field t, Numeric t) => Array D DIM2 t -> Array F DIM2 t Source

pinvSIO :: (Field t, Numeric t) => Array D DIM2 t -> IO (Array F DIM2 t) Source

pinvP :: (Field t, Numeric t, Monad m) => Array D DIM2 t -> m (Array F DIM2 t) Source

pinvPIO :: (Field t, Numeric t) => Array D DIM2 t -> IO (Array F DIM2 t) Source

pinvTol :: (Field t, Numeric t) => Double -> Array F DIM2 t -> Array F DIM2 t Source

pinvTol r computes the pseudoinverse of a matrix with tolerance tol=r*g*eps*(max rows cols), where g is the greatest singular value.

pinvTolP :: (Field t, Numeric t, Monad m) => Double -> Array D DIM2 t -> m (Array F DIM2 t) Source

Determinant and rank

rcond :: (Field t, Numeric t) => Array F DIM2 t -> Double Source

Reciprocal of the 2-norm condition number of a matrix, computed from the singular values.

rcondP :: (Field t, Numeric t, Monad m) => Array D DIM2 t -> m Double Source

rank :: (Field t, Numeric t) => Array F DIM2 t -> Int Source

Number of linearly independent rows or columns. See also ranksv.

rankS :: (Field t, Numeric t) => Array D DIM2 t -> Int Source

rankP :: (Field t, Numeric t, Monad m) => Array D DIM2 t -> m Int Source

det :: (Field t, Numeric t) => Array F DIM2 t -> t Source

Determinant of a square matrix. To avoid possible overflow or underflow use invlndet.

detS :: (Field t, Numeric t) => Array D DIM2 t -> t Source

detSIO :: (Field t, Numeric t) => Array D DIM2 t -> IO t Source

detP :: (Field t, Numeric t, Monad m) => Array D DIM2 t -> m t Source

detPIO :: (Field t, Numeric t) => Array D DIM2 t -> IO t Source

invlndet Source

Arguments

:: (Field t, Numeric t) 
=> Array F DIM2 t 
-> (Array F DIM2 t, (t, t))

(inverse, (log abs det, sign or phase of det)) ^Joint computation of inverse and logarithm of determinant of a square matrix.

invlndetS :: (Field t, Numeric t) => Array D DIM2 t -> (Array F DIM2 t, (t, t)) Source

invlndetSIO :: (Field t, Numeric t) => Array D DIM2 t -> IO (Array F DIM2 t, (t, t)) Source

invlndetP :: (Field t, Numeric t, Monad m) => Array D DIM2 t -> m (Array F DIM2 t, (t, t)) Source

invlndetPIO :: (Field t, Numeric t) => Array D DIM2 t -> IO (Array F DIM2 t, (t, t)) Source

Norms

norm_Frob :: (Normed (Vector t), Element t) => Array F DIM2 t -> Double Source

norm_FrobS :: (Normed (Vector t), Element t) => Array D DIM2 t -> Double Source

norm_FrobSIO :: (Normed (Vector t), Element t) => Array D DIM2 t -> IO Double Source

norm_FrobP :: (Normed (Vector t), Element t, Monad m) => Array D DIM2 t -> m Double Source

norm_FrobPIO :: (Normed (Vector t), Element t) => Array D DIM2 t -> IO Double Source

Nullspace and range

orth :: (Field t, Numeric t) => Array F DIM2 t -> Array F DIM2 t Source

An orthonormal basis of the range space of a matrix. See also orthSVD.

orthS :: (Field t, Numeric t) => Array D DIM2 t -> Array F DIM2 t Source

orthSIO :: (Field t, Numeric t) => Array D DIM2 t -> IO (Array F DIM2 t) Source

orthP :: (Field t, Numeric t, Monad m) => Array D DIM2 t -> m (Array F DIM2 t) Source

orthPIO :: (Field t, Numeric t) => Array D DIM2 t -> IO (Array F DIM2 t) Source

nullspace :: (Field t, Numeric t) => Array F DIM2 t -> Array F DIM2 t Source

An orthonormal basis of the null space of a matrix. See also nullspaceSVD.

nullspaceP :: (Field t, Numeric t, Monad m) => Array D DIM2 t -> m (Array F DIM2 t) Source

null1 :: Array F DIM2 Double -> Array F DIM1 Double Source

Solution of an overconstrained homogenous linear system.

null1sym :: Array F DIM2 Double -> Array F DIM1 Double Source

Solution of an overconstrained homogenous symmetric linear system.

SVD

svd :: (Field t, Numeric t) => Array F DIM2 t -> (Array F DIM2 t, Array F DIM1 Double, Array F DIM2 t) Source

Full singular value decomposition.

thinSVD :: (Field t, Numeric t) => Array F DIM2 t -> (Array F DIM2 t, Array F DIM1 Double, Array F DIM2 t) Source

A version of svd which returns only the min (rows m) (cols m) singular vectors of m. (u,s,v) = thinSVD m ==> m == u * diag s * tr v

compactSVD :: (Field t, Numeric t) => Array F DIM2 t -> (Array F DIM2 t, Array F DIM1 Double, Array F DIM2 t) Source

Similar to thinSVD, returning only the nonzero singular values and the corresponding singular vectors.

singularValues :: (Field t, Numeric t) => Array F DIM2 t -> Array F DIM1 Double Source

Singular values only.

leftSV :: (Field t, Numeric t) => Array F DIM2 t -> (Array F DIM2 t, Array F DIM1 Double) Source

Singular values and all left singular vectors (as columns).

rightSV :: (Field t, Numeric t) => Array F DIM2 t -> (Array F DIM1 Double, Array F DIM2 t) Source

Singular values and all right singular vectors (as columns).

Eigensystems

eig :: (Field t, Numeric t) => Array F DIM2 t -> (Array F DIM1 (Complex Double), Array F DIM2 (Complex Double)) Source

Eigenvalues (not ordered) and eigenvectors (as columns) of a general square matrix. (s,v) = eig m ==> m * v = v == v <> diag s

eigSH :: (Field t, Numeric t) => Array F DIM2 t -> (Array F DIM1 Double, Array F DIM2 t) Source

Eigenvalues and eigenvectors (as columns) of a complex hermitian or a real symmetric matrix, in descending order.

eigSH' :: (Field t, Numeric t) => Array F DIM2 t -> (Array F DIM1 Double, Array F DIM2 t) Source

Similar to eigSH without checking that the input matrix is hermitian or symmetric. It works with the upper triangular part.

eigenvalues :: (Field t, Numeric t) => Array F DIM2 t -> Array F DIM1 (Complex Double) Source

Eigenvalues (not ordered) of a general square matrix.

eigenvaluesSH :: (Field t, Numeric t) => Array F DIM2 t -> Array F DIM1 Double Source

Eigenvalues (in descending order) of a complex hermitian or real symmetric matrix.

eigenvaluesSH' :: (Field t, Numeric t) => Array F DIM2 t -> Array F DIM1 Double Source

Similar to eigenvaluesSH without checking that the input matrix is hermitian or symmetric. It works with the upper triangular part.

geigSH' :: (Field t, Numeric t) => Array F DIM2 t -> Array F DIM2 t -> (Array F DIM1 Double, Array F DIM2 t) Source

Generalized symmetric positive definite eigensystem Av = IBv, for A and B symmetric, B positive definite (conditions not checked).

QR

qr :: (Field t, Numeric t) => Array F DIM2 t -> (Array F DIM2 t, Array F DIM2 t) Source

QR factorization. (q,r) = qr m ==> m = q * r where q is unitary and r is upper triangular.

qrS :: (Field t, Numeric t) => Array D DIM2 t -> (Array F DIM2 t, Array F DIM2 t) Source

qrSIO :: (Field t, Numeric t) => Array D DIM2 t -> IO (Array F DIM2 t, Array F DIM2 t) Source

qrP :: (Field t, Numeric t, Monad m) => Array D DIM2 t -> m (Array F DIM2 t, Array F DIM2 t) Source

qrPIO :: (Field t, Numeric t) => Array D DIM2 t -> IO (Array F DIM2 t, Array F DIM2 t) Source

rq :: (Field t, Numeric t) => Array F DIM2 t -> (Array F DIM2 t, Array F DIM2 t) Source

RQ factorization. (r,q) = rq m ==> m = r * q where q is unitary and r is upper triangular.

rqS :: (Field t, Numeric t) => Array D DIM2 t -> (Array F DIM2 t, Array F DIM2 t) Source

rqSIO :: (Field t, Numeric t) => Array D DIM2 t -> IO (Array F DIM2 t, Array F DIM2 t) Source

rqP :: (Field t, Numeric t, Monad m) => Array D DIM2 t -> m (Array F DIM2 t, Array F DIM2 t) Source

rqPIO :: (Field t, Numeric t) => Array D DIM2 t -> IO (Array F DIM2 t, Array F DIM2 t) Source

qrRaw :: (Field t, Numeric t) => Array F DIM2 t -> (Array F DIM2 t, Array F DIM1 t) Source

qrRawS :: (Field t, Numeric t) => Array D DIM2 t -> (Array F DIM2 t, Array F DIM1 t) Source

qrRawP :: (Field t, Numeric t, Monad m) => Array D DIM2 t -> m (Array F DIM2 t, Array F DIM1 t) Source

qrgr :: (Field t, Numeric t) => Int -> (Array F DIM2 t, Array F DIM1 t) -> Array F DIM2 t Source

Generate a matrix with k othogonal columns from the output of qrRaw.

Cholesky

chol :: (Field t, Numeric t) => Array F DIM2 t -> Array F DIM2 t Source

Cholesky factorization of a positive definite hermitian or symmetric matrix. c = chol m ==> m == c' * c where c is upper triangular.

cholS :: (Field t, Numeric t) => Array D DIM2 t -> Array F DIM2 t Source

cholSIO :: (Field t, Numeric t) => Array D DIM2 t -> IO (Array F DIM2 t) Source

cholP :: (Field t, Numeric t, Monad m) => Array D DIM2 t -> m (Array F DIM2 t) Source

cholPIO :: (Field t, Numeric t) => Array D DIM2 t -> IO (Array F DIM2 t) Source

chol' :: (Field t, Numeric t) => Array F DIM2 t -> Array F DIM2 t Source

Similar to chol without checking that the input matrix is hermitian or symmetric. It works with the upper triangular part.

chol'SIO :: (Field t, Numeric t) => Array D DIM2 t -> IO (Array F DIM2 t) Source

chol'P :: (Field t, Numeric t, Monad m) => Array D DIM2 t -> m (Array F DIM2 t) Source

chol'PIO :: (Field t, Numeric t) => Array D DIM2 t -> IO (Array F DIM2 t) Source

Hessenberg

hess :: (Field t, Numeric t) => Array F DIM2 t -> (Array F DIM2 t, Array F DIM2 t) Source

Hessenberg factorization. (p,h) == hess m ==> p * h * p' where p is unitary and h is in upper Hessenberg form (zero entries below the first subdiagonal).

hessS :: (Field t, Numeric t) => Array D DIM2 t -> (Array F DIM2 t, Array F DIM2 t) Source

hessSIO :: (Field t, Numeric t) => Array D DIM2 t -> IO (Array F DIM2 t, Array F DIM2 t) Source

hessP :: (Field t, Numeric t, Monad m) => Array D DIM2 t -> m (Array F DIM2 t, Array F DIM2 t) Source

hessPIO :: (Field t, Numeric t) => Array D DIM2 t -> IO (Array F DIM2 t, Array F DIM2 t) Source

Schur

schur :: (Field t, Numeric t) => Array F DIM2 t -> (Array F DIM2 t, Array F DIM2 t) Source

Schur factorization. (u,s) = schur m ==> m == u * s * u' where u is unitary and s is a Schur matrix. A complex Schur matrix is upper triangular. A real Schur matrix is upper triangular in 2x2 blocks.

schurS :: (Field t, Numeric t) => Array D DIM2 t -> (Array F DIM2 t, Array F DIM2 t) Source

schurP :: (Field t, Numeric t, Monad m) => Array D DIM2 t -> m (Array F DIM2 t, Array F DIM2 t) Source

LU

lu :: (Field t, Numeric t) => Array F DIM2 t -> (Array F DIM2 t, Array F DIM2 t, Array F DIM2 t, t) Source

Explicit LU factorization of a general matrix. (l,u,p,s) = lu m ==> m = p * l * u where l is lower triangular, u is upper triangular, p is a permutation matrix, and s is the signature of the permutation.

luS :: (Field t, Numeric t) => Array D DIM2 t -> (Array F DIM2 t, Array F DIM2 t, Array F DIM2 t, t) Source

luSIO :: (Field t, Numeric t) => Array D DIM2 t -> IO (Array F DIM2 t, Array F DIM2 t, Array F DIM2 t, t) Source

luP :: (Field t, Numeric t, Monad m) => Array D DIM2 t -> m (Array F DIM2 t, Array F DIM2 t, Array F DIM2 t, t) Source

luPIO :: (Field t, Numeric t) => Array D DIM2 t -> IO (Array F DIM2 t, Array F DIM2 t, Array F DIM2 t, t) Source

luPacked :: (Field t, Numeric t) => Array F DIM2 t -> PackedLU t Source

Obtains the LU decomposition in a packed data structure suitable for luSolve.

luPackedS :: (Field t, Numeric t) => Array D DIM2 t -> PackedLU t Source

luPackedSIO :: (Field t, Numeric t) => Array D DIM2 t -> IO (PackedLU t) Source

luPackedP :: (Field t, Numeric t, Monad m) => Array D DIM2 t -> m (PackedLU t) Source

luPackedPIO :: (Field t, Numeric t) => Array D DIM2 t -> IO (PackedLU t) Source

Matrix functions

expm :: (Field t, Numeric t) => Array F DIM2 t -> Array F DIM2 t Source

Matrix exponential. It uses a direct translation of Algorithm 11.3.1 in Golub & Val Loan, based on a scaled Pade approximation.

expmS :: (Field t, Numeric t) => Array D DIM2 t -> Array F DIM2 t Source

expmSIO :: (Field t, Numeric t) => Array D DIM2 t -> IO (Array F DIM2 t) Source

expmP :: (Field t, Numeric t, Monad m) => Array D DIM2 t -> m (Array F DIM2 t) Source

expmPIO :: (Field t, Numeric t) => Array D DIM2 t -> IO (Array F DIM2 t) Source

sqrtm :: (Field t, Numeric t) => Array F DIM2 t -> Array F DIM2 t Source

Matrix square root. Currently it uses a simple iterative algorithm described in Wikipedia. It only works with invertible matrices that have a real solution.

sqrtmSIO :: (Field t, Numeric t) => Array D DIM2 t -> IO (Array F DIM2 t) Source

sqrtmP :: (Field t, Numeric t, Monad m) => Array D DIM2 t -> m (Array F DIM2 t) Source

sqrtmPIO :: (Field t, Numeric t) => Array D DIM2 t -> IO (Array F DIM2 t) Source

Correlation and convolution

corr :: (Product t, Numeric t) => Array F DIM1 t -> Array F DIM1 t -> Array F DIM1 t Source

Correlation.

corrS :: (Product t, Numeric t) => Array F DIM1 t -> Array D DIM1 t -> Array F DIM1 t Source

corrSIO :: (Product t, Numeric t) => Array F DIM1 t -> Array D DIM1 t -> IO (Array F DIM1 t) Source

corrP :: (Product t, Numeric t, Monad m) => Array F DIM1 t -> Array D DIM1 t -> m (Array F DIM1 t) Source

corrPIO :: (Product t, Numeric t) => Array F DIM1 t -> Array D DIM1 t -> IO (Array F DIM1 t) Source

conv :: (Product t, Numeric t) => Array F DIM1 t -> Array F DIM1 t -> Array F DIM1 t Source

Convolution - corr with reversed kernel and padded input, equivalent to polynomial multiplication.

convS :: (Product t, Numeric t) => Array F DIM1 t -> Array D DIM1 t -> Array F DIM1 t Source

convSIO :: (Product t, Numeric t) => Array F DIM1 t -> Array D DIM1 t -> IO (Array F DIM1 t) Source

convP :: (Product t, Numeric t, Monad m) => Array F DIM1 t -> Array D DIM1 t -> m (Array F DIM1 t) Source

convPIO :: (Product t, Numeric t) => Array F DIM1 t -> Array D DIM1 t -> IO (Array F DIM1 t) Source

corrMin :: (Product t, Numeric t, RealElement t) => Array F DIM1 t -> Array F DIM1 t -> Array F DIM1 t Source

Similar to corr but using min instead of (*).

corrMinS :: (Product t, Numeric t, RealElement t) => Array F DIM1 t -> Array D DIM1 t -> Array F DIM1 t Source

corrMinSIO :: (Product t, Numeric t, RealElement t) => Array F DIM1 t -> Array D DIM1 t -> IO (Array F DIM1 t) Source

corrMinP :: (Product t, Numeric t, RealElement t, Monad m) => Array F DIM1 t -> Array D DIM1 t -> m (Array F DIM1 t) Source

corrMinPIO :: (Product t, Numeric t, RealElement t) => Array F DIM1 t -> Array D DIM1 t -> IO (Array F DIM1 t) Source

corr2 :: (Product t, Numeric t) => Array F DIM2 t -> Array F DIM2 t -> Array F DIM2 t Source

2D correlation (without padding).

corr2SIO :: (Product t, Numeric t) => Array F DIM2 t -> Array D DIM2 t -> IO (Array F DIM2 t) Source

corr2P :: (Product t, Numeric t, Monad m) => Array F DIM2 t -> Array D DIM2 t -> m (Array F DIM2 t) Source

corr2PIO :: (Product t, Numeric t) => Array F DIM2 t -> Array D DIM2 t -> IO (Array F DIM2 t) Source

conv2 :: (Product t, Numeric t, Num (Vector t)) => Array F DIM2 t -> Array F DIM2 t -> Array F DIM2 t Source

2D convolution.

conv2S :: (Product t, Numeric t, Num (Vector t)) => Array F DIM2 t -> Array D DIM2 t -> Array F DIM2 t Source

conv2SIO :: (Product t, Numeric t, Num (Vector t)) => Array F DIM2 t -> Array D DIM2 t -> IO (Array F DIM2 t) Source

conv2P :: (Product t, Numeric t, Num (Vector t), Monad m) => Array F DIM2 t -> Array D DIM2 t -> m (Array F DIM2 t) Source

conv2PIO :: (Product t, Numeric t, Num (Vector t)) => Array F DIM2 t -> Array D DIM2 t -> IO (Array F DIM2 t) Source

Random vectors and matrices

randomVector :: Seed -> RandDist -> Int -> Array F DIM1 Double Source

Pseudorandom vector of na given size. Usee randomIO to get a random seed.

gaussianSample :: Seed -> Int -> Array F DIM1 Double -> Array F DIM2 Double -> Array F DIM2 Double Source

A matrix whose rows are pseudorandom samples from a multivariate Gaussian distribution.

uniformSample :: Seed -> Int -> [(Double, Double)] -> Array F DIM2 Double Source

A matrix whose rows are pseudorandom samples from a multivariate uniform distribution.

Misc

meanCov :: Array F DIM2 Double -> (Array F DIM1 Double, Array F DIM2 Double) Source

Compute mean vector and a covariance matrix of the rows of a matrix.

rowOuters :: Array F DIM2 Double -> Array F DIM2 Double -> Array F DIM2 Double Source

Outer product of the rows of the matrices.