Annotation of rpl/lapack/lapack/ztpcon.f, revision 1.15
1.9 bertrand 1: *> \brief \b ZTPCON
2: *
3: * =========== DOCUMENTATION ===========
4: *
1.15 ! bertrand 5: * Online html documentation available at
! 6: * http://www.netlib.org/lapack/explore-html/
1.9 bertrand 7: *
8: *> \htmlonly
1.15 ! bertrand 9: *> Download ZTPCON + dependencies
! 10: *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/ztpcon.f">
! 11: *> [TGZ]</a>
! 12: *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/ztpcon.f">
! 13: *> [ZIP]</a>
! 14: *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/ztpcon.f">
1.9 bertrand 15: *> [TXT]</a>
1.15 ! bertrand 16: *> \endhtmlonly
1.9 bertrand 17: *
18: * Definition:
19: * ===========
20: *
21: * SUBROUTINE ZTPCON( NORM, UPLO, DIAG, N, AP, RCOND, WORK, RWORK,
22: * INFO )
1.15 ! bertrand 23: *
1.9 bertrand 24: * .. Scalar Arguments ..
25: * CHARACTER DIAG, NORM, UPLO
26: * INTEGER INFO, N
27: * DOUBLE PRECISION RCOND
28: * ..
29: * .. Array Arguments ..
30: * DOUBLE PRECISION RWORK( * )
31: * COMPLEX*16 AP( * ), WORK( * )
32: * ..
1.15 ! bertrand 33: *
1.9 bertrand 34: *
35: *> \par Purpose:
36: * =============
37: *>
38: *> \verbatim
39: *>
40: *> ZTPCON estimates the reciprocal of the condition number of a packed
41: *> triangular matrix A, in either the 1-norm or the infinity-norm.
42: *>
43: *> The norm of A is computed and an estimate is obtained for
44: *> norm(inv(A)), then the reciprocal of the condition number is
45: *> computed as
46: *> RCOND = 1 / ( norm(A) * norm(inv(A)) ).
47: *> \endverbatim
48: *
49: * Arguments:
50: * ==========
51: *
52: *> \param[in] NORM
53: *> \verbatim
54: *> NORM is CHARACTER*1
55: *> Specifies whether the 1-norm condition number or the
56: *> infinity-norm condition number is required:
57: *> = '1' or 'O': 1-norm;
58: *> = 'I': Infinity-norm.
59: *> \endverbatim
60: *>
61: *> \param[in] UPLO
62: *> \verbatim
63: *> UPLO is CHARACTER*1
64: *> = 'U': A is upper triangular;
65: *> = 'L': A is lower triangular.
66: *> \endverbatim
67: *>
68: *> \param[in] DIAG
69: *> \verbatim
70: *> DIAG is CHARACTER*1
71: *> = 'N': A is non-unit triangular;
72: *> = 'U': A is unit triangular.
73: *> \endverbatim
74: *>
75: *> \param[in] N
76: *> \verbatim
77: *> N is INTEGER
78: *> The order of the matrix A. N >= 0.
79: *> \endverbatim
80: *>
81: *> \param[in] AP
82: *> \verbatim
83: *> AP is COMPLEX*16 array, dimension (N*(N+1)/2)
84: *> The upper or lower triangular matrix A, packed columnwise in
85: *> a linear array. The j-th column of A is stored in the array
86: *> AP as follows:
87: *> if UPLO = 'U', AP(i + (j-1)*j/2) = A(i,j) for 1<=i<=j;
88: *> if UPLO = 'L', AP(i + (j-1)*(2n-j)/2) = A(i,j) for j<=i<=n.
89: *> If DIAG = 'U', the diagonal elements of A are not referenced
90: *> and are assumed to be 1.
91: *> \endverbatim
92: *>
93: *> \param[out] RCOND
94: *> \verbatim
95: *> RCOND is DOUBLE PRECISION
96: *> The reciprocal of the condition number of the matrix A,
97: *> computed as RCOND = 1/(norm(A) * norm(inv(A))).
98: *> \endverbatim
99: *>
100: *> \param[out] WORK
101: *> \verbatim
102: *> WORK is COMPLEX*16 array, dimension (2*N)
103: *> \endverbatim
104: *>
105: *> \param[out] RWORK
106: *> \verbatim
107: *> RWORK is DOUBLE PRECISION array, dimension (N)
108: *> \endverbatim
109: *>
110: *> \param[out] INFO
111: *> \verbatim
112: *> INFO is INTEGER
113: *> = 0: successful exit
114: *> < 0: if INFO = -i, the i-th argument had an illegal value
115: *> \endverbatim
116: *
117: * Authors:
118: * ========
119: *
1.15 ! bertrand 120: *> \author Univ. of Tennessee
! 121: *> \author Univ. of California Berkeley
! 122: *> \author Univ. of Colorado Denver
! 123: *> \author NAG Ltd.
1.9 bertrand 124: *
1.15 ! bertrand 125: *> \date December 2016
1.9 bertrand 126: *
127: *> \ingroup complex16OTHERcomputational
128: *
129: * =====================================================================
1.1 bertrand 130: SUBROUTINE ZTPCON( NORM, UPLO, DIAG, N, AP, RCOND, WORK, RWORK,
131: $ INFO )
132: *
1.15 ! bertrand 133: * -- LAPACK computational routine (version 3.7.0) --
1.1 bertrand 134: * -- LAPACK is a software package provided by Univ. of Tennessee, --
135: * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
1.15 ! bertrand 136: * December 2016
1.1 bertrand 137: *
138: * .. Scalar Arguments ..
139: CHARACTER DIAG, NORM, UPLO
140: INTEGER INFO, N
141: DOUBLE PRECISION RCOND
142: * ..
143: * .. Array Arguments ..
144: DOUBLE PRECISION RWORK( * )
145: COMPLEX*16 AP( * ), WORK( * )
146: * ..
147: *
148: * =====================================================================
149: *
150: * .. Parameters ..
151: DOUBLE PRECISION ONE, ZERO
152: PARAMETER ( ONE = 1.0D+0, ZERO = 0.0D+0 )
153: * ..
154: * .. Local Scalars ..
155: LOGICAL NOUNIT, ONENRM, UPPER
156: CHARACTER NORMIN
157: INTEGER IX, KASE, KASE1
158: DOUBLE PRECISION AINVNM, ANORM, SCALE, SMLNUM, XNORM
159: COMPLEX*16 ZDUM
160: * ..
161: * .. Local Arrays ..
162: INTEGER ISAVE( 3 )
163: * ..
164: * .. External Functions ..
165: LOGICAL LSAME
166: INTEGER IZAMAX
167: DOUBLE PRECISION DLAMCH, ZLANTP
168: EXTERNAL LSAME, IZAMAX, DLAMCH, ZLANTP
169: * ..
170: * .. External Subroutines ..
171: EXTERNAL XERBLA, ZDRSCL, ZLACN2, ZLATPS
172: * ..
173: * .. Intrinsic Functions ..
174: INTRINSIC ABS, DBLE, DIMAG, MAX
175: * ..
176: * .. Statement Functions ..
177: DOUBLE PRECISION CABS1
178: * ..
179: * .. Statement Function definitions ..
180: CABS1( ZDUM ) = ABS( DBLE( ZDUM ) ) + ABS( DIMAG( ZDUM ) )
181: * ..
182: * .. Executable Statements ..
183: *
184: * Test the input parameters.
185: *
186: INFO = 0
187: UPPER = LSAME( UPLO, 'U' )
188: ONENRM = NORM.EQ.'1' .OR. LSAME( NORM, 'O' )
189: NOUNIT = LSAME( DIAG, 'N' )
190: *
191: IF( .NOT.ONENRM .AND. .NOT.LSAME( NORM, 'I' ) ) THEN
192: INFO = -1
193: ELSE IF( .NOT.UPPER .AND. .NOT.LSAME( UPLO, 'L' ) ) THEN
194: INFO = -2
195: ELSE IF( .NOT.NOUNIT .AND. .NOT.LSAME( DIAG, 'U' ) ) THEN
196: INFO = -3
197: ELSE IF( N.LT.0 ) THEN
198: INFO = -4
199: END IF
200: IF( INFO.NE.0 ) THEN
201: CALL XERBLA( 'ZTPCON', -INFO )
202: RETURN
203: END IF
204: *
205: * Quick return if possible
206: *
207: IF( N.EQ.0 ) THEN
208: RCOND = ONE
209: RETURN
210: END IF
211: *
212: RCOND = ZERO
213: SMLNUM = DLAMCH( 'Safe minimum' )*DBLE( MAX( 1, N ) )
214: *
215: * Compute the norm of the triangular matrix A.
216: *
217: ANORM = ZLANTP( NORM, UPLO, DIAG, N, AP, RWORK )
218: *
219: * Continue only if ANORM > 0.
220: *
221: IF( ANORM.GT.ZERO ) THEN
222: *
223: * Estimate the norm of the inverse of A.
224: *
225: AINVNM = ZERO
226: NORMIN = 'N'
227: IF( ONENRM ) THEN
228: KASE1 = 1
229: ELSE
230: KASE1 = 2
231: END IF
232: KASE = 0
233: 10 CONTINUE
234: CALL ZLACN2( N, WORK( N+1 ), WORK, AINVNM, KASE, ISAVE )
235: IF( KASE.NE.0 ) THEN
236: IF( KASE.EQ.KASE1 ) THEN
237: *
238: * Multiply by inv(A).
239: *
240: CALL ZLATPS( UPLO, 'No transpose', DIAG, NORMIN, N, AP,
241: $ WORK, SCALE, RWORK, INFO )
242: ELSE
243: *
1.8 bertrand 244: * Multiply by inv(A**H).
1.1 bertrand 245: *
246: CALL ZLATPS( UPLO, 'Conjugate transpose', DIAG, NORMIN,
247: $ N, AP, WORK, SCALE, RWORK, INFO )
248: END IF
249: NORMIN = 'Y'
250: *
251: * Multiply by 1/SCALE if doing so will not cause overflow.
252: *
253: IF( SCALE.NE.ONE ) THEN
254: IX = IZAMAX( N, WORK, 1 )
255: XNORM = CABS1( WORK( IX ) )
256: IF( SCALE.LT.XNORM*SMLNUM .OR. SCALE.EQ.ZERO )
257: $ GO TO 20
258: CALL ZDRSCL( N, SCALE, WORK, 1 )
259: END IF
260: GO TO 10
261: END IF
262: *
263: * Compute the estimate of the reciprocal condition number.
264: *
265: IF( AINVNM.NE.ZERO )
266: $ RCOND = ( ONE / ANORM ) / AINVNM
267: END IF
268: *
269: 20 CONTINUE
270: RETURN
271: *
272: * End of ZTPCON
273: *
274: END
CVSweb interface <joel.bertrand@systella.fr>