hmatrix-0.10.0.1: Linear algebra and numerical computation

Portabilityportable (uses FFI)
Stabilityprovisional
MaintainerAlberto Ruiz (aruiz at um dot es)

Numeric.LinearAlgebra.LAPACK

Contents

Description

Functional interface to selected LAPACK functions (http://www.netlib.org/lapack).

Synopsis

Matrix product

multiplyR :: Matrix Double -> Matrix Double -> Matrix DoubleSource

Matrix product based on BLAS's dgemm.

multiplyC :: Matrix (Complex Double) -> Matrix (Complex Double) -> Matrix (Complex Double)Source

Matrix product based on BLAS's zgemm.

multiplyF :: Matrix Float -> Matrix Float -> Matrix FloatSource

Matrix product based on BLAS's sgemm.

multiplyQ :: Matrix (Complex Float) -> Matrix (Complex Float) -> Matrix (Complex Float)Source

Matrix product based on BLAS's cgemm.

Linear systems

linearSolveR :: Matrix Double -> Matrix Double -> Matrix DoubleSource

Solve a real linear system (for square coefficient matrix and several right-hand sides) using the LU decomposition, based on LAPACK's dgesv. For underconstrained or overconstrained systems use linearSolveLSR or linearSolveSVDR. See also lusR.

linearSolveC :: Matrix (Complex Double) -> Matrix (Complex Double) -> Matrix (Complex Double)Source

Solve a complex linear system (for square coefficient matrix and several right-hand sides) using the LU decomposition, based on LAPACK's zgesv. For underconstrained or overconstrained systems use linearSolveLSC or linearSolveSVDC. See also lusC.

lusR :: Matrix Double -> [Int] -> Matrix Double -> Matrix DoubleSource

Solve a real linear system from a precomputed LU decomposition (luR), using LAPACK's dgetrs.

lusC :: Matrix (Complex Double) -> [Int] -> Matrix (Complex Double) -> Matrix (Complex Double)Source

Solve a real linear system from a precomputed LU decomposition (luC), using LAPACK's zgetrs.

cholSolveR :: Matrix Double -> Matrix Double -> Matrix DoubleSource

Solves a symmetric positive definite system of linear equations using a precomputed Cholesky factorization obtained by cholS.

cholSolveC :: Matrix (Complex Double) -> Matrix (Complex Double) -> Matrix (Complex Double)Source

Solves a Hermitian positive definite system of linear equations using a precomputed Cholesky factorization obtained by cholH.

linearSolveLSR :: Matrix Double -> Matrix Double -> Matrix DoubleSource

Least squared error solution of an overconstrained real linear system, or the minimum norm solution of an underconstrained system, using LAPACK's dgels. For rank-deficient systems use linearSolveSVDR.

linearSolveLSC :: Matrix (Complex Double) -> Matrix (Complex Double) -> Matrix (Complex Double)Source

Least squared error solution of an overconstrained complex linear system, or the minimum norm solution of an underconstrained system, using LAPACK's zgels. For rank-deficient systems use linearSolveSVDC.

linearSolveSVDRSource

Arguments

:: Maybe Double

rcond

-> Matrix Double

coefficient matrix

-> Matrix Double

right hand sides (as columns)

-> Matrix Double

solution vectors (as columns)

Minimum norm solution of a general real linear least squares problem Ax=B using the SVD, based on LAPACK's dgelss. Admits rank-deficient systems but it is slower than linearSolveLSR. The effective rank of A is determined by treating as zero those singular valures which are less than rcond times the largest singular value. If rcond == Nothing machine precision is used.

linearSolveSVDCSource

Arguments

:: Maybe Double

rcond

-> Matrix (Complex Double)

coefficient matrix

-> Matrix (Complex Double)

right hand sides (as columns)

-> Matrix (Complex Double)

solution vectors (as columns)

Minimum norm solution of a general complex linear least squares problem Ax=B using the SVD, based on LAPACK's zgelss. Admits rank-deficient systems but it is slower than linearSolveLSC. The effective rank of A is determined by treating as zero those singular valures which are less than rcond times the largest singular value. If rcond == Nothing machine precision is used.

SVD

svR :: Matrix Double -> Vector DoubleSource

Singular values of a real matrix, using LAPACK's dgesvd with jobu == jobvt == 'N'.

svRd :: Matrix Double -> Vector DoubleSource

Singular values of a real matrix, using LAPACK's dgesdd with jobz == 'N'.

svC :: Matrix (Complex Double) -> Vector DoubleSource

Singular values of a complex matrix, using LAPACK's zgesvd with jobu == jobvt == 'N'.

svCd :: Matrix (Complex Double) -> Vector DoubleSource

Singular values of a complex matrix, using LAPACK's zgesdd with jobz == 'N'.

svdR :: Matrix Double -> (Matrix Double, Vector Double, Matrix Double)Source

Full SVD of a real matrix using LAPACK's dgesvd.

svdRd :: Matrix Double -> (Matrix Double, Vector Double, Matrix Double)Source

Full SVD of a real matrix using LAPACK's dgesdd.

svdC :: Matrix (Complex Double) -> (Matrix (Complex Double), Vector Double, Matrix (Complex Double))Source

Full SVD of a complex matrix using LAPACK's zgesvd.

svdCd :: Matrix (Complex Double) -> (Matrix (Complex Double), Vector Double, Matrix (Complex Double))Source

Full SVD of a complex matrix using LAPACK's zgesdd.

thinSVDR :: Matrix Double -> (Matrix Double, Vector Double, Matrix Double)Source

Thin SVD of a real matrix, using LAPACK's dgesvd with jobu == jobvt == 'S'.

thinSVDRd :: Matrix Double -> (Matrix Double, Vector Double, Matrix Double)Source

Thin SVD of a real matrix, using LAPACK's dgesdd with jobz == 'S'.

thinSVDC :: Matrix (Complex Double) -> (Matrix (Complex Double), Vector Double, Matrix (Complex Double))Source

Thin SVD of a complex matrix, using LAPACK's zgesvd with jobu == jobvt == 'S'.

thinSVDCd :: Matrix (Complex Double) -> (Matrix (Complex Double), Vector Double, Matrix (Complex Double))Source

Thin SVD of a complex matrix, using LAPACK's zgesdd with jobz == 'S'.

rightSVR :: Matrix Double -> (Vector Double, Matrix Double)Source

Singular values and all right singular vectors of a real matrix, using LAPACK's dgesvd with jobu == 'N' and jobvt == 'A'.

rightSVC :: Matrix (Complex Double) -> (Vector Double, Matrix (Complex Double))Source

Singular values and all right singular vectors of a complex matrix, using LAPACK's zgesvd with jobu == 'N' and jobvt == 'A'.

leftSVR :: Matrix Double -> (Matrix Double, Vector Double)Source

Singular values and all left singular vectors of a real matrix, using LAPACK's dgesvd with jobu == 'A' and jobvt == 'N'.

leftSVC :: Matrix (Complex Double) -> (Matrix (Complex Double), Vector Double)Source

Singular values and all left singular vectors of a complex matrix, using LAPACK's zgesvd with jobu == 'A' and jobvt == 'N'.

Eigensystems

eigR :: Matrix Double -> (Vector (Complex Double), Matrix (Complex Double))Source

Eigenvalues and right eigenvectors of a general real matrix, using LAPACK's dgeev. The eigenvectors are the columns of v. The eigenvalues are not sorted.

eigC :: Matrix (Complex Double) -> (Vector (Complex Double), Matrix (Complex Double))Source

Eigenvalues and right eigenvectors of a general complex matrix, using LAPACK's zgeev. The eigenvectors are the columns of v. The eigenvalues are not sorted.

eigS :: Matrix Double -> (Vector Double, Matrix Double)Source

Eigenvalues and right eigenvectors of a symmetric real matrix, using LAPACK's dsyev. The eigenvectors are the columns of v. The eigenvalues are sorted in descending order (use eigS' for ascending order).

