SUBROUTINE LA_POTRF( UPLO, N, A, LDA, &
INFO )
CHARACTER(LEN=1), INTENT(IN) :: UPLO
INTEGER, INTENT(IN) :: LDA, N
INTEGER, INTENT(OUT) :: INFO
type(wp), INTENT(INOUT) :: A(LDA,*)
where
type ::= REAL COMPLEX
wp ::= KIND(1.0) KIND(1.0D0)
LA_POTRF computes the Cholesky factorization of a real
symmetric / complex Hermitian positive definite matrix .
References: See [1] and [9,20].
-----------------------------------
LA_POTRS
Real and complex Hermitian versions.
SUBROUTINE LA_POTRS( UPLO, N, NRHS, &
A, LDA, B, LDB, INFO )
CHARACTER(LEN=1), INTENT(IN) :: UPLO
INTEGER, INTENT(IN) :: LDA, LDB, N, &
NRHS
INTEGER, INTENT(OUT) :: INFO
type(wp), INTENT(IN) :: A( LDA,*)
type(wp), INTENT(INOUT) :: rhs
where
type ::= REAL COMPLEX
wp ::= KIND(1.0) KIND(1.0D0)
rhs ::= B(LDB,*) B(*)
LA_POTRS solves a system of linear equations
with a a real symmetric / complex Hermitian positive definite
matrix using the Cholesky factorization computed by LA_POTRF.
References: See [1] and [9,20].
-----------------------------------
SUBROUTINE LA_POCON( UPLO, N, A, LDA, &
ANORM, RCOND, WORK, IWORK, INFO )
CHARACTER(LEN=1), INTENT(IN) :: &
UPLO
INTEGER, INTENT(IN) :: LDA, N
INTEGER, INTENT(OUT) :: INFO
REAL(wp), INTENT(IN) :: ANORM
REAL(wp), INTENT(OUT) :: RCOND
INTEGER, INTENT(OUT) :: IWORK( * )
REAL(wp), INTENT(IN) :: A( LDA, * )
REAL(wp), INTENT(OUT) :: WORK( * )
where
wp ::= KIND(1.0) KIND(1.0D0)
Complex Hermitian version.
SUBROUTINE LA_POCON( UPLO, N, A, LDA, &
ANORM, RCOND, WORK, RWORK, INFO )
CHARACTER(LEN=1), INTENT(IN) :: &
UPLO
INTEGER, INTENT(IN) :: LDA, N
INTEGER, INTENT(OUT) :: INFO
REAL(wp), INTENT(IN) :: ANORM
REAL(wp), INTENT(OUT) :: RCOND, &
RWORK(*)
COMPLEX(wp), INTENT(IN) :: A( LDA, * )
COMPLEX(wp), INTENT(OUT) :: WORK( * )
where
wp ::= KIND(1.0) KIND(1.0D0)
LA_POCON estimates the reciprocal of the condition number
of a real symmetric / complex Hermitian positive definite matrix using the
Cholesky factorization computed by POTRF.
References: See [1] and [9,21,20].
-----------------------------------
SUBROUTINE LA_PORFS( UPLO, N, NRHS, &
A, LDA, AF, LDAF, B, LDB, X, LDX, &
FERR, BERR, WORK, IWORK, INFO )
CHARACTER(LEN=1), INTENT(IN) :: &
UPLO
INTEGER, INTENT(IN) :: LDA, LDAF, &
LDB, LDX, N, NRHS
INTEGER, INTENT(OUT) :: INFO, &
IWORK(*)
REAL(wp), INTENT(OUT) :: err
REAL(wp), INTENT(IN) :: A( LDA,*), &
AF( LDAF,*), rhs
REAL(wp), INTENT(INOUT) :: sol
REAL(wp), INTENT(OUT) :: WORK(*)
where
wp ::= KIND(1.0) KIND(1.0D0)
rhs ::= B(LDB,*) B(*)
sol ::= X(LDX,*) X(*)
err ::= FERR(*), BERR(*) FERR, BERR
Complex Hermitian version.
SUBROUTINE LA_PORFS( UPLO, N, NRHS, &
A, LDA, AF, LDAF, B, LDB, X, LDX, &
FERR, BERR, WORK, RWORK, INFO )
CHARACTER(LEN=1), INTENT(IN) :: &
UPLO
INTEGER, INTENT(IN) :: LDA, LDAF, &
LDB, LDX, N, NRHS
INTEGER, INTENT(OUT) :: INFO
REAL(wp), INTENT(OUT) :: err, RWORK(*)
COMPLEX(wp), INTENT(IN) :: A( LDA,*), &
AF( LDAF,*), rhs
COMPLEX(wp), INTENT(INOUT) :: sol
COMPLEX(wp), INTENT(OUT) :: WORK(*)
where
wp ::= KIND(1.0) KIND(1.0D0)
rhs ::= B(LDB,*) B(*)
sol ::= X(LDX,*) X(*)
err ::= FERR(*), BERR(*) FERR, BERR
LA_PORFS improves the computed solution to a system of linear
equations when the coefficient matrix is a real symmetric / complex
Hermitian positive definite, and provides error bounds and backward
error estimates for the solution.
References: See [1] and [9,21,20].
-----------------------------------
LA_POTRI
Real and complex Hermitian versions.
SUBROUTINE LA_POTRI( UPLO, N, A, LDA, &
INFO )
CHARACTER(LEN=1), INTENT(IN) :: UPLO
INTEGER, INTENT(IN) :: LDA, N
INTEGER, INTENT(OUT) :: INFO
type(wp), INTENT(INOUT) :: A( LDA,*)
where
type ::= REAL COMPLEX
wp ::= KIND(1.0) KIND(1.0D0)
LA_POTRI computes the inverse of a real symmetric /
complex Hermitian positive definite matrix using the Cholesky
factorization computed by LA_POTRF.
References: See [1] and [9,20].
-----------------------------------
LA_POEQU
Real and complex Hermitian versions.
SUBROUTINE LA_POEQU( N, A, LDA, S, &
SCOND, AMAX, INFO )
INTEGER, INTENT(IN) :: LDA, N
INTEGER, INTENT(OUT) :: INFO
REAL(wp), INTENT(OUT) :: AMAX, &
SCOND, S(*)
type(wp), INTENT(IN) :: A( LDA,*)
where
type ::= REAL COMPLEX
wp ::= KIND(1.0) KIND(1.0D0)
LA_POEQU computes row and column scalings intended to equilibrate a
real symmetric / complex Hermitian positive definite matrix and
reduce its condition number.
References: See [1] and [9,21,20].
-----------------------------------
LA_PPTRF
Real and complex Hermitian versions.
SUBROUTINE LA_PPTRF( UPLO, N, AP, &
INFO )
CHARACTER(LEN=1), INTENT(IN) :: UPLO
INTEGER, INTENT(IN) :: N
INTEGER, INTENT(OUT) :: INFO
type(wp), INTENT(INOUT) :: AP(*)
where
type ::= REAL COMPLEX
wp ::= KIND(1.0) KIND(1.0D0)
LA_PPTRF computes the Cholesky factorization of a real
symmetric / complex Hermitian positive definite matrix
stored in packed format.
References: See [1] and [9,20].
-----------------------------------
LA_PPTRS
Real and complex Hermitian versions.
SUBROUTINE LA_PPTRS( UPLO, N, NRHS, &
AP, B, LDB, INFO )
CHARACTER(LEN=1), INTENT(IN) :: UPLO
INTEGER, INTENT(IN) :: LDB, N, NRHS
INTEGER, INTENT(OUT) :: INFO
type(wp), INTENT(IN) :: AP(*)
type(wp), INTENT(INOUT) :: rhs
where
type ::= REAL COMPLEX
wp ::= KIND(1.0) KIND(1.0D0)
rhs ::= B(LDB,*) B(*)
LA_PPTRS solves a system of linear equations with
a real symmetric / complex Hermitian positive definite matrix
in packed storage using the Cholesky factorization computed by LA_PPTRF.
References: See [1] and [9,20].
-----------------------------------
SUBROUTINE LA_PPCON( UPLO, N, AP, &
ANORM, RCOND, WORK, IWORK, INFO )
CHARACTER(LEN=1), INTENT(IN) :: UPLO
INTEGER, INTENT(IN) :: N
INTEGER, INTENT(OUT) :: INFO, IWORK(*)
REAL(wp), INTENT(IN) :: ANORM
REAL(wp), INTENT(OUT) :: RCOND
REAL(wp), INTENT(IN) :: AP(*)
REAL(wp), INTENT(OUT) :: WORK(*)
where
wp ::= KIND(1.0) KIND(1.0D0)
Complex Hermitian version.
SUBROUTINE LA_PPCON( UPLO, N, AP, &
ANORM, RCOND, WORK, RWORK, INFO )
CHARACTER(LEN=1), INTENT(IN) :: UPLO
INTEGER, INTENT(IN) :: N
INTEGER, INTENT(OUT) :: INFO
REAL(wp), INTENT(IN) :: ANORM
REAL(wp), INTENT(OUT) :: RCOND, &
RWORK(*)
COMPLEX(wp), INTENT(IN) :: AP(*)
COMPLEX(wp), INTENT(OUT) :: WORK(*)
where
wp ::= KIND(1.0) KIND(1.0D0)
LA_PPCON estimates the reciprocal of the condition number
of a real symmetric / complex Hermitian positive definite packed
matrix using the Cholesky factorization computed by LA_PPTRF.
References: See [1] and [9,21,20].
-----------------------------------
SUBROUTINE LA_PPRFS( UPLO, N, NRHS, &
AP, AFP, B, LDB, X, LDX, FERR, BERR, &
WORK, IWORK, INFO )
CHARACTER(LEN=1), INTENT(IN) :: UPLO
INTEGER, INTENT(IN) :: LDB, LDX, N, NRHS
INTEGER, INTENT(OUT) :: INFO, IWORK(*)
REAL(wp), INTENT(OUT) :: err
REAL(wp), INTENT(IN) :: AFP(*), AP(*), rhs
REAL(wp), INTENT(INOUT) :: sol
REAL(wp), INTENT(OUT) :: WORK(*)
where
wp ::= KIND(1.0) KIND(1.0D0)
rhs ::= B(LDB,*) B(*)
sol ::= X(LDX,*) X(*)
err ::= FERR(*), BERR(*) FERR, BERR
Complex Hermitian version.
SUBROUTINE LA_PPRFS( UPLO, N, NRHS, &
AP, AFP, B, LDB, X, LDX, FERR, BERR, &
WORK, RWORK, INFO )
CHARACTER(LEN=1), INTENT(IN) :: UPLO
INTEGER, INTENT(IN) :: LDB, LDX, N, NRHS
INTEGER, INTENT(OUT) :: INFO
REAL(wp), INTENT(OUT) :: err, RWORK(*)
COMPLEX(wp), INTENT(IN) :: AFP(*), AP(*), &
rhs
COMPLEX(wp), INTENT(INOUT) :: sol
COMPLEX(wp), INTENT(OUT) :: WORK(*)
where
wp ::= KIND(1.0) KIND(1.0D0)
rhs ::= B(LDB,*) B(*)
sol ::= X(LDX,*) X(*)
err ::= FERR(*), BERR(*) FERR, BERR
LA_PPRFS improves the computed solution to a system of linear
equations when the coefficient matrix is a real symmetric /
complex Hermitian positive definite and packed, and provides error
bounds and backward error estimates for the solution.
References: See [1] and [9,21,20].
-----------------------------------
LA_PPTRI
Real and complex Hermitian versions.
SUBROUTINE LA_PPTRI( UPLO, N, AP, INFO )
CHARACTER(LEN=1), INTENT(IN) :: UPLO
INTEGER, INTENT(IN) :: N
INTEGER, INTENT(OUT) :: INFO
type(wp), INTENT(INOUT) :: AP(*)
where
type ::= REAL COMPLEX
wp ::= KIND(1.0) KIND(1.0D0)
LA_PPTRI computes the inverse of real symmetric /
complex Hermitian positive definite matrix in packed storage format
using the Cholesky factorization computed by LA_PPTRF.
References: See [1] and [9,20].
-----------------------------------
LA_PPEQU
Real and complex Hermitian versions.
SUBROUTINE LA_PPEQU( UPLO, N, AP, S, &
SCOND, AMAX, INFO )
CHARACTER(LEN=1), INTENT(IN) :: UPLO
INTEGER, INTENT(IN) :: N
INTEGER, INTENT(OUT) :: INFO
REAL(wp), INTENT(OUT) :: AMAX, SCOND, &
S(*)
type(wp), INTENT(IN) :: AP(*)
where
type ::= REAL COMPLEX
wp ::= KIND(1.0) KIND(1.0D0)
LA_PPEQU computes row and column scalings intended to
equilibrate a real symmetric / complex Hermitian positive definite
matrix in packed storage and reduce its condition number.
References: See [1] and [9,21,20].
-----------------------------------
LA_PBTRF
Real and complex Hermitian versions.
SUBROUTINE LA_PBTRF( UPLO, N, KD, AB, &
LDAB, INFO )
CHARACTER(LEN=1), INTENT(IN) :: UPLO
INTEGER, INTENT(IN) :: KD, LDAB, N
INTEGER, INTENT(OUT) :: INFO
type(wp), INTENT(INOUT) :: AB( LDAB,*)
where
type ::= REAL COMPLEX
wp ::= KIND(1.0) KIND(1.0D0)
LA_PBTRF computes the Cholesky factorization of a real
symmetric / complex Hermitian positive definite band matrix .
References: See [1] and [9,20].
-----------------------------------
LA_PBTRS
Real and complex Hermitian versions.
SUBROUTINE LA_PBTRS( UPLO, N, KD, &
NRHS, AB, LDAB, B, LDB, INFO )
CHARACTER(LEN=1), INTENT(IN) :: UPLO
INTEGER, INTENT(IN) :: KD, LDAB, LDB, &
N, NRHS
INTEGER, INTENT(OUT) :: INFO
type(wp), INTENT(IN) :: AB( LDAB,*)
type(wp), INTENT(INOUT) :: rhs
where
type ::= REAL COMPLEX
wp ::= KIND(1.0) KIND(1.0D0)
rhs ::= B(LDB,*) B(*)
LA_PBTRS solves a system of linear equations with
a real symmetric / complex Hermitian positive definite band matrix
using the Cholesky factorization computed by LA_PBTRF.
References: See [1] and [9,20].
-----------------------------------
SUBROUTINE LA_PBCON( UPLO, N, KD, AB, &
LDAB, ANORM, RCOND, WORK, IWORK, &
INFO )
CHARACTER(LEN=1), INTENT(IN) :: UPLO
INTEGER, INTENT(IN) :: KD, LDAB, N
INTEGER, INTENT(OUT) :: INFO, IWORK(*)
REAL(wp), INTENT(IN) :: ANORM
REAL(wp), INTENT(OUT) :: RCOND
REAL(wp), INTENT(IN) :: AB( LDAB,*)
REAL(wp), INTENT(OUT) :: WORK(*)
where
wp ::= KIND(1.0) KIND(1.0D0)
Complex Hermitian version.
SUBROUTINE LA_PBCON( UPLO, N, KD, AB, &
LDAB, ANORM, RCOND, WORK, RWORK, &
INFO )
CHARACTER(LEN=1), INTENT(IN) :: UPLO
INTEGER, INTENT(IN) :: KD, LDAB, N
INTEGER, INTENT(OUT) :: INFO
REAL(wp), INTENT(IN) :: ANORM
REAL(wp), INTENT(OUT) :: RCOND, &
RWORK(*)
COMPLEX(wp), INTENT(IN) :: AB( LDAB,*)
COMPLEX(wp), INTENT(OUT) :: WORK(*)
where
wp ::= KIND(1.0) KIND(1.0D0)
LA_PBCON estimates the reciprocal of the condition number
of a real symmetric / complex Hermitian positive definite band
matrix using the Cholesky factorization computed by LA_PBTRF.
References: See [1] and [9,21,20].
-----------------------------------
SUBROUTINE LA_PBRFS( UPLO, N, KD, &
NRHS, AB, LDAB, AFB, LDAFB, B, LDB, &
X, LDX, FERR, BERR, WORK, IWORK, &
INFO )
CHARACTER(LEN=1), INTENT(IN) :: UPLO
INTEGER, INTENT(IN) :: KD, LDAB, LDAFB, &
LDB, LDX, N, NRHS
INTEGER, INTENT(OUT) :: INFO, IWORK(*)
REAL(wp), INTENT(OUT) :: err
REAL(wp), INTENT(IN) :: AB( LDAB,*), &
AFB( LDAFB,*), rhs
REAL(wp), INTENT(INOUT) :: sol
REAL(wp), INTENT(OUT) :: WORK(*)
where
wp ::= KIND(1.0) KIND(1.0D0)
rhs ::= B(LDB,*) B(*)
sol ::= X(LDX,*) X(*)
err ::= FERR(*), BERR(*) FERR, BERR
Complex Hermitian version.
SUBROUTINE LA_PBRFS( UPLO, N, KD, &
NRHS, AB, LDAB, AFB, LDAFB, B, LDB, &
X, LDX, FERR, BERR, WORK, RWORK, &
INFO )
CHARACTER(LEN=1), INTENT(IN) :: UPLO
INTEGER, INTENT(IN) :: KD, LDAB, LDAFB, &
LDB, LDX, N, NRHS
INTEGER, INTENT(OUT) :: INFO
REAL(wp), INTENT(OUT) :: err, RWORK(*),
COMPLEX(wp), INTENT(IN) :: AB( LDAB,*), &
AFB( LDAFB,*), rhs
COMPLEX(wp), INTENT(INOUT) :: sol
COMPLEX(wp), INTENT(OUT) :: WORK(*)
where
wp ::= KIND(1.0) KIND(1.0D0)
rhs ::= B(LDB,*) B(*)
sol ::= X(LDX,*) X(*)
err ::= FERR(*), BERR(*) FERR, BERR
LA_PBRFS improves the computed solution to a system of linear
equations when the coefficient matrix is a real symmetric / complex
Hermitian positive definite banded, and provides error bounds and
backward error estimates for the solution.
References: See [1] and [9,21,20].
-----------------------------------
LA_PBEQU
Real and complex Hermitian versions.
SUBROUTINE LA_PBEQU( UPLO, N, KD, AB, &
LDAB, S, SCOND, AMAX, INFO )
CHARACTER(LEN=1), INTENT(IN) :: UPLO
INTEGER, INTENT(IN) :: KD, LDAB, N
INTEGER, INTENT(OUT) :: INFO
REAL(wp), INTENT(OUT) :: AMAX, SCOND, &
S(*)
type(wp), INTENT(IN) :: AB( LDAB,*)
where
type ::= REAL COMPLEX
wp ::= KIND(1.0) KIND(1.0D0)
LA_PBEQU computes row and column scalings intended to
equilibrate a real symmetric / complex Hermitian positive definite
band matrix A and reduce its condition number.
References: See [1] and [9,21,20].
-----------------------------------
LA_PTTRF
Real and complex Hermitian versions.
SUBROUTINE LA_PTTRF( N, D, E, INFO )
INTEGER, INTENT(IN) :: N
INTEGER, INTENT(OUT) :: INFO
REAL(wp), INTENT(INOUT) :: D( * )
type(wp), INTENT(INOUT) :: E( * )
where
type ::= REAL COMPLEX
wp ::= KIND(1.0) KIND(1.0D0)
LA_PTTRF computes the factorization of a real
symmetric / complex Hermitian positive definite tridiagonal matrix
. The factorization may also be regarded as having the form .
References: See [1] and [9,20].
-----------------------------------
SUBROUTINE LA_PTTRS( N, NRHS, D, E, B, &
LDB, INFO )
INTEGER, INTENT(IN) :: LDB, N, NRHS
INTEGER, INTENT(OUT) :: INFO
REAL(wp), INTENT(IN) :: D(*)
REAL(wp), INTENT(IN) :: E(*)
REAL(wp), INTENT(INOUT) :: rhs
where
wp ::= KIND(1.0) KIND(1.0D0)
rhs ::= B(LDB,*) B(*)
SUBROUTINE LA_PTTRS( UPLO, N, NRHS, D, &
E, B, LDB, INFO )
CHARACTER(LEN=1), INTENT(IN) :: UPLO
INTEGER, INTENT(IN) :: LDB, N, NRHS
INTEGER, INTENT(OUT) :: INFO
REAL(wp), INTENT(IN) :: D(*)
COMPLEX(wp), INTENT(IN) :: E(*)
COMPLEX(wp), INTENT(INOUT) :: rhs
where
wp ::= KIND(1.0) KIND(1.0D0)
rhs ::= B(LDB,*) B(*)
LA_PTTRS solves a real symmetric / complex Hermitian positive
definite tridiagonal system of the form ,
using the factorization computed by LA_PTTRF.
References: See [1] and [9,20].
-----------------------------------
LA_PTCON
Real and complex Hermitian versions.
SUBROUTINE LA_PTCON( N, D, E, ANORM, &
RCOND, RWORK, INFO )
INTEGER, INTENT(IN) :: N
INTEGER, INTENT(OUT) :: INFO
REAL(wp), INTENT(IN) :: ANORM, D(*)
REAL(wp), INTENT(OUT) :: RCOND, &
RWORK(*)
type(wp), INTENT(IN) :: E(*)
where
type ::= REAL COMPLEX
wp ::= KIND(1.0) KIND(1.0D0)
LA_PTCON computes the reciprocal of the condition number
of a real symmetric / complex Hermitian positive definite tridiagonal matrix
using the factorization computed by LA_PTTRF.
References: See [1] and [9,21,20].
-----------------------------------
SUBROUTINE LA_PTRFS( N, NRHS, D, E, DF, &
EF, B, LDB, X, LDX, FERR, BERR, WORK, &
INFO )
INTEGER, INTENT(IN) :: LDB, LDX, N, NRHS
INTEGER, INTENT(OUT) :: INFO
REAL(wp), INTENT(IN) :: D(*), DF(*)
REAL(wp), INTENT(OUT) :: err
REAL(wp), INTENT(IN) :: rhs, E(*), EF(*)
REAL(wp), INTENT(INOUT) :: sol
REAL(wp), INTENT(OUT) :: WORK(*)
where
wp ::= KIND(1.0) KIND(1.0D0)
rhs ::= B(LDB,*) B(*)
sol ::= X(LDX,*) X(*)
err ::= FERR(*), BERR(*) FERR, BERR
Complex Hermitian version.
SUBROUTINE LA_PTRFS( UPLO, N, NRHS, D, &
E, DF, EF, B, LDB, X, LDX, FERR, BERR, &
WORK, RWORK, INFO )
CHARACTER(LEN=1), INTENT(IN) :: UPLO
INTEGER, INTENT(IN) :: LDB, LDX, N, NRHS
INTEGER, INTENT(OUT) :: INFO
REAL(wp), INTENT(IN) :: D(*), DF(*)
REAL(wp), INTENT(OUT) :: err, &
RWORK(*)
COMPLEX(wp), INTENT(IN) :: rhs, E(*), EF(*)
COMPLEX(wp), INTENT(INOUT) :: sol
COMPLEX(wp), INTENT(OUT) :: WORK(*)
where
wp ::= KIND(1.0) KIND(1.0D0)
rhs ::= B(LDB,*) B(*)
sol ::= X(LDX,*) X(*)
err ::= FERR(*), BERR(*) FERR, BERR
LA_PTRFS improves the computed solution to a system of linear
equations when the coefficient matrix is a real symmetric / complex
Hermitian positive definite and tridiagonal, and provides error bounds
and backward error estimates for the solution.
References: See [1] and [9,21,20].
-----------------------------------