1*> \brief \b CSYCON
2*
3*  =========== DOCUMENTATION ===========
4*
5* Online html documentation available at
6*            http://www.netlib.org/lapack/explore-html/
7*
8*> \htmlonly
9*> Download CSYCON + dependencies
10*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/csycon.f">
11*> [TGZ]</a>
12*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/csycon.f">
13*> [ZIP]</a>
14*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/csycon.f">
15*> [TXT]</a>
16*> \endhtmlonly
17*
18*  Definition:
19*  ===========
20*
21*       SUBROUTINE CSYCON( UPLO, N, A, LDA, IPIV, ANORM, RCOND, WORK,
22*                          INFO )
23*
24*       .. Scalar Arguments ..
25*       CHARACTER          UPLO
26*       INTEGER            INFO, LDA, N
27*       REAL               ANORM, RCOND
28*       ..
29*       .. Array Arguments ..
30*       INTEGER            IPIV( * )
31*       COMPLEX            A( LDA, * ), WORK( * )
32*       ..
33*
34*
35*> \par Purpose:
36*  =============
37*>
38*> \verbatim
39*>
40*> CSYCON estimates the reciprocal of the condition number (in the
41*> 1-norm) of a complex symmetric matrix A using the factorization
42*> A = U*D*U**T or A = L*D*L**T computed by CSYTRF.
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*>          Specifies whether the details of the factorization are stored
55*>          as an upper or lower triangular matrix.
56*>          = 'U':  Upper triangular, form is A = U*D*U**T;
57*>          = 'L':  Lower triangular, form is A = L*D*L**T.
58*> \endverbatim
59*>
60*> \param[in] N
61*> \verbatim
62*>          N is INTEGER
63*>          The order of the matrix A.  N >= 0.
64*> \endverbatim
65*>
66*> \param[in] A
67*> \verbatim
68*>          A is COMPLEX array, dimension (LDA,N)
69*>          The block diagonal matrix D and the multipliers used to
70*>          obtain the factor U or L as computed by CSYTRF.
71*> \endverbatim
72*>
73*> \param[in] LDA
74*> \verbatim
75*>          LDA is INTEGER
76*>          The leading dimension of the array A.  LDA >= max(1,N).
77*> \endverbatim
78*>
79*> \param[in] IPIV
80*> \verbatim
81*>          IPIV is INTEGER array, dimension (N)
82*>          Details of the interchanges and the block structure of D
83*>          as determined by CSYTRF.
84*> \endverbatim
85*>
86*> \param[in] ANORM
87*> \verbatim
88*>          ANORM is REAL
89*>          The 1-norm of the original matrix A.
90*> \endverbatim
91*>
92*> \param[out] RCOND
93*> \verbatim
94*>          RCOND is REAL
95*>          The reciprocal of the condition number of the matrix A,
96*>          computed as RCOND = 1/(ANORM * AINVNM), where AINVNM is an
97*>          estimate of the 1-norm of inv(A) computed in this routine.
98*> \endverbatim
99*>
100*> \param[out] WORK
101*> \verbatim
102*>          WORK is COMPLEX array, dimension (2*N)
103*> \endverbatim
104*>
105*> \param[out] INFO
106*> \verbatim
107*>          INFO is INTEGER
108*>          = 0:  successful exit
109*>          < 0:  if INFO = -i, the i-th argument had an illegal value
110*> \endverbatim
111*
112*  Authors:
113*  ========
114*
115*> \author Univ. of Tennessee
116*> \author Univ. of California Berkeley
117*> \author Univ. of Colorado Denver
118*> \author NAG Ltd.
119*
120*> \ingroup complexSYcomputational
121*
122*  =====================================================================
123      SUBROUTINE CSYCON( UPLO, N, A, LDA, IPIV, ANORM, RCOND, WORK,
124     $                   INFO )
125*
126*  -- LAPACK computational routine --
127*  -- LAPACK is a software package provided by Univ. of Tennessee,    --
128*  -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
129*
130*     .. Scalar Arguments ..
131      CHARACTER          UPLO
132      INTEGER            INFO, LDA, N
133      REAL               ANORM, RCOND
134*     ..
135*     .. Array Arguments ..
136      INTEGER            IPIV( * )
137      COMPLEX            A( LDA, * ), WORK( * )
138*     ..
139*
140*  =====================================================================
141*
142*     .. Parameters ..
143      REAL               ONE, ZERO
144      PARAMETER          ( ONE = 1.0E+0, ZERO = 0.0E+0 )
145*     ..
146*     .. Local Scalars ..
147      LOGICAL            UPPER
148      INTEGER            I, KASE
149      REAL               AINVNM
150*     ..
151*     .. Local Arrays ..
152      INTEGER            ISAVE( 3 )
153*     ..
154*     .. External Functions ..
155      LOGICAL            LSAME
156      EXTERNAL           LSAME
157*     ..
158*     .. External Subroutines ..
159      EXTERNAL           CLACN2, CSYTRS, XERBLA
160*     ..
161*     .. Intrinsic Functions ..
162      INTRINSIC          MAX
163*     ..
164*     .. Executable Statements ..
165*
166*     Test the input parameters.
167*
168      INFO = 0
169      UPPER = LSAME( UPLO, 'U' )
170      IF( .NOT.UPPER .AND. .NOT.LSAME( UPLO, 'L' ) ) THEN
171         INFO = -1
172      ELSE IF( N.LT.0 ) THEN
173         INFO = -2
174      ELSE IF( LDA.LT.MAX( 1, N ) ) THEN
175         INFO = -4
176      ELSE IF( ANORM.LT.ZERO ) THEN
177         INFO = -6
178      END IF
179      IF( INFO.NE.0 ) THEN
180         CALL XERBLA( 'CSYCON', -INFO )
181         RETURN
182      END IF
183*
184*     Quick return if possible
185*
186      RCOND = ZERO
187      IF( N.EQ.0 ) THEN
188         RCOND = ONE
189         RETURN
190      ELSE IF( ANORM.LE.ZERO ) THEN
191         RETURN
192      END IF
193*
194*     Check that the diagonal matrix D is nonsingular.
195*
196      IF( UPPER ) THEN
197*
198*        Upper triangular storage: examine D from bottom to top
199*
200         DO 10 I = N, 1, -1
201            IF( IPIV( I ).GT.0 .AND. A( I, I ).EQ.ZERO )
202     $         RETURN
203   10    CONTINUE
204      ELSE
205*
206*        Lower triangular storage: examine D from top to bottom.
207*
208         DO 20 I = 1, N
209            IF( IPIV( I ).GT.0 .AND. A( I, I ).EQ.ZERO )
210     $         RETURN
211   20    CONTINUE
212      END IF
213*
214*     Estimate the 1-norm of the inverse.
215*
216      KASE = 0
217   30 CONTINUE
218      CALL CLACN2( N, WORK( N+1 ), WORK, AINVNM, KASE, ISAVE )
219      IF( KASE.NE.0 ) THEN
220*
221*        Multiply by inv(L*D*L**T) or inv(U*D*U**T).
222*
223         CALL CSYTRS( UPLO, N, 1, A, LDA, IPIV, WORK, N, INFO )
224         GO TO 30
225      END IF
226*
227*     Compute the estimate of the reciprocal condition number.
228*
229      IF( AINVNM.NE.ZERO )
230     $   RCOND = ( ONE / AINVNM ) / ANORM
231*
232      RETURN
233*
234*     End of CSYCON
235*
236      END
237