dblaux - Man Page

Name

dblaux — Double Precision Auxiliary Routines

— Helper routines for double precision computations.  

Synopsis

Functions

subroutine dla_itranspose (k, kh, l, lh, x, ldx)
Solver for 4-by-4 Linear Systems.
subroutine dla_qtrmm2 (side, trans, m, n, alpha, a, lda, b, ldb, c, ldc)
Multiply with the sub-diagonal entries of a quasi triangular matrix.
subroutine dla_small_solve4 (n, a, rhs, info, eps, smlnum)
Solver for 4-by-4 Linear Systems.
subroutine dla_small_solve8 (n, a, rhs, info, eps, smlnum)
Solver for 8-by-8 Linear Systems.
subroutine dla_sort_ev (n, a, lda, q, ldq, nb, work, info)
Block Reordering of generalized Eigenvalues.
subroutine dla_sort_gev (n, a, lda, b, ldb, q, ldq, z, ldz, nb, work, lwork, info)
Block Reordering of generalized Eigenvalues.
subroutine dla_transform_general (trans, m, n, x, ldx, qa, ldqa, qb, ldqb, work)
Transform the Right-Hand Side or Solution for generalized projections.
subroutine dla_transform_standard (trans, m, x, ldx, q, ldq, work)
Transform the Right-Hand Side or Solution for standard projections.

Detailed Description

Helper routines for double precision computations.

This section contains a set of helper routines for the double precision computational routines. This includes the transformation of the right-hand-sides, the transformation of the solutions, the solution of special linear systems and the sorting of eigenvalues.

Function Documentation

subroutine dla_itranspose (integer k, integer kh, integer l, integer lh, double precision, dimension(ldx,*) x, integer ldx)

Solver for 4-by-4 Linear Systems.

Purpose:

!>
!> DLA_ITRANSPOSE performs the implicit transpose
!>
!>    X(L:LH,K:KH ) <- X(K:KH,L:LH)**T                                                   (1)
!>
!>
Parameters

K

!>          K is INTEGER
!>          First index of the transpose operations as in (1)
!>

KH

!>          KH is INTEGER
!>          Second index of the transpose operations as in (1)
!>

L

!>          L is INTEGER
!>          Third index of the transpose operations as in (1)
!>

LH

!>          LH is INTEGER
!>          Fourth index of the transpose operations as in (1)
!>

X

!>          X is DOUBLE PRECISION array, dimension (LDX,*)
!>          X is the matrix to perform the transpose on.
!>

LDX

!>             LDX  is  INTEGER
!>             The leading dimension of the array X.  LDX >= MAX(1,KH,LH).
!>
Author

Martin Koehler, MPI Magdeburg

Date

January 2024

Definition at line 86 of file dla_itranspose.f90.

subroutine dla_qtrmm2 (character(1) side, character(1) trans, integer m, integer n, double precision alpha, double precision, dimension(lda, *) a, integer lda, double precision, dimension(ldb, *) b, integer ldb, double precision, dimension(ldc,*) c, integer ldc)

Multiply with the sub-diagonal entries of a quasi triangular matrix.

Purpose:

!>
!>     Multiply a matrix with the sub-diagonal entries of a quasi-triangular matrix. 
!>     Consider a quasi-triangular matrix A where sub(A) is the matrix only containing 
!>     the sub-diagonal entries. Than the DLA_QTRMM2 routine computes 
!> 
!>        C = C + ALPHA * op(sub(A)) * B                                                (1) 
!> 
!>     or 
!> 
!>        C = C + ALPHA * B * op(sub(A))                                                (2) 
!> 
!>
Attention

The routine does not check the input arguments.

Parameters

SIDE

!>          SIDE is CHARACTER(1)
!>           On entry,  SIDE specifies whether  op( A ) multiplies B from
!>           the left or right as follows:
!>
!>              SIDE = 'L' or 'l'   B := alpha*op( A )*B.
!>
!>              SIDE = 'R' or 'r'   B := alpha*B*op( A ).
!>

TRANS

