LAPACK 3.3.1
Linear Algebra PACKage

ctrcon.f

Go to the documentation of this file.
00001       SUBROUTINE CTRCON( NORM, UPLO, DIAG, N, A, LDA, RCOND, WORK,
00002      $                   RWORK, INFO )
00003 *
00004 *  -- LAPACK routine (version 3.2) --
00005 *  -- LAPACK is a software package provided by Univ. of Tennessee,    --
00006 *  -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
00007 *     November 2006
00008 *
00009 *     Modified to call CLACN2 in place of CLACON, 10 Feb 03, SJH.
00010 *
00011 *     .. Scalar Arguments ..
00012       CHARACTER          DIAG, NORM, UPLO
00013       INTEGER            INFO, LDA, N
00014       REAL               RCOND
00015 *     ..
00016 *     .. Array Arguments ..
00017       REAL               RWORK( * )
00018       COMPLEX            A( LDA, * ), WORK( * )
00019 *     ..
00020 *
00021 *  Purpose
00022 *  =======
00023 *
00024 *  CTRCON estimates the reciprocal of the condition number of a
00025 *  triangular matrix A, in either the 1-norm or the infinity-norm.
00026 *
00027 *  The norm of A is computed and an estimate is obtained for
00028 *  norm(inv(A)), then the reciprocal of the condition number is
00029 *  computed as
00030 *     RCOND = 1 / ( norm(A) * norm(inv(A)) ).
00031 *
00032 *  Arguments
00033 *  =========
00034 *
00035 *  NORM    (input) CHARACTER*1
00036 *          Specifies whether the 1-norm condition number or the
00037 *          infinity-norm condition number is required:
00038 *          = '1' or 'O':  1-norm;
00039 *          = 'I':         Infinity-norm.
00040 *
00041 *  UPLO    (input) CHARACTER*1
00042 *          = 'U':  A is upper triangular;
00043 *          = 'L':  A is lower triangular.
00044 *
00045 *  DIAG    (input) CHARACTER*1
00046 *          = 'N':  A is non-unit triangular;
00047 *          = 'U':  A is unit triangular.
00048 *
00049 *  N       (input) INTEGER
00050 *          The order of the matrix A.  N >= 0.
00051 *
00052 *  A       (input) COMPLEX array, dimension (LDA,N)
00053 *          The triangular matrix A.  If UPLO = 'U', the leading N-by-N
00054 *          upper triangular part of the array A contains the upper
00055 *          triangular matrix, and the strictly lower triangular part of
00056 *          A is not referenced.  If UPLO = 'L', the leading N-by-N lower
00057 *          triangular part of the array A contains the lower triangular
00058 *          matrix, and the strictly upper triangular part of A is not
00059 *          referenced.  If DIAG = 'U', the diagonal elements of A are
00060 *          also not referenced and are assumed to be 1.
00061 *
00062 *  LDA     (input) INTEGER
00063 *          The leading dimension of the array A.  LDA >= max(1,N).
00064 *
00065 *  RCOND   (output) REAL
00066 *          The reciprocal of the condition number of the matrix A,
00067 *          computed as RCOND = 1/(norm(A) * norm(inv(A))).
00068 *
00069 *  WORK    (workspace) COMPLEX array, dimension (2*N)
00070 *
00071 *  RWORK   (workspace) REAL array, dimension (N)
00072 *
00073 *  INFO    (output) INTEGER
00074 *          = 0:  successful exit
00075 *          < 0:  if INFO = -i, the i-th argument had an illegal value
00076 *
00077 *  =====================================================================
00078 *
00079 *     .. Parameters ..
00080       REAL               ONE, ZERO
00081       PARAMETER          ( ONE = 1.0E+0, ZERO = 0.0E+0 )
00082 *     ..
00083 *     .. Local Scalars ..
00084       LOGICAL            NOUNIT, ONENRM, UPPER
00085       CHARACTER          NORMIN
00086       INTEGER            IX, KASE, KASE1
00087       REAL               AINVNM, ANORM, SCALE, SMLNUM, XNORM
00088       COMPLEX            ZDUM
00089 *     ..
00090 *     .. Local Arrays ..
00091       INTEGER            ISAVE( 3 )
00092 *     ..
00093 *     .. External Functions ..
00094       LOGICAL            LSAME
00095       INTEGER            ICAMAX
00096       REAL               CLANTR, SLAMCH
00097       EXTERNAL           LSAME, ICAMAX, CLANTR, SLAMCH
00098 *     ..
00099 *     .. External Subroutines ..
00100       EXTERNAL           CLACN2, CLATRS, CSRSCL, XERBLA
00101 *     ..
00102 *     .. Intrinsic Functions ..
00103       INTRINSIC          ABS, AIMAG, MAX, REAL
00104 *     ..
00105 *     .. Statement Functions ..
00106       REAL               CABS1
00107 *     ..
00108 *     .. Statement Function definitions ..
00109       CABS1( ZDUM ) = ABS( REAL( ZDUM ) ) + ABS( AIMAG( ZDUM ) )
00110 *     ..
00111 *     .. Executable Statements ..
00112 *
00113 *     Test the input parameters.
00114 *
00115       INFO = 0
00116       UPPER = LSAME( UPLO, 'U' )
00117       ONENRM = NORM.EQ.'1' .OR. LSAME( NORM, 'O' )
00118       NOUNIT = LSAME( DIAG, 'N' )
00119 *
00120       IF( .NOT.ONENRM .AND. .NOT.LSAME( NORM, 'I' ) ) THEN
00121          INFO = -1
00122       ELSE IF( .NOT.UPPER .AND. .NOT.LSAME( UPLO, 'L' ) ) THEN
00123          INFO = -2
00124       ELSE IF( .NOT.NOUNIT .AND. .NOT.LSAME( DIAG, 'U' ) ) THEN
00125          INFO = -3
00126       ELSE IF( N.LT.0 ) THEN
00127          INFO = -4
00128       ELSE IF( LDA.LT.MAX( 1, N ) ) THEN
00129          INFO = -6
00130       END IF
00131       IF( INFO.NE.0 ) THEN
00132          CALL XERBLA( 'CTRCON', -INFO )
00133          RETURN
00134       END IF
00135 *
00136 *     Quick return if possible
00137 *
00138       IF( N.EQ.0 ) THEN
00139          RCOND = ONE
00140          RETURN
00141       END IF
00142 *
00143       RCOND = ZERO
00144       SMLNUM = SLAMCH( 'Safe minimum' )*REAL( MAX( 1, N ) )
00145 *
00146 *     Compute the norm of the triangular matrix A.
00147 *
00148       ANORM = CLANTR( NORM, UPLO, DIAG, N, N, A, LDA, RWORK )
00149 *
00150 *     Continue only if ANORM > 0.
00151 *
00152       IF( ANORM.GT.ZERO ) THEN
00153 *
00154 *        Estimate the norm of the inverse of A.
00155 *
00156          AINVNM = ZERO
00157          NORMIN = 'N'
00158          IF( ONENRM ) THEN
00159             KASE1 = 1
00160          ELSE
00161             KASE1 = 2
00162          END IF
00163          KASE = 0
00164    10    CONTINUE
00165          CALL CLACN2( N, WORK( N+1 ), WORK, AINVNM, KASE, ISAVE )
00166          IF( KASE.NE.0 ) THEN
00167             IF( KASE.EQ.KASE1 ) THEN
00168 *
00169 *              Multiply by inv(A).
00170 *
00171                CALL CLATRS( UPLO, 'No transpose', DIAG, NORMIN, N, A,
00172      $                      LDA, WORK, SCALE, RWORK, INFO )
00173             ELSE
00174 *
00175 *              Multiply by inv(A**H).
00176 *
00177                CALL CLATRS( UPLO, 'Conjugate transpose', DIAG, NORMIN,
00178      $                      N, A, LDA, WORK, SCALE, RWORK, INFO )
00179             END IF
00180             NORMIN = 'Y'
00181 *
00182 *           Multiply by 1/SCALE if doing so will not cause overflow.
00183 *
00184             IF( SCALE.NE.ONE ) THEN
00185                IX = ICAMAX( N, WORK, 1 )
00186                XNORM = CABS1( WORK( IX ) )
00187                IF( SCALE.LT.XNORM*SMLNUM .OR. SCALE.EQ.ZERO )
00188      $            GO TO 20
00189                CALL CSRSCL( N, SCALE, WORK, 1 )
00190             END IF
00191             GO TO 10
00192          END IF
00193 *
00194 *        Compute the estimate of the reciprocal condition number.
00195 *
00196          IF( AINVNM.NE.ZERO )
00197      $      RCOND = ( ONE / ANORM ) / AINVNM
00198       END IF
00199 *
00200    20 CONTINUE
00201       RETURN
00202 *
00203 *     End of CTRCON
00204 *
00205       END
 All Files Functions