1*> \brief <b> ZHECON_ROOK estimates the reciprocal of the condition number fort HE matrices using factorization obtained with one of the bounded diagonal pivoting methods (max 2 interchanges) </b>
2*
3*  =========== DOCUMENTATION ===========
4*
5* Online html documentation available at
6*            http://www.netlib.org/lapack/explore-html/
7*
8*> \htmlonly
9*> Download ZHECON_ROOK + dependencies
10*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/zhecon_rook.f">
11*> [TGZ]</a>
12*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/zhecon_rook.f">
13*> [ZIP]</a>
14*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zhecon_rook.f">
15*> [TXT]</a>
16*> \endhtmlonly
17*
18*  Definition:
19*  ===========
20*
21*       SUBROUTINE ZHECON_ROOK( UPLO, N, A, LDA, IPIV, ANORM, RCOND, WORK,
22*                               INFO )
23*
24*       .. Scalar Arguments ..
25*       CHARACTER          UPLO
26*       INTEGER            INFO, LDA, N
27*       DOUBLE PRECISION   ANORM, RCOND
28*       ..
29*       .. Array Arguments ..
30*       INTEGER            IPIV( * )
31*       COMPLEX*16         A( LDA, * ), WORK( * )
32*       ..
33*
34*
35*> \par Purpose:
36*  =============
37*>
38*> \verbatim
39*>
40*> ZHECON_ROOK estimates the reciprocal of the condition number of a complex
41*> Hermitian matrix A using the factorization A = U*D*U**H or
42*> A = L*D*L**H computed by CHETRF_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**H;
57*>          = 'L':  Lower triangular, form is A = L*D*L**H.
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*16 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 CHETRF_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 CHETRF_ROOK.
84*> \endverbatim
85*>
86*> \param[in] ANORM
87*> \verbatim
88*>          ANORM is DOUBLE PRECISION
89*>          The 1-norm of the original matrix A.
90*> \endverbatim
91*>
92*> \param[out] RCOND
93*> \verbatim
94*>          RCOND is DOUBLE PRECISION
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*16 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 complex16HEcomputational
121*
122*> \par Contributors:
123*  ==================
124*> \verbatim
125*>
126*>  June 2017,  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 ZHECON_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      DOUBLE PRECISION   ANORM, RCOND
148*     ..
149*     .. Array Arguments ..
150      INTEGER            IPIV( * )
151      COMPLEX*16         A( LDA, * ), WORK( * )
152*     ..
153*
154*  =====================================================================
155*
156*     .. Parameters ..
157      DOUBLE PRECISION   ONE, ZERO
158      PARAMETER          ( ONE = 1.0D+0, ZERO = 0.0D+0 )
159*     ..
160*     .. Local Scalars ..
161      LOGICAL            UPPER
162      INTEGER            I, KASE
163      DOUBLE PRECISION   AINVNM
164*     ..
165*     .. Local Arrays ..
166      INTEGER            ISAVE( 3 )
167*     ..
168*     .. External Functions ..
169      LOGICAL            LSAME
170      EXTERNAL           LSAME
171*     ..
172*     .. External Subroutines ..
173      EXTERNAL           ZHETRS_ROOK, ZLACN2, XERBLA
174*     ..
175*     .. Intrinsic Functions ..
176      INTRINSIC          MAX
177*     ..
178*     .. Executable Statements ..
179*
180*     Test the input parameters.
181*
182      INFO = 0
183      UPPER = LSAME( UPLO, 'U' )
184      IF( .NOT.UPPER .AND. .NOT.LSAME( UPLO, 'L' ) ) THEN
185         INFO = -1
186      ELSE IF( N.LT.0 ) THEN
187         INFO = -2
188      ELSE IF( LDA.LT.MAX( 1, N ) ) THEN
189         INFO = -4
190      ELSE IF( ANORM.LT.ZERO ) THEN
191         INFO = -6
192      END IF
193      IF( INFO.NE.0 ) THEN
194         CALL XERBLA( 'ZHECON_ROOK', -INFO )
195         RETURN
196      END IF
197*
198*     Quick return if possible
199*
200      RCOND = ZERO
201      IF( N.EQ.0 ) THEN
202         RCOND = ONE
203         RETURN
204      ELSE IF( ANORM.LE.ZERO ) THEN
205         RETURN
206      END IF
207*
208*     Check that the diagonal matrix D is nonsingular.
209*
210      IF( UPPER ) THEN
211*
212*        Upper triangular storage: examine D from bottom to top
213*
214         DO 10 I = N, 1, -1
215            IF( IPIV( I ).GT.0 .AND. A( I, I ).EQ.ZERO )
216     $         RETURN
217   10    CONTINUE
218      ELSE
219*
220*        Lower triangular storage: examine D from top to bottom.
221*
222         DO 20 I = 1, N
223            IF( IPIV( I ).GT.0 .AND. A( I, I ).EQ.ZERO )
224     $         RETURN
225   20    CONTINUE
226      END IF
227*
228*     Estimate the 1-norm of the inverse.
229*
230      KASE = 0
231   30 CONTINUE
232      CALL ZLACN2( N, WORK( N+1 ), WORK, AINVNM, KASE, ISAVE )
233      IF( KASE.NE.0 ) THEN
234*
235*        Multiply by inv(L*D*L**H) or inv(U*D*U**H).
236*
237         CALL ZHETRS_ROOK( UPLO, N, 1, A, LDA, IPIV, WORK, N, INFO )
238         GO TO 30
239      END IF
240*
241*     Compute the estimate of the reciprocal condition number.
242*
243      IF( AINVNM.NE.ZERO )
244     $   RCOND = ( ONE / AINVNM ) / ANORM
245*
246      RETURN
247*
248*     End of ZHECON_ROOK
249*
250      END
251