sla_gbrcond - estimate the Skeel condition number for a general banded matrix
REAL FUNCTION SLA_GBRCOND(TRANS, N, KL, KU, AB, LDAB, AFB, LDAFB, IPIV, CMODE, C, INFO, WORK, IWORK) CHARACTER*1 TRANS INTEGER N, LDAB, LDAFB, INFO, KL, KU, CMODE INTEGER IWORK(*), IPIV(*) REAL AB(LDAB,*), AFB(LDAFB,*), WORK(*), C(*) REAL FUNCTION SLA_GBRCOND_64(TRANS, N, KL, KU, AB, LDAB, AFB, LDAFB, IPIV, CMODE, C, INFO, WORK, IWORK) CHARACTER*1 TRANS INTEGER*8 N, LDAB, LDAFB, INFO, KL, KU, CMODE INTEGER*8 IWORK(*), IPIV(*) REAL AB(LDAB,*), AFB(LDAFB,*), WORK(*), C(*) F95 INTERFACE REAL FUNCTION LA_GBRCOND(TRANS, N, KL, KU, AB, LDAB, AFB, LDAFB, IPIV, CMODE, C, INFO, WORK, IWORK) REAL, DIMENSION(:,:) :: AB, AFB INTEGER :: N, KL, KU, LDAB, LDAFB, CMODE, INFO CHARACTER(LEN=1) :: TRANS INTEGER, DIMENSION(:) :: IPIV, IWORK REAL, DIMENSION(:) :: C, WORK REAL FUNCTION LA_GBRCOND_64(TRANS, N, KL, KU, AB, LDAB, AFB, LDAFB, IPIV, CMODE, C, INFO, WORK, IWORK) REAL, DIMENSION(:,:) :: AB, AFB INTEGER(8) :: N, KL, KU, LDAB, LDAFB, CMODE, INFO CHARACTER(LEN=1) :: TRANS INTEGER(8), DIMENSION(:) :: IPIV, IWORK REAL, DIMENSION(:) :: C, WORK C INTERFACE #include <sunperf.h> float sla_gbrcond (char trans, int n, int kl, int ku, float *ab, int ldab, float *afb, int ldafb, int *ipiv, int cmode, float *c, int *info); float sla_gbrcond_64 (char trans, long n, long kl, long ku, float *ab, long ldab, float * afb, long ldafb, long *ipiv, long cmode, float *c, long *info);
Oracle Solaris Studio Performance Library sla_gbrcond(3P)
NAME
sla_gbrcond - estimate the Skeel condition number for a general banded
matrix
SYNOPSIS
REAL FUNCTION SLA_GBRCOND(TRANS, N, KL, KU, AB, LDAB, AFB, LDAFB, IPIV,
CMODE, C, INFO, WORK, IWORK)
CHARACTER*1 TRANS
INTEGER N, LDAB, LDAFB, INFO, KL, KU, CMODE
INTEGER IWORK(*), IPIV(*)
REAL AB(LDAB,*), AFB(LDAFB,*), WORK(*), C(*)
REAL FUNCTION SLA_GBRCOND_64(TRANS, N, KL, KU, AB, LDAB, AFB, LDAFB,
IPIV, CMODE, C, INFO, WORK, IWORK)
CHARACTER*1 TRANS
INTEGER*8 N, LDAB, LDAFB, INFO, KL, KU, CMODE
INTEGER*8 IWORK(*), IPIV(*)
REAL AB(LDAB,*), AFB(LDAFB,*), WORK(*), C(*)
F95 INTERFACE
REAL FUNCTION LA_GBRCOND(TRANS, N, KL, KU, AB, LDAB, AFB, LDAFB, IPIV,
CMODE, C, INFO, WORK, IWORK)
REAL, DIMENSION(:,:) :: AB, AFB
INTEGER :: N, KL, KU, LDAB, LDAFB, CMODE, INFO
CHARACTER(LEN=1) :: TRANS
INTEGER, DIMENSION(:) :: IPIV, IWORK
REAL, DIMENSION(:) :: C, WORK
REAL FUNCTION LA_GBRCOND_64(TRANS, N, KL, KU, AB, LDAB, AFB, LDAFB,
IPIV, CMODE, C, INFO, WORK, IWORK)
REAL, DIMENSION(:,:) :: AB, AFB
INTEGER(8) :: N, KL, KU, LDAB, LDAFB, CMODE, INFO
CHARACTER(LEN=1) :: TRANS
INTEGER(8), DIMENSION(:) :: IPIV, IWORK
REAL, DIMENSION(:) :: C, WORK
C INTERFACE
#include <sunperf.h>
float sla_gbrcond (char trans, int n, int kl, int ku, float *ab, int
ldab, float *afb, int ldafb, int *ipiv, int cmode, float *c,
int *info);
float sla_gbrcond_64 (char trans, long n, long kl, long ku, float *ab,
long ldab, float * afb, long ldafb, long *ipiv, long cmode,
float *c, long *info);
PURPOSE
sla_gbrcond Estimates the Skeel condition number of op(A) * op2(C)
where op2 is determined by CMODE as follows:
CMODE = 1 op2(C) = C
CMODE = 0 op2(C) = I
CMODE = -1 op2(C) = inv(C)
The Skeel condition number cond(A)=norminf(|inv(A)||A|) is computed by
computing scaling factors R such that diag(R)*A*op2(C) is row equili-
brated and computing the standard infinity-norm condition number.
ARGUMENTS
TRANS (input)
TRANS is CHARACTER*1
Specifies the form of the system of equations:
= 'N': A * X = B (No transpose)
= 'T': A**T * X = B (Transpose)
= 'C': A**H * X = B (Conjugate Transpose = Transpose)
N (input)
N is INTEGER
The number of linear equations, i.e., the order of the matrix
A. N >= 0.
KL (input)
KL is INTEGER
The number of subdiagonals within the band of A. KL >= 0.
KU (input)
KU is INTEGER
The number of superdiagonals within the band of A. KU >= 0.
AB (input)
AB is REAL array, dimension (LDAB,N)
On entry, the matrix A in band storage, in rows 1 to KL+KU+1.
The j-th column of A is stored in the j-th column of the
array AB as follows:
AB(KU+1+i-j,j) = A(i,j)
for max(1,j-KU)<=i<=min(N,j+kl)
LDAB (input)
LDAB is INTEGER
The leading dimension of the array AB.
LDAB >= KL+KU+1.
AFB (input)
AFB is REAL array, dimension (LDAFB,N)
Details of the LU factorization of the band matrix A, as com-
puted by SGBTRF. 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.
LDAFB (input)
LDAFB is INTEGER
The leading dimension of the array AFB.
LDAFB >= 2*KL+KU+1.
IPIV (input)
IPIV is INTEGER array, dimension (N)
The pivot indices from the factorization A=P*L*U as computed
by SGBTRF; row i of the matrix was interchanged with row
IPIV(i).
CMODE (input)
CMODE is INTEGER
Determines op2(C) in the formula op(A)*op2(C) as follows:
CMODE = 1 op2(C) = C
CMODE = 0 op2(C) = I
CMODE = -1 op2(C) = inv(C)
C (input)
C is REAL array, dimension (N)
The vector C in the formula op(A) * op2(C).
INFO (output)
INFO is INTEGER
= 0: Successful exit.
i > 0: The ith argument is invalid.
WORK (input)
WORK is REAL array, dimension (5*N).
Workspace.
IWORK (input)
IWORK is INTEGER array, dimension (N).
Workspace.
7 Nov 2015 sla_gbrcond(3P)