!>          TRANS is CHARACTER(1)
!>           On entry, TRANS specifies the form of op( A ) to be used in
!>           the matrix multiplication as follows:
!>
!>              TRANS == 'N' or 'n'   op( A ) = A.
!>
!>              TRANS == 'T' or 't'   op( A ) = A**T.
!>
!>              TRANS = 'C' or 'c'   op( A ) = A**T.
!>

M

!>          M is INTEGER
!>           On entry, M specifies the number of rows of B. M must be at
!>           least zero.
!>

N

!>          N is INTEGER
!>           On entry, N specifies the number of columns of B.  N must be
!>           at least zero.
!>

ALPHA

!>          ALPHA is DOUBLE PRECISION.
!>           On entry,  ALPHA specifies the scalar  alpha. When  alpha is
!>           zero then  A is not referenced and  B need not be set before
!>           entry.
!>

A

!>           A is DOUBLE PRECISION array of DIMENSION ( LDA, k ), where k is m
!>           when  SIDE = 'L' or 'l'  and is  n  when  SIDE = 'R' or 'r'.
!>           The  leading  k by k 
!>           upper triangular part of the array  A must contain the upper
!>           quasi triangular matrix.
!>

LDA

!>          LDA is INTEGER
!>           On entry, LDA specifies the first dimension of A as declared
!>           in the calling (sub) program.  When  SIDE = 'L' or 'l'  then
!>           LDA  must be at least  max( 1, m ),  when  SIDE = 'R' or 'r'
!>           then LDA must be at least max( 1, n ).
!>

B

!>           B is DOUBLE PRECISION array of DIMENSION ( LDB, n ).
!>           Before entry,  the leading  m by n part of the array  B must
!>           contain the matrix  B.
!>

LDB

!>          LDB is INTEGER
!>           On entry, LDB specifies the first dimension of B as declared
!>           in  the  calling  (sub)  program.   LDB  must  be  at  least
!>           max( 1, m ).
!>

C

!>           C is DOUBLE PRECISION array of DIMENSION ( LDC, n ).
!>           Before entry,  the leading  m by n part of the array  C must
!>           contain the matrix  C,  and  on exit  is overwritten  by the
!>           update January 2021
!>

LDC

!>          LDC is INTEGER
!>           On entry, LDC specifies the first dimension of C as declared
!>           in  the  calling  (sub)  program.   LDB  must  be  at  least
!>           max( 1, m ).
!>
Author

Martin Koehler, MPI Magdeburg

Date

January 2024

Definition at line 153 of file dla_qtrmm2.f90.

subroutine dla_small_solve4 (integer n, double precision, dimension( 4, 4 ) a, double precision, dimension(4) rhs, integer info, double precision eps, double precision smlnum)

Solver for 4-by-4 Linear Systems.

Purpose:

!>
!> DLA_SMALL_SOLVE4 solves a linear system
!>
!>    A * x = b                                                                          (1)
!>
!> where A is a most a 4 by 4 matrix.
!>
Parameters

N

!>          N is INTEGER
!>          The order of the matrix A  N = (1,2,4).
!>

A

!>          A is DOUBLE PRECISION array, dimension (4,4)
!>          The matrix A must be stored in a 4-by-4 matrix even if it is smaller.
!>          On output the matrix  A is destroyed.
!>

RHS

!>          RHS is DOUBLE PRECISION array, dimension (4)
!>          The matrix RHS contains the right hand side on input and the solution X on output if INFO == 0
!>

INFO

!>          INFO is INTEGER
!>          == 0:  successful exit
!>          < 0:  if INFO = -i, the i-th argument had an illegal value
!>          > 0:  The equation is not solved correctly. One of the arising inner
!>                system got singular.
!>

EPS

!>          EPS is DOUBLE PRECISION
!>          EPS is the machine epsilon determined by DLAMCH
!>

SMLNUM

!>          SMLNUM is DOUBLE PRECISION
!>          SMLNUM is the smallest number in DOUBLE PRECISION which can be represented without underflow.
!>
Author

