sgbcon - eral band matrix A, in either the 1-norm or the infinity-norm, using the LU factorization computed by SGBTRF
SUBROUTINE SGBCON(NORM, N, KL, KU, A, LDA, IPIVOT, ANORM, RCOND, WORK, WORK2, INFO) CHARACTER*1 NORM INTEGER N, KL, KU, LDA, INFO INTEGER IPIVOT(*), WORK2(*) REAL ANORM, RCOND REAL A(LDA,*), WORK(*) SUBROUTINE SGBCON_64(NORM, N, KL, KU, A, LDA, IPIVOT, ANORM, RCOND, WORK, WORK2, INFO) CHARACTER*1 NORM INTEGER*8 N, KL, KU, LDA, INFO INTEGER*8 IPIVOT(*), WORK2(*) REAL ANORM, RCOND REAL A(LDA,*), WORK(*) F95 INTERFACE SUBROUTINE GBCON(NORM, N, KL, KU, A, LDA, IPIVOT, ANORM, RCOND, WORK, WORK2, INFO) CHARACTER(LEN=1) :: NORM INTEGER :: N, KL, KU, LDA, INFO INTEGER, DIMENSION(:) :: IPIVOT, WORK2 REAL :: ANORM, RCOND REAL, DIMENSION(:) :: WORK REAL, DIMENSION(:,:) :: A SUBROUTINE GBCON_64(NORM, N, KL, KU, A, LDA, IPIVOT, ANORM, RCOND, WORK, WORK2, INFO) CHARACTER(LEN=1) :: NORM INTEGER(8) :: N, KL, KU, LDA, INFO INTEGER(8), DIMENSION(:) :: IPIVOT, WORK2 REAL :: ANORM, RCOND REAL, DIMENSION(:) :: WORK REAL, DIMENSION(:,:) :: A C INTERFACE #include <sunperf.h> void sgbcon(char norm, int n, int kl, int ku, float *a, int lda, int *ipivot, float anorm, float *rcond, int *info); void sgbcon_64(char norm, long n, long kl, long ku, float *a, long lda, long *ipivot, float anorm, float *rcond, long *info);
Oracle Solaris Studio Performance Library sgbcon(3P)
NAME
sgbcon - estimate the reciprocal of the condition number of a real gen-
eral band matrix A, in either the 1-norm or the infinity-norm, using
the LU factorization computed by SGBTRF
SYNOPSIS
SUBROUTINE SGBCON(NORM, N, KL, KU, A, LDA, IPIVOT, ANORM,
RCOND, WORK, WORK2, INFO)
CHARACTER*1 NORM
INTEGER N, KL, KU, LDA, INFO
INTEGER IPIVOT(*), WORK2(*)
REAL ANORM, RCOND
REAL A(LDA,*), WORK(*)
SUBROUTINE SGBCON_64(NORM, N, KL, KU, A, LDA, IPIVOT, ANORM,
RCOND, WORK, WORK2, INFO)
CHARACTER*1 NORM
INTEGER*8 N, KL, KU, LDA, INFO
INTEGER*8 IPIVOT(*), WORK2(*)
REAL ANORM, RCOND
REAL A(LDA,*), WORK(*)
F95 INTERFACE
SUBROUTINE GBCON(NORM, N, KL, KU, A, LDA, IPIVOT, ANORM,
RCOND, WORK, WORK2, INFO)
CHARACTER(LEN=1) :: NORM
INTEGER :: N, KL, KU, LDA, INFO
INTEGER, DIMENSION(:) :: IPIVOT, WORK2
REAL :: ANORM, RCOND
REAL, DIMENSION(:) :: WORK
REAL, DIMENSION(:,:) :: A
SUBROUTINE GBCON_64(NORM, N, KL, KU, A, LDA, IPIVOT, ANORM,
RCOND, WORK, WORK2, INFO)
CHARACTER(LEN=1) :: NORM
INTEGER(8) :: N, KL, KU, LDA, INFO
INTEGER(8), DIMENSION(:) :: IPIVOT, WORK2
REAL :: ANORM, RCOND
REAL, DIMENSION(:) :: WORK
REAL, DIMENSION(:,:) :: A
C INTERFACE
#include <sunperf.h>
void sgbcon(char norm, int n, int kl, int ku, float *a, int lda, int
*ipivot, float anorm, float *rcond, int *info);
void sgbcon_64(char norm, long n, long kl, long ku, float *a, long lda,
long *ipivot, float anorm, float *rcond, long *info);
PURPOSE
sgbcon estimates the reciprocal of the condition number of a real gen-
eral band matrix A, in either the 1-norm or the infinity-norm, using
the LU factorization computed by SGBTRF.
An estimate is obtained for norm(inv(A)), and the reciprocal of the
condition number is computed as
RCOND = 1 / ( norm(A) * norm(inv(A)) ).
ARGUMENTS
NORM (input)
Specifies whether the 1-norm condition number or the infin-
ity-norm condition number is required:
= '1' or 'O': 1-norm;
= 'I': Infinity-norm.
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.
A (input) 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.
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).
ANORM (input)
If NORM = '1' or 'O', the 1-norm of the original matrix A.
If NORM = 'I', the infinity-norm of the original matrix A.
RCOND (output)
The reciprocal of the condition number of the matrix A, com-
puted as RCOND = 1/(norm(A) * norm(inv(A))).
WORK (workspace)
dimension(3*N)
WORK2 (workspace)
dimension (N)
INFO (output)
= 0: successful exit;
< 0: if INFO = -i, the i-th argument had an illegal value.
7 Nov 2015 sgbcon(3P)