SUBROUTINE LA_GEQP3( M, N, A, LDA, &
JPVT, TAU, WORK, LWORK, INFO )
INTEGER, INTENT(IN) :: LDA, LWORK, M, N
INTEGER, INTENT(OUT) :: INFO
INTEGER, INTENT(INOUT) :: JPVT( * )
REAL(wp), INTENT(INOUT) :: A( LDA, * )
REAL(wp), INTENT(OUT) :: TAU( * ), &
WORK(LWORK)
where
wp ::= KIND(1.0) KIND(1.0D0)
Complex version.
SUBROUTINE LA_GEQP3( M, N, A, LDA, &
JPVT, TAU, WORK, LWORK, RWORK, INFO )
INTEGER, INTENT(IN) :: LDA, LWORK, M, N
INTEGER, INTENT(OUT) :: INFO
INTEGER, INTENT(INOUT) :: JPVT( * )
COMPLEX(wp), INTENT(INOUT) :: A( LDA, * )
COMPLEX(wp), INTENT(OUT) :: TAU( * ), &
WORK(LWORK)
REAL(wp), INTENT(OUT) :: RWORK( * )
where
wp ::= KIND(1.0) KIND(1.0D0)
LA_GEQP3 computes a factorization with column pivoting of a
matrix : using Level 3 BLAS.
References: See [1] and [9,20,36].
-----------------------------------
LA_GEQRF
Real and complex versions.
SUBROUTINE LA_GEQRF( M, N, A, LDA, TAU, &
WORK, LWORK, INFO )
INTEGER, INTENT(IN) :: LDA, LWORK, M, N
INTEGER, INTENT(OUT) :: INFO
type(wp), INTENT(INOUT) :: A(LDA,*)
type(wp), INTENT(OUT) :: TAU(*), &
WORK(LWORK)
where
type ::= REAL COMPLEX
wp ::= KIND(1.0) KIND(1.0D0)
LA_GEQRF computes a factorization of a real / complex
matrix .
References: See [1, pages 31, 33, 35, 45, 63, 147, 158,
160, 161, 188, 234] and [9,20].
-----------------------------------
LA_ORGQR / LA_UNGQR
Real and complex versions.
SUBROUTINE LA_ORGQR / LA_UNGQR( M, N, &
K, A, LDA, TAU, WORK, LWORK, INFO )
INTEGER, INTENT(IN) :: K, LDA, LWORK, M, N
INTEGER, INTENT(OUT) :: INFO
type(wp), INTENT(INOUT) :: A(LDA,*)
type(wp), INTENT(IN) :: TAU(*)
type(wp), INTENT(OUT) :: WORK(LWORK)
where
type ::= REAL COMPLEX
wp ::= KIND(1.0) KIND(1.0D0)
LA_ORGQR / LA_UNGQR generate an real / complex matrix
with orthonormal columns, which is defined as the first columns
of a product of elementary reflectors of order
as returned by LA_GEQRF.
References: See [1] and [9,20].
-----------------------------------
LA_ORMQR / LA_UNMQR
Real and complex versions.
SUBROUTINE LA_ORMQR / LA_UNMQR( &
SIDE, TRANS, M, N, K, A, LDA, TAU, C, &
LDC, WORK, LWORK, INFO )
CHARACTER(LEN=1), INTENT(IN) :: SIDE, &
TRANS
INTEGER, INTENT(IN) :: K, LDA, LDC, &
LWORK, M, N
INTEGER, INTENT(OUT) :: INFO
type(wp), INTENT(IN) :: A(LDA,*), TAU(*)
type(wp), INTENT(INOUT) :: C(LDC,*)
type(wp), INTENT(OUT) :: WORK(LWORK)
where
type ::= REAL COMPLEX
wp ::= KIND(1.0) KIND(1.0D0)
LA_ORMQR / LA_UNMQR overwrite the general real / complex
matrix C with , , or (respectively)
where is real orthogonal / complex unitary matrix defined as the product of
elementary reflectors as returned by LA_GEQRF.
References: See [1] and [9,20].
-----------------------------------
LA_GELQF
Real and complex versions.
SUBROUTINE LA_GELQF( M, N, A, LDA, TAU, &
WORK, LWORK, INFO )
INTEGER, INTENT(IN) :: LDA, LWORK, M, N
INTEGER, INTENT(OUT) :: INFO
type(wp), INTENT(INOUT) :: A(LDA,*)
type(wp), INTENT(OUT) :: TAU(*), &
WORK(LWORK)
where
type ::= REAL COMPLEX
wp ::= KIND(1.0) KIND(1.0D0)
LA_GELQF computes an factorization of a real /
complex : .
References: See [1] and [9,20].
-----------------------------------
LA_ORGLQ / LA_UNGLQ
Real and complex versions.
SUBROUTINE LA_ORGLQ / LA_UNGLQ( M, &
N, K, A, LDA, TAU, WORK, LWORK, INFO )
INTEGER, INTENT(IN) :: K, LDA, LWORK, &
M, N
INTEGER, INTENT(OUT) :: INFO
type(wp), INTENT(IN) :: TAU(*)
type(wp), INTENT(INOUT) :: A(LDA,*)
type(wp), INTENT(OUT) :: &
WORK(LWORK)
where
type ::= REAL COMPLEX
wp ::= KIND(1.0) KIND(1.0D0)
LA_ORGLQ / LA_UNGLQ generates an a real /
complex matrix with orthonormal rows, which is defined as the first
rows of a product of elementary reflectors of order
as returned by LA_GELQF.
References: See [1] and [9,20].
-----------------------------------
LA_ORMLQ / LA_UNMLQ
Real and complex versions.
SUBROUTINE LA_ORMLQ / LA_UNMLQ( SIDE, &
TRANS, M, N, K, A, LDA, TAU, C, LDC, &
WORK, LWORK, INFO )
CHARACTER(LEN=1), INTENT(IN) :: SIDE, &
TRANS
INTEGER, INTENT(IN) :: K, LDA, LDC, &
LWORK, M, N
INTEGER, INTENT(OUT) :: INFO
type(wp), INTENT(IN) :: A(LDA,*), TAU(*)
type(wp), INTENT(INOUT) :: C(LDC,*)
type(wp), INTENT(OUT) :: WORK(LWORK)
where
type ::= REAL COMPLEX
wp ::= KIND(1.0) KIND(1.0D0)
LA_ORMLQ / LA_UNMLQ overwrite the general real / complex
matrix with , , or (respectively)
where is a real orthogonal / complex unitary matrix defined as the product of
elementary reflectors as returned by LA_GELQF.
References: See [1] and [9,20].
-----------------------------------
LA_GEQLF
Real and complex versions.
SUBROUTINE LA_GEQLF( M, N, A, LDA, TAU, &
WORK, LWORK, INFO )
INTEGER, INTENT(IN) :: LDA, LWORK, M, N
INTEGER, INTENT(OUT) :: INFO
type(wp), INTENT(INOUT) :: A(LDA,*)
type(wp), INTENT(OUT) :: TAU(*), &
WORK(LWORK)
where
type ::= REAL COMPLEX
wp ::= KIND(1.0) KIND(1.0D0)
LA_GEQLF computes a factorization of a real / complex
matrix : .
References: See [1] and [9,20].
-----------------------------------
LA_ORGQL / LA_UNGQL
Real and complex versions.
SUBROUTINE LA_ORGQL / LA_UNGQL( M, N, &
K, A, LDA, TAU, WORK, LWORK, INFO )
INTEGER, INTENT(IN) :: K, LDA, LWORK, &
M, N
INTEGER, INTENT(OUT) :: INFO
type(wp), INTENT(IN) :: TAU(*)
type(wp), INTENT(INOUT) :: A(LDA,*)
type(wp), INTENT(OUT) :: WORK(LWORK)
where
type ::= REAL COMPLEX
wp ::= KIND(1.0) KIND(1.0D0)
LA_ORGQL / LA_UNGQL generate an real /
complex matrix Q with orthonormal columns, which is defined as the
last columns of a product of elementary reflectors of order
as returned by LA_GEQLF.
References: See [1] and [9,20].
-----------------------------------
LA_ORMQL / LA_UNMQL
Real and complex versions.
SUBROUTINE LA_ORMQL / LA_UNMQL( SIDE, &
TRANS, M, N, K, A, LDA, TAU, C, LDC, &
WORK, LWORK, INFO )
CHARACTER(LEN=1), INTENT(IN) :: SIDE, &
TRANS
INTEGER, INTENT(IN) :: K, LDA, LDC, &
LWORK, M, N
INTEGER, INTENT(OUT) :: INFO
type(wp), INTENT(IN) :: A(LDA,*), TAU(*)
type(wp), INTENT(INOUT) :: C(LDC,*)
type(wp), INTENT(OUT) :: &
WORK(LWORK)
where
type ::= REAL COMPLEX
wp ::= KIND(1.0) KIND(1.0D0)
LA_ORMQL / LA_UNMQL overwrites the general real /
complex matrix with , , and
(respectively) where is a real orthogonal / complex unitary matrix
defined as the product of as returned by LA_GEQLF.
References: See [1] and [9,20].
-----------------------------------
LA_GERQF
Real and complex versions.
SUBROUTINE LA_GERQF( M, N, A, LDA, TAU, &
WORK, LWORK, INFO )
INTEGER, INTENT(IN) :: LDA, LWORK, M, N
INTEGER, INTENT(OUT) :: INFO
type(wp), INTENT(INOUT) :: A(LDA,*)
type(wp), INTENT(OUT) :: TAU(*), &
WORK(LWORK)
where
type ::= REAL COMPLEX
wp ::= KIND(1.0) KIND(1.0D0)
LA_GERQF computes an factorization of a real /
complex matrix : .
References: See [1] and [9,20].
-----------------------------------
LA_ORGRQ / LA_UNGRQ
Real and complex versions.
SUBROUTINE LA_ORGRQ / LA_UNGRQ( M, &
N, K, A, LDA, TAU, WORK, LWORK, INFO )
INTEGER, INTENT(IN) :: K, LDA, LWORK, &
M, N
INTEGER, INTENT(OUT) :: INFO
type(wp), INTENT(IN) :: TAU(*)
type(wp), INTENT(INOUT) :: A(LDA,*)
type(wp), INTENT(OUT) :: &
WORK(LWORK)
where
type ::= REAL COMPLEX
wp ::= KIND(1.0) KIND(1.0D0)
LA_ORGRQ / LA_UNGRQ generates an real /
complex matrix with orthonormal rows,
which is defined as the last rows of a product of elementary
reflectors of order as returned by LA_GERQF.
References: See [1] and [9,20].
-----------------------------------
LA_ORMRQ / LA_UNMRQ
Real and complex versions.
SUBROUTINE LA_ORMRQ / LA_UNMRQ( SIDE, &
TRANS, M, N, K, A, LDA, TAU, C, LDC, &
WORK, LWORK, INFO )
CHARACTER(LEN=1), INTENT(IN) :: SIDE, &
TRANS
INTEGER, INTENT(IN) :: K, LDA, LDC, &
LWORK, M, N
INTEGER, INTENT(OUT) :: INFO
type(wp), INTENT(IN) :: A(LDA,*), TAU(*)
type(wp), INTENT(INOUT) :: C(LDC,*)
type(wp), INTENT(OUT) :: &
WORK(LWORK)
where
type ::= REAL COMPLEX
wp ::= KIND(1.0) KIND(1.0D0)
LA_ORMRQ / LA_UNMRQ overwrites the general real
/ complex matrix with , , and
(respectively),
where is a real orthogonal / complex unitary matrix defined as
the product of elementary reflectors as returned by LA_GERQF.
References: See [1] and [9,20].
-----------------------------------
LA_TZRZF
Real and complex versions.
SUBROUTINE LA_TZRZF( M, N, A, LDA, &
TAU, WORK, LWORK, INFO )
INTEGER, INTENT(IN) :: LDA, LWORK, M, N
INTEGER, INTENT(OUT) :: INFO
type(wp), INTENT(INOUT) :: A( LDA, * )
type(wp), INTENT(OUT) :: TAU( * ), &
WORK(LWORK)
where
type ::= REAL COMPLEX
wp ::= KIND(1.0) KIND(1.0D0)
LA_TZRZF reduces the ( ) real / complex
upper trapezoidal
matrix to upper triangular form by means of real orthogonal / unitary transformations.
References: See [1] and [9,20].
-----------------------------------
LA_ORMRZ / LA_UNMRZ
Real and complex versions.
SUBROUTINE LA_ORMRZ / LA_UNMRZ( SIDE, &
TRANS, M, N, K, L, A, LDA, TAU, C, LDC, &
WORK, LWORK, INFO )
CHARACTER(LEN=1), INTENT(IN) :: SIDE, &
TRANS
INTEGER, INTENT(IN) :: K, L, LDA, LDC, &
LWORK, M, N
INTEGER, INTENT(OUT) :: INFO
type(wp), INTENT(IN) :: A( LDA, * ), TAU( * )
type(wp), INTENT(INOUT) :: C( LDC, * )
type(wp), INTENT(OUT) :: WORK(LWORK)
where
type ::= REAL COMPLEX
wp ::= KIND(1.0) KIND(1.0D0)
LA_ORMRZ / LA_UNMRZ overwrites the general real / complex
with , , or (respectively)
where is a real orthogonal / complex unitary matrix defined as the
product of elementary reflectors as returned by LA_TZRZF.
References: See [1] and [9,20].
-----------------------------------