Martin Koehler, MPI Magdeburg

Date

January 2024

Definition at line 98 of file dla_small_solve4.f90.

subroutine dla_small_solve8 (integer n, double precision, dimension( 8, 8 ) a, double precision, dimension(8) rhs, integer info, double precision eps, double precision smlnum)

Solver for 8-by-8 Linear Systems.

Purpose:

!>
!> DLA_SMALL_SOLVE8 solves a linear system
!>
!>    A * x = b                                                                          (1)
!>
!> where A is a most a 8 by 8 matrix with leading dimension 8.
!>
Parameters

N

!>          N is INTEGER
!>          The order of the matrix A  N = {1,2,4,8} .
!>

A

!>          A is DOUBLE PRECISION array, dimension (8,8)
!>          The matrix A must be stored in a 4-by-4 matrix even if it is smaller.
!>          On output the matrix  A is destroyed.
!>

RHS

!>          RHS is DOUBLE PRECISION array, dimension (8)
!>          The matrix RHS contains the right hand side on input and the solution X on output if INFO == 0
!>

INFO

!>          INFO is INTEGER
!>          == 0:  successful exit
!>          < 0:  if INFO = -i, the i-th argument had an illegal value
!>          > 0:  The equation is not solved correctly. One of the arising inner
!>                system got singular.
!>

EPS

!>          EPS is DOUBLE PRECISION
!>          EPS is the machine epsilon determined by DLAMCH
!>

SMLNUM

!>          SMLNUM is DOUBLE PRECISION
!>          SMLNUM is the smallest number in DOUBLE PRECISION which can be represented without underflow.
!>
Author

Martin Koehler, MPI Magdeburg

Date

January 2024

Definition at line 98 of file dla_small_solve8.f90.

subroutine dla_sort_ev (integer n, double precision, dimension( lda, * ) a, integer lda, double precision, dimension( ldq, * ) q, integer ldq, integer nb, double precision, dimension( * ) work, integer info)

Block Reordering of generalized Eigenvalues.

Purpose:

!>
!>     Reorder the eigenvalues of a matrix A such that
!>     the complex eigenvalues pairs will not cause a change of the block
!>     size in blocked linear matrix equation solver codes.
!>
!>     The function uses DTREXC from LAPACK for moving the eigenvalues
!>     on the diagonal.
!>
!>
Parameters

N

!>          N is INTEGER
!>          The order of the matrices A and Q, N >= 0.
!>

A

!>             A  is a DOUBLE PRECISION array, dimension (LDA,N)
!>             On entry, the leading N-by-N upper
!>             Hessenberg part of this array must contain the
!>             generalized Schur factor A_s of the matrix A.
!>             On exit, the leading N-by-N part of this array contains
!>             the generalized Schur factor A_s of the matrix A with
!>             no complex eigenvalues pairs an A(k*NB,k*NB), where k is
!>             a non negative integer.
!>

LDA

!>             LDA is INTEGER
!>             The leading dimension of the array A.  LDA >= MAX(1,N).
!>

Q

!>             Q is a DOUBLE PRECISION array, dimension (LDQ,N)
!>             On entry, the leading N-by-N part of
!>             this array must contain the orthogonal matrix Q from
!>             the generalized Schur factorization.
!>             On exit, the leading N-by-N part of this array contains
!>             the update January 2021
!>             factorization with integrated eigenvalue reordering.
!>

LDQ

!>             LDQ  is  INTEGER
!>             The leading dimension of the array Q.  LDQ >= MAX(1,N).
!>

NB

!>            NB is INTEGER
!>             Block size of the solver planed to use. Typical values
!>             are 16, 32, or 64. The block size must be an even positive
!>             integer otherwise an error is returned.
!>

WORK

!>             WORK is INTEGER array, dimension (N)
!>             Workspace
!>

INFO

!>             INFO is INTEGER
!>             == 0:  successful exit;
!>             < 0:  if INFO = -i, the i-th argument had an illegal
!>                   value;
!>             = 1:  The internal DTGEX2 caused an error. ]
!>
Author

