LAPACK 3.3.1
Linear Algebra PACKage

zpbcon.f

Go to the documentation of this file.
00001       SUBROUTINE ZPBCON( UPLO, N, KD, AB, LDAB, ANORM, RCOND, WORK,
00002      $                   RWORK, INFO )
00003 *
00004 *  -- LAPACK routine (version 3.3.1) --
00005 *  -- LAPACK is a software package provided by Univ. of Tennessee,    --
00006 *  -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
00007 *  -- April 2011                                                      --
00008 *
00009 *     Modified to call ZLACN2 in place of ZLACON, 10 Feb 03, SJH.
00010 *
00011 *     .. Scalar Arguments ..
00012       CHARACTER          UPLO
00013       INTEGER            INFO, KD, LDAB, N
00014       DOUBLE PRECISION   ANORM, RCOND
00015 *     ..
00016 *     .. Array Arguments ..
00017       DOUBLE PRECISION   RWORK( * )
00018       COMPLEX*16         AB( LDAB, * ), WORK( * )
00019 *     ..
00020 *
00021 *  Purpose
00022 *  =======
00023 *
00024 *  ZPBCON estimates the reciprocal of the condition number (in the
00025 *  1-norm) of a complex Hermitian positive definite band matrix using
00026 *  the Cholesky factorization A = U**H*U or A = L*L**H computed by
00027 *  ZPBTRF.
00028 *
00029 *  An estimate is obtained for norm(inv(A)), and the reciprocal of the
00030 *  condition number is computed as RCOND = 1 / (ANORM * norm(inv(A))).
00031 *
00032 *  Arguments
00033 *  =========
00034 *
00035 *  UPLO    (input) CHARACTER*1
00036 *          = 'U':  Upper triangular factor stored in AB;
00037 *          = 'L':  Lower triangular factor stored in AB.
00038 *
00039 *  N       (input) INTEGER
00040 *          The order of the matrix A.  N >= 0.
00041 *
00042 *  KD      (input) INTEGER
00043 *          The number of superdiagonals of the matrix A if UPLO = 'U',
00044 *          or the number of sub-diagonals if UPLO = 'L'.  KD >= 0.
00045 *
00046 *  AB      (input) COMPLEX*16 array, dimension (LDAB,N)
00047 *          The triangular factor U or L from the Cholesky factorization
00048 *          A = U**H*U or A = L*L**H of the band matrix A, stored in the
00049 *          first KD+1 rows of the array.  The j-th column of U or L is
00050 *          stored in the j-th column of the array AB as follows:
00051 *          if UPLO ='U', AB(kd+1+i-j,j) = U(i,j) for max(1,j-kd)<=i<=j;
00052 *          if UPLO ='L', AB(1+i-j,j)    = L(i,j) for j<=i<=min(n,j+kd).
00053 *
00054 *  LDAB    (input) INTEGER
00055 *          The leading dimension of the array AB.  LDAB >= KD+1.
00056 *
00057 *  ANORM   (input) DOUBLE PRECISION
00058 *          The 1-norm (or infinity-norm) of the Hermitian band matrix A.
00059 *
00060 *  RCOND   (output) DOUBLE PRECISION
00061 *          The reciprocal of the condition number of the matrix A,
00062 *          computed as RCOND = 1/(ANORM * AINVNM), where AINVNM is an
00063 *          estimate of the 1-norm of inv(A) computed in this routine.
00064 *
00065 *  WORK    (workspace) COMPLEX*16 array, dimension (2*N)
00066 *
00067 *  RWORK   (workspace) DOUBLE PRECISION array, dimension (N)
00068 *
00069 *  INFO    (output) INTEGER
00070 *          = 0:  successful exit
00071 *          < 0:  if INFO = -i, the i-th argument had an illegal value
00072 *
00073 *  =====================================================================
00074 *
00075 *     .. Parameters ..
00076       DOUBLE PRECISION   ONE, ZERO
00077       PARAMETER          ( ONE = 1.0D+0, ZERO = 0.0D+0 )
00078 *     ..
00079 *     .. Local Scalars ..
00080       LOGICAL            UPPER
00081       CHARACTER          NORMIN
00082       INTEGER            IX, KASE
00083       DOUBLE PRECISION   AINVNM, SCALE, SCALEL, SCALEU, SMLNUM
00084       COMPLEX*16         ZDUM
00085 *     ..
00086 *     .. Local Arrays ..
00087       INTEGER            ISAVE( 3 )
00088 *     ..
00089 *     .. External Functions ..
00090       LOGICAL            LSAME
00091       INTEGER            IZAMAX
00092       DOUBLE PRECISION   DLAMCH
00093       EXTERNAL           LSAME, IZAMAX, DLAMCH
00094 *     ..
00095 *     .. External Subroutines ..
00096       EXTERNAL           XERBLA, ZDRSCL, ZLACN2, ZLATBS
00097 *     ..
00098 *     .. Intrinsic Functions ..
00099       INTRINSIC          ABS, DBLE, DIMAG
00100 *     ..
00101 *     .. Statement Functions ..
00102       DOUBLE PRECISION   CABS1
00103 *     ..
00104 *     .. Statement Function definitions ..
00105       CABS1( ZDUM ) = ABS( DBLE( ZDUM ) ) + ABS( DIMAG( ZDUM ) )
00106 *     ..
00107 *     .. Executable Statements ..
00108 *
00109 *     Test the input parameters.
00110 *
00111       INFO = 0
00112       UPPER = LSAME( UPLO, 'U' )
00113       IF( .NOT.UPPER .AND. .NOT.LSAME( UPLO, 'L' ) ) THEN
00114          INFO = -1
00115       ELSE IF( N.LT.0 ) THEN
00116          INFO = -2
00117       ELSE IF( KD.LT.0 ) THEN
00118          INFO = -3
00119       ELSE IF( LDAB.LT.KD+1 ) THEN
00120          INFO = -5
00121       ELSE IF( ANORM.LT.ZERO ) THEN
00122          INFO = -6
00123       END IF
00124       IF( INFO.NE.0 ) THEN
00125          CALL XERBLA( 'ZPBCON', -INFO )
00126          RETURN
00127       END IF
00128 *
00129 *     Quick return if possible
00130 *
00131       RCOND = ZERO
00132       IF( N.EQ.0 ) THEN
00133          RCOND = ONE
00134          RETURN
00135       ELSE IF( ANORM.EQ.ZERO ) THEN
00136          RETURN
00137       END IF
00138 *
00139       SMLNUM = DLAMCH( 'Safe minimum' )
00140 *
00141 *     Estimate the 1-norm of the inverse.
00142 *
00143       KASE = 0
00144       NORMIN = 'N'
00145    10 CONTINUE
00146       CALL ZLACN2( N, WORK( N+1 ), WORK, AINVNM, KASE, ISAVE )
00147       IF( KASE.NE.0 ) THEN
00148          IF( UPPER ) THEN
00149 *
00150 *           Multiply by inv(U**H).
00151 *
00152             CALL ZLATBS( 'Upper', 'Conjugate transpose', 'Non-unit',
00153      $                   NORMIN, N, KD, AB, LDAB, WORK, SCALEL, RWORK,
00154      $                   INFO )
00155             NORMIN = 'Y'
00156 *
00157 *           Multiply by inv(U).
00158 *
00159             CALL ZLATBS( 'Upper', 'No transpose', 'Non-unit', NORMIN, N,
00160      $                   KD, AB, LDAB, WORK, SCALEU, RWORK, INFO )
00161          ELSE
00162 *
00163 *           Multiply by inv(L).
00164 *
00165             CALL ZLATBS( 'Lower', 'No transpose', 'Non-unit', NORMIN, N,
00166      $                   KD, AB, LDAB, WORK, SCALEL, RWORK, INFO )
00167             NORMIN = 'Y'
00168 *
00169 *           Multiply by inv(L**H).
00170 *
00171             CALL ZLATBS( 'Lower', 'Conjugate transpose', 'Non-unit',
00172      $                   NORMIN, N, KD, AB, LDAB, WORK, SCALEU, RWORK,
00173      $                   INFO )
00174          END IF
00175 *
00176 *        Multiply by 1/SCALE if doing so will not cause overflow.
00177 *
00178          SCALE = SCALEL*SCALEU
00179          IF( SCALE.NE.ONE ) THEN
00180             IX = IZAMAX( N, WORK, 1 )
00181             IF( SCALE.LT.CABS1( WORK( IX ) )*SMLNUM .OR. SCALE.EQ.ZERO )
00182      $         GO TO 20
00183             CALL ZDRSCL( N, SCALE, WORK, 1 )
00184          END IF
00185          GO TO 10
00186       END IF
00187 *
00188 *     Compute the estimate of the reciprocal condition number.
00189 *
00190       IF( AINVNM.NE.ZERO )
00191      $   RCOND = ( ONE / AINVNM ) / ANORM
00192 *
00193    20 CONTINUE
00194 *
00195       RETURN
00196 *
00197 *     End of ZPBCON
00198 *
00199       END
 All Files Functions