ENH: Improving the travis dashboard name
[platform/upstream/lapack.git] / SRC / cppcon.f
1 *> \brief \b CPPCON
2 *
3 *  =========== DOCUMENTATION ===========
4 *
5 * Online html documentation available at
6 *            http://www.netlib.org/lapack/explore-html/
7 *
8 *> \htmlonly
9 *> Download CPPCON + dependencies
10 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/cppcon.f">
11 *> [TGZ]</a>
12 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/cppcon.f">
13 *> [ZIP]</a>
14 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/cppcon.f">
15 *> [TXT]</a>
16 *> \endhtmlonly
17 *
18 *  Definition:
19 *  ===========
20 *
21 *       SUBROUTINE CPPCON( UPLO, N, AP, ANORM, RCOND, WORK, RWORK, INFO )
22 *
23 *       .. Scalar Arguments ..
24 *       CHARACTER          UPLO
25 *       INTEGER            INFO, N
26 *       REAL               ANORM, RCOND
27 *       ..
28 *       .. Array Arguments ..
29 *       REAL               RWORK( * )
30 *       COMPLEX            AP( * ), WORK( * )
31 *       ..
32 *
33 *
34 *> \par Purpose:
35 *  =============
36 *>
37 *> \verbatim
38 *>
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
42 *> CPPTRF.
43 *>
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))).
46 *> \endverbatim
47 *
48 *  Arguments:
49 *  ==========
50 *
51 *> \param[in] UPLO
52 *> \verbatim
53 *>          UPLO is CHARACTER*1
54 *>          = 'U':  Upper triangle of A is stored;
55 *>          = 'L':  Lower triangle of A is stored.
56 *> \endverbatim
57 *>
58 *> \param[in] N
59 *> \verbatim
60 *>          N is INTEGER
61 *>          The order of the matrix A.  N >= 0.
62 *> \endverbatim
63 *>
64 *> \param[in] AP
65 *> \verbatim
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
70 *>          as follows:
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.
73 *> \endverbatim
74 *>
75 *> \param[in] ANORM
76 *> \verbatim
77 *>          ANORM is REAL
78 *>          The 1-norm (or infinity-norm) of the Hermitian matrix A.
79 *> \endverbatim
80 *>
81 *> \param[out] RCOND
82 *> \verbatim
83 *>          RCOND is REAL
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.
87 *> \endverbatim
88 *>
89 *> \param[out] WORK
90 *> \verbatim
91 *>          WORK is COMPLEX array, dimension (2*N)
92 *> \endverbatim
93 *>
94 *> \param[out] RWORK
95 *> \verbatim
96 *>          RWORK is REAL array, dimension (N)
97 *> \endverbatim
98 *>
99 *> \param[out] INFO
100 *> \verbatim
101 *>          INFO is INTEGER
102 *>          = 0:  successful exit
103 *>          < 0:  if INFO = -i, the i-th argument had an illegal value
104 *> \endverbatim
105 *
106 *  Authors:
107 *  ========
108 *
109 *> \author Univ. of Tennessee
110 *> \author Univ. of California Berkeley
111 *> \author Univ. of Colorado Denver
112 *> \author NAG Ltd.
113 *
114 *> \date November 2011
115 *
116 *> \ingroup complexOTHERcomputational
117 *
118 *  =====================================================================
119       SUBROUTINE CPPCON( UPLO, N, AP, ANORM, RCOND, WORK, RWORK, INFO )
120 *
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..--
124 *     November 2011
125 *
126 *     .. Scalar Arguments ..
127       CHARACTER          UPLO
128       INTEGER            INFO, N
129       REAL               ANORM, RCOND
130 *     ..
131 *     .. Array Arguments ..
132       REAL               RWORK( * )
133       COMPLEX            AP( * ), WORK( * )
134 *     ..
135 *
136 *  =====================================================================
137 *
138 *     .. Parameters ..
139       REAL               ONE, ZERO
140       PARAMETER          ( ONE = 1.0E+0, ZERO = 0.0E+0 )
141 *     ..
142 *     .. Local Scalars ..
143       LOGICAL            UPPER
144       CHARACTER          NORMIN
145       INTEGER            IX, KASE
146       REAL               AINVNM, SCALE, SCALEL, SCALEU, SMLNUM
147       COMPLEX            ZDUM
148 *     ..
149 *     .. Local Arrays ..
150       INTEGER            ISAVE( 3 )
151 *     ..
152 *     .. External Functions ..
153       LOGICAL            LSAME
154       INTEGER            ICAMAX
155       REAL               SLAMCH
156       EXTERNAL           LSAME, ICAMAX, SLAMCH
157 *     ..
158 *     .. External Subroutines ..
159       EXTERNAL           CLACN2, CLATPS, CSRSCL, XERBLA
160 *     ..
161 *     .. Intrinsic Functions ..
162       INTRINSIC          ABS, AIMAG, REAL
163 *     ..
164 *     .. Statement Functions ..
165       REAL               CABS1
166 *     ..
167 *     .. Statement Function definitions ..
168       CABS1( ZDUM ) = ABS( REAL( ZDUM ) ) + ABS( AIMAG( ZDUM ) )
169 *     ..
170 *     .. Executable Statements ..
171 *
172 *     Test the input parameters.
173 *
174       INFO = 0
175       UPPER = LSAME( UPLO, 'U' )
176       IF( .NOT.UPPER .AND. .NOT.LSAME( UPLO, 'L' ) ) THEN
177          INFO = -1
178       ELSE IF( N.LT.0 ) THEN
179          INFO = -2
180       ELSE IF( ANORM.LT.ZERO ) THEN
181          INFO = -4
182       END IF
183       IF( INFO.NE.0 ) THEN
184          CALL XERBLA( 'CPPCON', -INFO )
185          RETURN
186       END IF
187 *
188 *     Quick return if possible
189 *
190       RCOND = ZERO
191       IF( N.EQ.0 ) THEN
192          RCOND = ONE
193          RETURN
194       ELSE IF( ANORM.EQ.ZERO ) THEN
195          RETURN
196       END IF
197 *
198       SMLNUM = SLAMCH( 'Safe minimum' )
199 *
200 *     Estimate the 1-norm of the inverse.
201 *
202       KASE = 0
203       NORMIN = 'N'
204    10 CONTINUE
205       CALL CLACN2( N, WORK( N+1 ), WORK, AINVNM, KASE, ISAVE )
206       IF( KASE.NE.0 ) THEN
207          IF( UPPER ) THEN
208 *
209 *           Multiply by inv(U**H).
210 *
211             CALL CLATPS( 'Upper', 'Conjugate transpose', 'Non-unit',
212      $                   NORMIN, N, AP, WORK, SCALEL, RWORK, INFO )
213             NORMIN = 'Y'
214 *
215 *           Multiply by inv(U).
216 *
217             CALL CLATPS( 'Upper', 'No transpose', 'Non-unit', NORMIN, N,
218      $                   AP, WORK, SCALEU, RWORK, INFO )
219          ELSE
220 *
221 *           Multiply by inv(L).
222 *
223             CALL CLATPS( 'Lower', 'No transpose', 'Non-unit', NORMIN, N,
224      $                   AP, WORK, SCALEL, RWORK, INFO )
225             NORMIN = 'Y'
226 *
227 *           Multiply by inv(L**H).
228 *
229             CALL CLATPS( 'Lower', 'Conjugate transpose', 'Non-unit',
230      $                   NORMIN, N, AP, WORK, SCALEU, RWORK, INFO )
231          END IF
232 *
233 *        Multiply by 1/SCALE if doing so will not cause overflow.
234 *
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 )
239      $         GO TO 20
240             CALL CSRSCL( N, SCALE, WORK, 1 )
241          END IF
242          GO TO 10
243       END IF
244 *
245 *     Compute the estimate of the reciprocal condition number.
246 *
247       IF( AINVNM.NE.ZERO )
248      $   RCOND = ( ONE / AINVNM ) / ANORM
249 *
250    20 CONTINUE
251       RETURN
252 *
253 *     End of CPPCON
254 *
255       END