ctrcon - lar matrix A, in either the 1-norm or the infinity-norm
SUBROUTINE CTRCON(NORM, UPLO, DIAG, N, A, LDA, RCOND, WORK, WORK2, INFO) CHARACTER*1 NORM, UPLO, DIAG COMPLEX A(LDA,*), WORK(*) INTEGER N, LDA, INFO REAL RCOND REAL WORK2(*) SUBROUTINE CTRCON_64(NORM, UPLO, DIAG, N, A, LDA, RCOND, WORK, WORK2, INFO) CHARACTER*1 NORM, UPLO, DIAG COMPLEX A(LDA,*), WORK(*) INTEGER*8 N, LDA, INFO REAL RCOND REAL WORK2(*) F95 INTERFACE SUBROUTINE TRCON(NORM, UPLO, DIAG, N, A, LDA, RCOND, WORK, WORK2, INFO) CHARACTER(LEN=1) :: NORM, UPLO, DIAG COMPLEX, DIMENSION(:) :: WORK COMPLEX, DIMENSION(:,:) :: A INTEGER :: N, LDA, INFO REAL :: RCOND REAL, DIMENSION(:) :: WORK2 SUBROUTINE TRCON_64(NORM, UPLO, DIAG, N, A, LDA, RCOND, WORK, WORK2, INFO) CHARACTER(LEN=1) :: NORM, UPLO, DIAG COMPLEX, DIMENSION(:) :: WORK COMPLEX, DIMENSION(:,:) :: A INTEGER(8) :: N, LDA, INFO REAL :: RCOND REAL, DIMENSION(:) :: WORK2 C INTERFACE #include <sunperf.h> void ctrcon(char norm, char uplo, char diag, int n, complex *a, int lda, float *rcond, int *info); void ctrcon_64(char norm, char uplo, char diag, long n, complex *a, long lda, float *rcond, long *info);
Oracle Solaris Studio Performance Library ctrcon(3P)
NAME
ctrcon - estimate the reciprocal of the condition number of a triangu-
lar matrix A, in either the 1-norm or the infinity-norm
SYNOPSIS
SUBROUTINE CTRCON(NORM, UPLO, DIAG, N, A, LDA, RCOND, WORK, WORK2,
INFO)
CHARACTER*1 NORM, UPLO, DIAG
COMPLEX A(LDA,*), WORK(*)
INTEGER N, LDA, INFO
REAL RCOND
REAL WORK2(*)
SUBROUTINE CTRCON_64(NORM, UPLO, DIAG, N, A, LDA, RCOND, WORK, WORK2,
INFO)
CHARACTER*1 NORM, UPLO, DIAG
COMPLEX A(LDA,*), WORK(*)
INTEGER*8 N, LDA, INFO
REAL RCOND
REAL WORK2(*)
F95 INTERFACE
SUBROUTINE TRCON(NORM, UPLO, DIAG, N, A, LDA, RCOND, WORK,
WORK2, INFO)
CHARACTER(LEN=1) :: NORM, UPLO, DIAG
COMPLEX, DIMENSION(:) :: WORK
COMPLEX, DIMENSION(:,:) :: A
INTEGER :: N, LDA, INFO
REAL :: RCOND
REAL, DIMENSION(:) :: WORK2
SUBROUTINE TRCON_64(NORM, UPLO, DIAG, N, A, LDA, RCOND, WORK,
WORK2, INFO)
CHARACTER(LEN=1) :: NORM, UPLO, DIAG
COMPLEX, DIMENSION(:) :: WORK
COMPLEX, DIMENSION(:,:) :: A
INTEGER(8) :: N, LDA, INFO
REAL :: RCOND
REAL, DIMENSION(:) :: WORK2
C INTERFACE
#include <sunperf.h>
void ctrcon(char norm, char uplo, char diag, int n, complex *a, int
lda, float *rcond, int *info);
void ctrcon_64(char norm, char uplo, char diag, long n, complex *a,
long lda, float *rcond, long *info);
PURPOSE
ctrcon estimates the reciprocal of the condition number of a triangular
matrix A, in either the 1-norm or the infinity-norm.
The norm of A is computed and an estimate is obtained for norm(inv(A)),
then 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.
UPLO (input)
= 'U': A is upper triangular;
= 'L': A is lower triangular.
DIAG (input)
= 'N': A is non-unit triangular;
= 'U': A is unit triangular.
N (input) The order of the matrix A. N >= 0.
A (input) The triangular matrix A. If UPLO = 'U', the leading N-by-N
upper triangular part of the array A contains the upper tri-
angular matrix, and the strictly lower triangular part of A
is not referenced. If UPLO = 'L', the leading N-by-N lower
triangular part of the array A contains the lower triangular
matrix, and the strictly upper triangular part of A is not
referenced. If DIAG = 'U', the diagonal elements of A are
also not referenced and are assumed to be 1.
LDA (input)
The leading dimension of the array A. LDA >= max(1,N).
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(2*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 ctrcon(3P)