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