dgbtrs - eral band matrix A using the LU factorization computed by DGBTRF
SUBROUTINE DGBTRS(TRANSA, N, KL, KU, NRHS, A, LDA, IPIVOT, B, LDB, INFO) CHARACTER*1 TRANSA INTEGER N, KL, KU, NRHS, LDA, LDB, INFO INTEGER IPIVOT(*) DOUBLE PRECISION A(LDA,*), B(LDB,*) SUBROUTINE DGBTRS_64(TRANSA, N, KL, KU, NRHS, A, LDA, IPIVOT, B, LDB, INFO) CHARACTER*1 TRANSA INTEGER*8 N, KL, KU, NRHS, LDA, LDB, INFO INTEGER*8 IPIVOT(*) DOUBLE PRECISION A(LDA,*), B(LDB,*) F95 INTERFACE SUBROUTINE GBTRS(TRANSA, N, KL, KU, NRHS, A, LDA, IPIVOT, B, LDB, INFO) CHARACTER(LEN=1) :: TRANSA INTEGER :: N, KL, KU, NRHS, LDA, LDB, INFO INTEGER, DIMENSION(:) :: IPIVOT REAL(8), DIMENSION(:,:) :: A, B SUBROUTINE GBTRS_64(TRANSA, N, KL, KU, NRHS, A, LDA, IPIVOT, B, LDB, INFO) CHARACTER(LEN=1) :: TRANSA INTEGER(8) :: N, KL, KU, NRHS, LDA, LDB, INFO INTEGER(8), DIMENSION(:) :: IPIVOT REAL(8), DIMENSION(:,:) :: A, B C INTERFACE #include <sunperf.h> void dgbtrs(char transa, int n, int kl, int ku, int nrhs, double *a, int lda, int *ipivot, double *b, int ldb, int *info); void dgbtrs_64(char transa, long n, long kl, long ku, long nrhs, double *a, long lda, long *ipivot, double *b, long ldb, long *info);
Oracle Solaris Studio Performance Library dgbtrs(3P)
NAME
dgbtrs - solve a system of linear equations A*X=B or A'*X=B with a gen-
eral band matrix A using the LU factorization computed by DGBTRF
SYNOPSIS
SUBROUTINE DGBTRS(TRANSA, N, KL, KU, NRHS, A, LDA, IPIVOT, B,
LDB, INFO)
CHARACTER*1 TRANSA
INTEGER N, KL, KU, NRHS, LDA, LDB, INFO
INTEGER IPIVOT(*)
DOUBLE PRECISION A(LDA,*), B(LDB,*)
SUBROUTINE DGBTRS_64(TRANSA, N, KL, KU, NRHS, A, LDA, IPIVOT,
B, LDB, INFO)
CHARACTER*1 TRANSA
INTEGER*8 N, KL, KU, NRHS, LDA, LDB, INFO
INTEGER*8 IPIVOT(*)
DOUBLE PRECISION A(LDA,*), B(LDB,*)
F95 INTERFACE
SUBROUTINE GBTRS(TRANSA, N, KL, KU, NRHS, A, LDA,
IPIVOT, B, LDB, INFO)
CHARACTER(LEN=1) :: TRANSA
INTEGER :: N, KL, KU, NRHS, LDA, LDB, INFO
INTEGER, DIMENSION(:) :: IPIVOT
REAL(8), DIMENSION(:,:) :: A, B
SUBROUTINE GBTRS_64(TRANSA, N, KL, KU, NRHS, A, LDA,
IPIVOT, B, LDB, INFO)
CHARACTER(LEN=1) :: TRANSA
INTEGER(8) :: N, KL, KU, NRHS, LDA, LDB, INFO
INTEGER(8), DIMENSION(:) :: IPIVOT
REAL(8), DIMENSION(:,:) :: A, B
C INTERFACE
#include <sunperf.h>
void dgbtrs(char transa, int n, int kl, int ku, int nrhs, double *a,
int lda, int *ipivot, double *b, int ldb, int *info);
void dgbtrs_64(char transa, long n, long kl, long ku, long nrhs, double
*a, long lda, long *ipivot, double *b, long ldb, long *info);
PURPOSE
dgbtrs solves a system of linear equations
A * X = B or A' * X = B with a general band matrix A using the LU
factorization computed by DGBTRF.
ARGUMENTS
TRANSA (input)
Specifies the form of the system of equations. = 'N': A * X
= B (No transpose)
= 'T': A'* X = B (Transpose)
= 'C': A'* X = B (Conjugate transpose = Transpose)
N (input) The order of the matrix A. N >= 0.
KL (input)
The number of subdiagonals within the band of A. KL >= 0.
KU (input)
The number of superdiagonals within the band of A. KU >= 0.
NRHS (input)
The number of right hand sides, i.e., the number of columns
of the matrix B. NRHS >= 0.
A (input) Details of the LU factorization of the band matrix A, as com-
puted by DGBTRF. U is stored as an upper triangular band
matrix with KL+KU superdiagonals in rows 1 to KL+KU+1, and
the multipliers used during the factorization are stored in
rows KL+KU+2 to 2*KL+KU+1.
LDA (input)
The leading dimension of the array A. LDA >= 2*KL+KU+1.
IPIVOT (input)
The pivot indices; for 1 <= i <= N, row i of the matrix was
interchanged with row IPIVOT(i).
B (input/output)
On entry, the right hand side matrix B. On exit, the solu-
tion matrix X.
LDB (input)
The leading dimension of the array B. LDB >= max(1,N).
INFO (output)
= 0: successful exit
< 0: if INFO = -i, the i-th argument had an illegal value
7 Nov 2015 dgbtrs(3P)