1*> \brief <b> CSYCON_ROOK </b>
2*
3*  =========== DOCUMENTATION ===========
4*
5* Online html documentation available at
6*            http://www.netlib.org/lapack/explore-html/
7*
8*> \htmlonly
9*> Download CSYCON_ROOK + dependencies
10*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/csycon_rook.f">
11*> [TGZ]</a>
12*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/csycon_rook.f">
13*> [ZIP]</a>
14*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/csycon_rook.f">
15*> [TXT]</a>
16*> \endhtmlonly
17*
18*  Definition:
19*  ===========
20*
21*       SUBROUTINE CSYCON_ROOK( UPLO, N, A, LDA, IPIV, ANORM, RCOND,
22*                               WORK, 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_ROOK 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_ROOK.
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_ROOK.
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_ROOK.
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*> \par Contributors:
123*  ==================
124*> \verbatim
125*>
126*>   April 2012, Igor Kozachenko,
127*>                  Computer Science Division,
128*>                  University of California, Berkeley
129*>
130*>  September 2007, Sven Hammarling, Nicholas J. Higham, Craig Lucas,
131*>                  School of Mathematics,
132*>                  University of Manchester
133*>
134*> \endverbatim
135*
136*  =====================================================================
137      SUBROUTINE CSYCON_ROOK( UPLO, N, A, LDA, IPIV, ANORM, RCOND, WORK,
138     $                        INFO )
139*
140*  -- LAPACK computational routine --
141*  -- LAPACK is a software package provided by Univ. of Tennessee,    --
142*  -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
143*
144*     .. Scalar Arguments ..
145      CHARACTER          UPLO
146      INTEGER            INFO, LDA, N
147      REAL               ANORM, RCOND
148*     ..
149*     .. Array Arguments ..
150      INTEGER            IPIV( * )
151      COMPLEX            A( LDA, * ), WORK( * )
152*     ..
153*
154*  =====================================================================
155*
156*     .. Parameters ..
157      REAL               ONE, ZERO
158      PARAMETER          ( ONE = 1.0E+0, ZERO = 0.0E+0 )
159      COMPLEX            CZERO
160      PARAMETER          ( CZERO = ( 0.0E+0, 0.0E+0 ) )
161*     ..
162*     .. Local Scalars ..
163      LOGICAL            UPPER
164      INTEGER            I, KASE
165      REAL               AINVNM
166*     ..
167*     .. Local Arrays ..
168      INTEGER            ISAVE( 3 )
169*     ..
170*     .. External Functions ..
171      LOGICAL            LSAME
172      EXTERNAL           LSAME
173*     ..
174*     .. External Subroutines ..
175      EXTERNAL           CLACN2, CSYTRS_ROOK, XERBLA
176*     ..
177*     .. Intrinsic Functions ..
178      INTRINSIC          MAX
179*     ..
180*     .. Executable Statements ..
181*
182*     Test the input parameters.
183*
184      INFO = 0
185      UPPER = LSAME( UPLO, 'U' )
186      IF( .NOT.UPPER .AND. .NOT.LSAME( UPLO, 'L' ) ) THEN
187         INFO = -1
188      ELSE IF( N.LT.0 ) THEN
189         INFO = -2
190      ELSE IF( LDA.LT.MAX( 1, N ) ) THEN
191         INFO = -4
192      ELSE IF( ANORM.LT.ZERO ) THEN
193         INFO = -6
194      END IF
195      IF( INFO.NE.0 ) THEN
196         CALL XERBLA( 'CSYCON_ROOK', -INFO )
197         RETURN
198      END IF
199*
200*     Quick return if possible
201*
202      RCOND = ZERO
203      IF( N.EQ.0 ) THEN
204         RCOND = ONE
205         RETURN
206      ELSE IF( ANORM.LE.ZERO ) THEN
207         RETURN
208      END IF
209*
210*     Check that the diagonal matrix D is nonsingular.
211*
212      IF( UPPER ) THEN
213*
214*        Upper triangular storage: examine D from bottom to top
215*
216         DO 10 I = N, 1, -1
217            IF( IPIV( I ).GT.0 .AND. A( I, I ).EQ.CZERO )
218     $         RETURN
219   10    CONTINUE
220      ELSE
221*
222*        Lower triangular storage: examine D from top to bottom.
223*
224         DO 20 I = 1, N
225            IF( IPIV( I ).GT.0 .AND. A( I, I ).EQ.CZERO )
226     $         RETURN
227   20    CONTINUE
228      END IF
229*
230*     Estimate the 1-norm of the inverse.
231*
232      KASE = 0
233   30 CONTINUE
234      CALL CLACN2( N, WORK( N+1 ), WORK, AINVNM, KASE, ISAVE )
235      IF( KASE.NE.0 ) THEN
236*
237*        Multiply by inv(L*D*L**T) or inv(U*D*U**T).
238*
239         CALL CSYTRS_ROOK( UPLO, N, 1, A, LDA, IPIV, WORK, N, INFO )
240         GO TO 30
241      END IF
242*
243*     Compute the estimate of the reciprocal condition number.
244*
245      IF( AINVNM.NE.ZERO )
246     $   RCOND = ( ONE / AINVNM ) / ANORM
247*
248      RETURN
249*
250*     End of CSYCON_ROOK
251*
252      END
253