Martin Koehler, MPI Magdeburg

Date

January 2024

Definition at line 124 of file dla_sort_ev.f90.

subroutine dla_sort_gev (integer n, double precision, dimension( lda, * ) a, integer lda, double precision, dimension( ldb, * ) b, integer ldb, double precision, dimension( ldq, * ) q, integer ldq, double precision, dimension( ldz, * ) z, integer ldz, integer nb, double precision, dimension( * ) work, integer lwork, integer info)

Block Reordering of generalized Eigenvalues.

Purpose:

!>
!>     Reorder the eigenvalues of a matrix pencil (A,B) such that
!>     the complex eigenvalues pairs will not cause a change of the block
!>     size in blocked linear matrix equation solver codes.
!>
!>     The function uses DTGEX2 from LAPACK for moving the eigenvalues
!>     on the diagonal.
!>
!>
Parameters

N

!>          N is INTEGER
!>          The order of the matrices A, B, Q, and Z, N >= 0.
!>

A

!>             A  is a DOUBLE PRECISION array, dimension (LDA,N)
!>             On entry, the leading N-by-N upper
!>             Hessenberg part of this array must contain the
!>             generalized Schur factor A_s of the matrix A.
!>             On exit, the leading N-by-N part of this array contains
!>             the generalized Schur factor A_s of the matrix A with
!>             no complex eigenvalues pairs an A(k*NB,k*NB), where k is
!>             a non negative integer.
!>

LDA

!>             LDA is INTEGER
!>             The leading dimension of the array A.  LDA >= MAX(1,N).
!>

B

!>             B is a DOUBLE PRECISION array, dimension (LDB,N)
!>             On entry, the leading N-by-N upper
!>             triangular part of this array must contain the
!>             generalized Schur factor B_s of the matrix B,
!>             On exit, the leading N-by-N part of this array contains
!>             the generalized Schur factor B_s of the matrix B
!>             with reordered eigenvalues.
!>

LDB

!>             LDB is INTEGER
!>             The leading dimension of the array B.  LDB >= MAX(1,N).
!>

Q

!>             Q is a DOUBLE PRECISION array, dimension (LDQ,N)
!>             On entry, the leading N-by-N part of
!>             this array must contain the orthogonal matrix Q from
!>             the generalized Schur factorization.
!>             On exit, the leading N-by-N part of this array contains
!>             the update January 2021
!>             factorization with integrated eigenvalue reordering.
!>

LDQ

!>             LDQ  is  INTEGER
!>             The leading dimension of the array Q.  LDQ >= MAX(1,N).
!>

Z

!>              Z is a DOUBLE PRECISION array, dimension (LDZ,N)
!>              On entry, the leading N-by-N part of
!>              this array must contain the orthogonal matrix Z from
!>              the generalized Schur factorization.
!>              On exit, the leading N-by-N part of this array contains
!>              the update January 2021
!>              factorization with integrated eigenvalue reordering.
!>

LDZ

!>             LDZ is INTEGER
!>             The leading dimension of the array Z.  LDZ >= MAX(1,N).
!>

NB

!>            NB is INTEGER
!>             Block size of the solver planed to use. Typical values
!>             are 16, 32, or 64. The block size must be an even positive
!>             integer otherwise an error is returned.
!>

WORK

!>             WORK is INTEGER array, dimension (LWORK)
!>             Workspace
!>

LWORK

!>            LWORK  is INTEGER
!>            Size of the workspace.
!>            LWORK >= MAX(1, 4*N, 256)
!>

INFO

!>             INFO is INTEGER
!>             == 0:  successful exit;
!>             < 0:  if INFO = -i, the i-th argument had an illegal
!>                   value;
!>             = 1:  The internal DTGEX2 caused an error. ]
!>
Author

Martin Koehler, MPI Magdeburg

Date

January 2024

Definition at line 165 of file dla_sort_gev.f90.

