3 * =========== DOCUMENTATION ===========
5 * Online html documentation available at
6 * http://www.netlib.org/lapack/explore-html/
9 *> Download CPPCON + dependencies
10 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/cppcon.f">
12 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/cppcon.f">
14 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/cppcon.f">
21 * SUBROUTINE CPPCON( UPLO, N, AP, ANORM, RCOND, WORK, RWORK, INFO )
23 * .. Scalar Arguments ..
28 * .. Array Arguments ..
30 * COMPLEX AP( * ), WORK( * )
39 *> CPPCON estimates the reciprocal of the condition number (in the
40 *> 1-norm) of a complex Hermitian positive definite packed matrix using
41 *> the Cholesky factorization A = U**H*U or A = L*L**H computed by
44 *> An estimate is obtained for norm(inv(A)), and the reciprocal of the
45 *> condition number is computed as RCOND = 1 / (ANORM * norm(inv(A))).
53 *> UPLO is CHARACTER*1
54 *> = 'U': Upper triangle of A is stored;
55 *> = 'L': Lower triangle of A is stored.
61 *> The order of the matrix A. N >= 0.
66 *> AP is COMPLEX array, dimension (N*(N+1)/2)
67 *> The triangular factor U or L from the Cholesky factorization
68 *> A = U**H*U or A = L*L**H, packed columnwise in a linear
69 *> array. The j-th column of U or L is stored in the array AP
71 *> if UPLO = 'U', AP(i + (j-1)*j/2) = U(i,j) for 1<=i<=j;
72 *> if UPLO = 'L', AP(i + (j-1)*(2n-j)/2) = L(i,j) for j<=i<=n.
78 *> The 1-norm (or infinity-norm) of the Hermitian matrix A.
84 *> The reciprocal of the condition number of the matrix A,
85 *> computed as RCOND = 1/(ANORM * AINVNM), where AINVNM is an
86 *> estimate of the 1-norm of inv(A) computed in this routine.
91 *> WORK is COMPLEX array, dimension (2*N)
96 *> RWORK is REAL array, dimension (N)
102 *> = 0: successful exit
103 *> < 0: if INFO = -i, the i-th argument had an illegal value
109 *> \author Univ. of Tennessee
110 *> \author Univ. of California Berkeley
111 *> \author Univ. of Colorado Denver
114 *> \date November 2011
116 *> \ingroup complexOTHERcomputational
118 * =====================================================================
119 SUBROUTINE CPPCON( UPLO, N, AP, ANORM, RCOND, WORK, RWORK, INFO )
121 * -- LAPACK computational routine (version 3.4.0) --
122 * -- LAPACK is a software package provided by Univ. of Tennessee, --
123 * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
126 * .. Scalar Arguments ..
131 * .. Array Arguments ..
133 COMPLEX AP( * ), WORK( * )
136 * =====================================================================
140 PARAMETER ( ONE = 1.0E+0, ZERO = 0.0E+0 )
142 * .. Local Scalars ..
146 REAL AINVNM, SCALE, SCALEL, SCALEU, SMLNUM
152 * .. External Functions ..
156 EXTERNAL LSAME, ICAMAX, SLAMCH
158 * .. External Subroutines ..
159 EXTERNAL CLACN2, CLATPS, CSRSCL, XERBLA
161 * .. Intrinsic Functions ..
162 INTRINSIC ABS, AIMAG, REAL
164 * .. Statement Functions ..
167 * .. Statement Function definitions ..
168 CABS1( ZDUM ) = ABS( REAL( ZDUM ) ) + ABS( AIMAG( ZDUM ) )
170 * .. Executable Statements ..
172 * Test the input parameters.
175 UPPER = LSAME( UPLO, 'U' )
176 IF( .NOT.UPPER .AND. .NOT.LSAME( UPLO, 'L' ) ) THEN
178 ELSE IF( N.LT.0 ) THEN
180 ELSE IF( ANORM.LT.ZERO ) THEN
184 CALL XERBLA( 'CPPCON', -INFO )
188 * Quick return if possible
194 ELSE IF( ANORM.EQ.ZERO ) THEN
198 SMLNUM = SLAMCH( 'Safe minimum' )
200 * Estimate the 1-norm of the inverse.
205 CALL CLACN2( N, WORK( N+1 ), WORK, AINVNM, KASE, ISAVE )
209 * Multiply by inv(U**H).
211 CALL CLATPS( 'Upper', 'Conjugate transpose', 'Non-unit',
212 $ NORMIN, N, AP, WORK, SCALEL, RWORK, INFO )
215 * Multiply by inv(U).
217 CALL CLATPS( 'Upper', 'No transpose', 'Non-unit', NORMIN, N,
218 $ AP, WORK, SCALEU, RWORK, INFO )
221 * Multiply by inv(L).
223 CALL CLATPS( 'Lower', 'No transpose', 'Non-unit', NORMIN, N,
224 $ AP, WORK, SCALEL, RWORK, INFO )
227 * Multiply by inv(L**H).
229 CALL CLATPS( 'Lower', 'Conjugate transpose', 'Non-unit',
230 $ NORMIN, N, AP, WORK, SCALEU, RWORK, INFO )
233 * Multiply by 1/SCALE if doing so will not cause overflow.
235 SCALE = SCALEL*SCALEU
236 IF( SCALE.NE.ONE ) THEN
237 IX = ICAMAX( N, WORK, 1 )
238 IF( SCALE.LT.CABS1( WORK( IX ) )*SMLNUM .OR. SCALE.EQ.ZERO )
240 CALL CSRSCL( N, SCALE, WORK, 1 )
245 * Compute the estimate of the reciprocal condition number.
248 $ RCOND = ( ONE / AINVNM ) / ANORM