eigS' :: Matrix Double -> (Vector Double, Matrix Double)Source

eigS in ascending order

eigH :: Matrix (Complex Double) -> (Vector Double, Matrix (Complex Double))Source

Eigenvalues and right eigenvectors of a hermitian complex matrix, using LAPACK's zheev. The eigenvectors are the columns of v. The eigenvalues are sorted in descending order (use eigH' for ascending order).

eigOnlyR :: Matrix Double -> Vector (Complex Double)Source

Eigenvalues of a general real matrix, using LAPACK's dgeev with jobz == 'N'. The eigenvalues are not sorted.

eigOnlyC :: Matrix (Complex Double) -> Vector (Complex Double)Source

Eigenvalues of a general complex matrix, using LAPACK's zgeev with jobz == 'N'. The eigenvalues are not sorted.

eigOnlyS :: Matrix Double -> Vector DoubleSource

Eigenvalues of a symmetric real matrix, using LAPACK's dsyev with jobz == 'N'. The eigenvalues are sorted in descending order.

eigOnlyH :: Matrix (Complex Double) -> Vector DoubleSource

Eigenvalues of a hermitian complex matrix, using LAPACK's zheev with jobz == 'N'. The eigenvalues are sorted in descending order.

LU

luR :: Matrix Double -> (Matrix Double, [Int])Source

LU factorization of a general real matrix, using LAPACK's dgetrf.

luC :: Matrix (Complex Double) -> (Matrix (Complex Double), [Int])Source

LU factorization of a general complex matrix, using LAPACK's zgetrf.

Cholesky

cholS :: Matrix Double -> Matrix DoubleSource

Cholesky factorization of a real symmetric positive definite matrix, using LAPACK's dpotrf.

cholH :: Matrix (Complex Double) -> Matrix (Complex Double)Source

Cholesky factorization of a complex Hermitian positive definite matrix, using LAPACK's zpotrf.

mbCholS :: Matrix Double -> Maybe (Matrix Double)Source

Cholesky factorization of a real symmetric positive definite matrix, using LAPACK's dpotrf (Maybe version).

mbCholH :: Matrix (Complex Double) -> Maybe (Matrix (Complex Double))Source

Cholesky factorization of a complex Hermitian positive definite matrix, using LAPACK's zpotrf (Maybe version).

QR

qrR :: Matrix Double -> (Matrix Double, Vector Double)Source

QR factorization of a real matrix, using LAPACK's dgeqr2.

qrC :: Matrix (Complex Double) -> (Matrix (Complex Double), Vector (Complex Double))Source

QR factorization of a complex matrix, using LAPACK's zgeqr2.

Hessenberg

hessR :: Matrix Double -> (Matrix Double, Vector Double)Source

Hessenberg factorization of a square real matrix, using LAPACK's dgehrd.

hessC :: Matrix (Complex Double) -> (Matrix (Complex Double), Vector (Complex Double))Source

Hessenberg factorization of a square complex matrix, using LAPACK's zgehrd.

Schur

schurR :: Matrix Double -> (Matrix Double, Matrix Double)Source

Schur factorization of a square real matrix, using LAPACK's dgees.

schurC :: Matrix (Complex Double) -> (Matrix (Complex Double), Matrix (Complex Double))Source

Schur factorization of a square complex matrix, using LAPACK's zgees.