LAPACK 3.3.1
Linear Algebra PACKage

stbcon.f

Go to the documentation of this file.
00001       SUBROUTINE STBCON( NORM, UPLO, DIAG, N, KD, AB, LDAB, RCOND, WORK,
00002      $                   IWORK, 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 SLACN2 in place of SLACON, 7 Feb 03, SJH.
00010 *
00011 *     .. Scalar Arguments ..
00012       CHARACTER          DIAG, NORM, UPLO
00013       INTEGER            INFO, KD, LDAB, N
00014       REAL               RCOND
00015 *     ..
00016 *     .. Array Arguments ..
00017       INTEGER            IWORK( * )
00018       REAL               AB( LDAB, * ), WORK( * )
00019 *     ..
00020 *
00021 *  Purpose
00022 *  =======
00023 *
00024 *  STBCON estimates the reciprocal of the condition number of a
00025 *  triangular band 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 *  KD      (input) INTEGER
00053 *          The number of superdiagonals or subdiagonals of the
00054 *          triangular band matrix A.  KD >= 0.
00055 *
00056 *  AB      (input) REAL array, dimension (LDAB,N)
00057 *          The upper or lower triangular band matrix A, stored in the
00058 *          first kd+1 rows of the array. The j-th column of A is stored
00059 *          in the j-th column of the array AB as follows:
00060 *          if UPLO = 'U', AB(kd+1+i-j,j) = A(i,j) for max(1,j-kd)<=i<=j;
00061 *          if UPLO = 'L', AB(1+i-j,j)    = A(i,j) for j<=i<=min(n,j+kd).
00062 *          If DIAG = 'U', the diagonal elements of A are not referenced
00063 *          and are assumed to be 1.
00064 *
00065 *  LDAB    (input) INTEGER
00066 *          The leading dimension of the array AB.  LDAB >= KD+1.
00067 *
00068 *  RCOND   (output) REAL
00069 *          The reciprocal of the condition number of the matrix A,
00070 *          computed as RCOND = 1/(norm(A) * norm(inv(A))).
00071 *
00072 *  WORK    (workspace) REAL array, dimension (3*N)
00073 *
00074 *  IWORK   (workspace) INTEGER array, dimension (N)
00075 *
00076 *  INFO    (output) INTEGER
00077 *          = 0:  successful exit
00078 *          < 0:  if INFO = -i, the i-th argument had an illegal value
00079 *
00080 *  =====================================================================
00081 *
00082 *     .. Parameters ..
00083       REAL               ONE, ZERO
00084       PARAMETER          ( ONE = 1.0E+0, ZERO = 0.0E+0 )
00085 *     ..
00086 *     .. Local Scalars ..
00087       LOGICAL            NOUNIT, ONENRM, UPPER
00088       CHARACTER          NORMIN
00089       INTEGER            IX, KASE, KASE1
00090       REAL               AINVNM, ANORM, SCALE, SMLNUM, XNORM
00091 *     ..
00092 *     .. Local Arrays ..
00093       INTEGER            ISAVE( 3 )
00094 *     ..
00095 *     .. External Functions ..
00096       LOGICAL            LSAME
00097       INTEGER            ISAMAX
00098       REAL               SLAMCH, SLANTB
00099       EXTERNAL           LSAME, ISAMAX, SLAMCH, SLANTB
00100 *     ..
00101 *     .. External Subroutines ..
00102       EXTERNAL           SLACN2, SLATBS, SRSCL, XERBLA
00103 *     ..
00104 *     .. Intrinsic Functions ..
00105       INTRINSIC          ABS, MAX, REAL
00106 *     ..
00107 *     .. Executable Statements ..
00108 *
00109 *     Test the input parameters.
00110 *
00111       INFO = 0
00112       UPPER = LSAME( UPLO, 'U' )
00113       ONENRM = NORM.EQ.'1' .OR. LSAME( NORM, 'O' )
00114       NOUNIT = LSAME( DIAG, 'N' )
00115 *
00116       IF( .NOT.ONENRM .AND. .NOT.LSAME( NORM, 'I' ) ) THEN
00117          INFO = -1
00118       ELSE IF( .NOT.UPPER .AND. .NOT.LSAME( UPLO, 'L' ) ) THEN
00119          INFO = -2
00120       ELSE IF( .NOT.NOUNIT .AND. .NOT.LSAME( DIAG, 'U' ) ) THEN
00121          INFO = -3
00122       ELSE IF( N.LT.0 ) THEN
00123          INFO = -4
00124       ELSE IF( KD.LT.0 ) THEN
00125          INFO = -5
00126       ELSE IF( LDAB.LT.KD+1 ) THEN
00127          INFO = -7
00128       END IF
00129       IF( INFO.NE.0 ) THEN
00130          CALL XERBLA( 'STBCON', -INFO )
00131          RETURN
00132       END IF
00133 *
00134 *     Quick return if possible
00135 *
00136       IF( N.EQ.0 ) THEN
00137          RCOND = ONE
00138          RETURN
00139       END IF
00140 *
00141       RCOND = ZERO
00142       SMLNUM = SLAMCH( 'Safe minimum' )*REAL( MAX( 1, N ) )
00143 *
00144 *     Compute the norm of the triangular matrix A.
00145 *
00146       ANORM = SLANTB( NORM, UPLO, DIAG, N, KD, AB, LDAB, WORK )
00147 *
00148 *     Continue only if ANORM > 0.
00149 *
00150       IF( ANORM.GT.ZERO ) THEN
00151 *
00152 *        Estimate the norm of the inverse of A.
00153 *
00154          AINVNM = ZERO
00155          NORMIN = 'N'
00156          IF( ONENRM ) THEN
00157             KASE1 = 1
00158          ELSE
00159             KASE1 = 2
00160          END IF
00161          KASE = 0
00162    10    CONTINUE
00163          CALL SLACN2( N, WORK( N+1 ), WORK, IWORK, AINVNM, KASE, ISAVE )
00164          IF( KASE.NE.0 ) THEN
00165             IF( KASE.EQ.KASE1 ) THEN
00166 *
00167 *              Multiply by inv(A).
00168 *
00169                CALL SLATBS( UPLO, 'No transpose', DIAG, NORMIN, N, KD,
00170      $                      AB, LDAB, WORK, SCALE, WORK( 2*N+1 ), INFO )
00171             ELSE
00172 *
00173 *              Multiply by inv(A**T).
00174 *
00175                CALL SLATBS( UPLO, 'Transpose', DIAG, NORMIN, N, KD, AB,
00176      $                      LDAB, WORK, SCALE, WORK( 2*N+1 ), INFO )
00177             END IF
00178             NORMIN = 'Y'
00179 *
00180 *           Multiply by 1/SCALE if doing so will not cause overflow.
00181 *
00182             IF( SCALE.NE.ONE ) THEN
00183                IX = ISAMAX( N, WORK, 1 )
00184                XNORM = ABS( WORK( IX ) )
00185                IF( SCALE.LT.XNORM*SMLNUM .OR. SCALE.EQ.ZERO )
00186      $            GO TO 20
00187                CALL SRSCL( N, SCALE, WORK, 1 )
00188             END IF
00189             GO TO 10
00190          END IF
00191 *
00192 *        Compute the estimate of the reciprocal condition number.
00193 *
00194          IF( AINVNM.NE.ZERO )
00195      $      RCOND = ( ONE / ANORM ) / AINVNM
00196       END IF
00197 *
00198    20 CONTINUE
00199       RETURN
00200 *
00201 *     End of STBCON
00202 *
00203       END
 All Files Functions