subroutine dla_transform_general (character, dimension(*) trans, integer m, integer n, double precision, dimension(ldx, *) x, integer ldx, double precision, dimension(ldqa, *) qa, integer ldqa, double precision, dimension(ldqb, *) qb, integer ldqb, double precision, dimension(*) work)

Transform the Right-Hand Side or Solution for generalized projections.

Purpose:

!> DLA_TRANSFORM_STANDARD computes either
!>
!>    X <-  QA*X*QB**T                              (1)
!>
!> or
!>
!>    X <- QA**T*X*QB                               (2)
!>
!> where QA is a M-by-M matrices, QB is a N-by-N matrix, and X is a M-by-N matrix.
!>
Remarks

The function does not perform any check on the input arguments.

Parameters

TRANS

!>          TRANS is CHARACTER(1)
!>          Specifies which transformation is applied:
!>          == 'N':  Transformation (1)
!>          == 'T':  Transformation (2)
!>

M

!>          M is INTEGER
!>          The order of the matrices QA and the number of rows of X.  M >= 0.
!>

N

!>          N is INTEGER
!>          The order of the matrices QB and the number of columns of X.  N >= 0.
!>

X

!>          X is DOUBLE PRECISION array, dimension (LDX,N)
!>          The matrix X is a general M-by-N matrix overwritten by (1) or (2)
!>

LDX

!>          LDX is INTEGER
!>          The leading dimension of the array X.  LDX >= max(1,M).
!>

QA

!>          QA is DOUBLE PRECISION array, dimension (LDQA,M)
!>          The matrix QA is M-by-M the transformation matrix.
!>

LDQA

!>          LDQA is INTEGER
!>          The leading dimension of the array QA.  LDQA >= max(1,M).
!>

QB

!>          QB is DOUBLE PRECISION array, dimension (LDQB,N)
!>          The matrix QB is N-by-N the transformation matrix.
!>

LDQB

!>          LDQB is INTEGER
!>          The leading dimension of the array QB.  LDQB >= max(1,N).
!>

WORK

!>          WORK is DOUBLE PRECISION array, dimension (M*N)
!>          Workspace for the computation.
!>
Author

Martin Koehler, MPI Magdeburg

Date

January 2024

Definition at line 119 of file dla_transform_general.f90.

subroutine dla_transform_standard (character, dimension(*) trans, integer m, double precision, dimension(ldx, *) x, integer ldx, double precision, dimension(ldq, *) q, integer ldq, double precision, dimension(*) work)

Transform the Right-Hand Side or Solution for standard projections.

Purpose:

!> DLA_TRANSFORM_STANDARD computes either
!>
!>    X <-  Q*X*Q**T                              (1)
!>
!> or
!>
!>    X <- Q**T*X*Q                               (2)
!>
!> where Q and X are M-by-M matrices.
!>
Remarks

The function does not perform any check on the input arguments.

Parameters

TRANS

!>          TRANS is CHARACTER(1)
!>          Specifies which transformation is applied:
!>          == 'N':  Transformation (1)
!>          == 'T':  Transformation (2)
!>

M

!>          M is INTEGER
!>          The order of the matrices Q and X.  M >= 0.
!>

X

!>          X is DOUBLE PRECISION array, dimension (LDX,M)
!>          The matrix X is a general M-by-M matrix overwritten by (1) or (2)
!>

LDX

!>          LDX is INTEGER
!>          The leading dimension of the array X.  LDX >= max(1,M).
!>

Q

!>          Q is DOUBLE PRECISION array, dimension (LDQ,M)
!>          The matrix Q is M-by-M the transformation matrix.
!>

LDQ

!>          LDQ is INTEGER
!>          The leading dimension of the array Q.  LDQ >= max(1,M).
!>

WORK

!>          WORK is DOUBLE PRECISION array, dimension (M**2)
!>          Workspace for the computation.
!>
Author

Martin Koehler, MPI Magdeburg

Date

January 2024

Definition at line 101 of file dla_transform_standard.f90.

Author

Generated automatically by Doxygen for MEPACK from the source code.

Info

Fri Oct 25 2024 00:00:00 Version 1.1.1 MEPACK