LAPACK  3.6.1
LAPACK: Linear Algebra PACKage
double precision function zla_syrcond_x ( character  UPLO,
integer  N,
complex*16, dimension( lda, * )  A,
integer  LDA,
complex*16, dimension( ldaf, * )  AF,
integer  LDAF,
integer, dimension( * )  IPIV,
complex*16, dimension( * )  X,
integer  INFO,
complex*16, dimension( * )  WORK,
double precision, dimension( * )  RWORK 
)

ZLA_SYRCOND_X computes the infinity norm condition number of op(A)*diag(x) for symmetric indefinite matrices.

Download ZLA_SYRCOND_X + dependencies [TGZ] [ZIP] [TXT]

Purpose:
    ZLA_SYRCOND_X Computes the infinity norm condition number of
    op(A) * diag(X) where X is a COMPLEX*16 vector.
Parameters
[in]UPLO
          UPLO is CHARACTER*1
       = 'U':  Upper triangle of A is stored;
       = 'L':  Lower triangle of A is stored.
[in]N
          N is INTEGER
     The number of linear equations, i.e., the order of the
     matrix A.  N >= 0.
[in]A
          A is COMPLEX*16 array, dimension (LDA,N)
     On entry, the N-by-N matrix A.
[in]LDA
          LDA is INTEGER
     The leading dimension of the array A.  LDA >= max(1,N).
[in]AF
          AF is COMPLEX*16 array, dimension (LDAF,N)
     The block diagonal matrix D and the multipliers used to
     obtain the factor U or L as computed by ZSYTRF.
[in]LDAF
          LDAF is INTEGER
     The leading dimension of the array AF.  LDAF >= max(1,N).
[in]IPIV
          IPIV is INTEGER array, dimension (N)
     Details of the interchanges and the block structure of D
     as determined by ZSYTRF.
[in]X
          X is COMPLEX*16 array, dimension (N)
     The vector X in the formula op(A) * diag(X).
[out]INFO
          INFO is INTEGER
       = 0:  Successful exit.
     i > 0:  The ith argument is invalid.
[in]WORK
          WORK is COMPLEX*16 array, dimension (2*N).
     Workspace.
[in]RWORK
          RWORK is DOUBLE PRECISION array, dimension (N).
     Workspace.
Author
Univ. of Tennessee
Univ. of California Berkeley
Univ. of Colorado Denver
NAG Ltd.
Date
September 2012

Definition at line 135 of file zla_syrcond_x.f.

135 *
136 * -- LAPACK computational routine (version 3.4.2) --
137 * -- LAPACK is a software package provided by Univ. of Tennessee, --
138 * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
139 * September 2012
140 *
141 * .. Scalar Arguments ..
142  CHARACTER uplo
143  INTEGER n, lda, ldaf, info
144 * ..
145 * .. Array Arguments ..
146  INTEGER ipiv( * )
147  COMPLEX*16 a( lda, * ), af( ldaf, * ), work( * ), x( * )
148  DOUBLE PRECISION rwork( * )
149 * ..
150 *
151 * =====================================================================
152 *
153 * .. Local Scalars ..
154  INTEGER kase
155  DOUBLE PRECISION ainvnm, anorm, tmp
156  INTEGER i, j
157  LOGICAL up, upper
158  COMPLEX*16 zdum
159 * ..
160 * .. Local Arrays ..
161  INTEGER isave( 3 )
162 * ..
163 * .. External Functions ..
164  LOGICAL lsame
165  EXTERNAL lsame
166 * ..
167 * .. External Subroutines ..
168  EXTERNAL zlacn2, zsytrs, xerbla
169 * ..
170 * .. Intrinsic Functions ..
171  INTRINSIC abs, max
172 * ..
173 * .. Statement Functions ..
174  DOUBLE PRECISION cabs1
175 * ..
176 * .. Statement Function Definitions ..
177  cabs1( zdum ) = abs( dble( zdum ) ) + abs( dimag( zdum ) )
178 * ..
179 * .. Executable Statements ..
180 *
181  zla_syrcond_x = 0.0d+0
182 *
183  info = 0
184  upper = lsame( uplo, 'U' )
185  IF( .NOT.upper .AND. .NOT.lsame( uplo, 'L' ) ) THEN
186  info = -1
187  ELSE IF( n.LT.0 ) THEN
188  info = -2
189  ELSE IF( lda.LT.max( 1, n ) ) THEN
190  info = -4
191  ELSE IF( ldaf.LT.max( 1, n ) ) THEN
192  info = -6
193  END IF
194  IF( info.NE.0 ) THEN
195  CALL xerbla( 'ZLA_SYRCOND_X', -info )
196  RETURN
197  END IF
198  up = .false.
199  IF ( lsame( uplo, 'U' ) ) up = .true.
200 *
201 * Compute norm of op(A)*op2(C).
202 *
203  anorm = 0.0d+0
204  IF ( up ) THEN
205  DO i = 1, n
206  tmp = 0.0d+0
207  DO j = 1, i
208  tmp = tmp + cabs1( a( j, i ) * x( j ) )
209  END DO
210  DO j = i+1, n
211  tmp = tmp + cabs1( a( i, j ) * x( j ) )
212  END DO
213  rwork( i ) = tmp
214  anorm = max( anorm, tmp )
215  END DO
216  ELSE
217  DO i = 1, n
218  tmp = 0.0d+0
219  DO j = 1, i
220  tmp = tmp + cabs1( a( i, j ) * x( j ) )
221  END DO
222  DO j = i+1, n
223  tmp = tmp + cabs1( a( j, i ) * x( j ) )
224  END DO
225  rwork( i ) = tmp
226  anorm = max( anorm, tmp )
227  END DO
228  END IF
229 *
230 * Quick return if possible.
231 *
232  IF( n.EQ.0 ) THEN
233  zla_syrcond_x = 1.0d+0
234  RETURN
235  ELSE IF( anorm .EQ. 0.0d+0 ) THEN
236  RETURN
237  END IF
238 *
239 * Estimate the norm of inv(op(A)).
240 *
241  ainvnm = 0.0d+0
242 *
243  kase = 0
244  10 CONTINUE
245  CALL zlacn2( n, work( n+1 ), work, ainvnm, kase, isave )
246  IF( kase.NE.0 ) THEN
247  IF( kase.EQ.2 ) THEN
248 *
249 * Multiply by R.
250 *
251  DO i = 1, n
252  work( i ) = work( i ) * rwork( i )
253  END DO
254 *
255  IF ( up ) THEN
256  CALL zsytrs( 'U', n, 1, af, ldaf, ipiv,
257  $ work, n, info )
258  ELSE
259  CALL zsytrs( 'L', n, 1, af, ldaf, ipiv,
260  $ work, n, info )
261  ENDIF
262 *
263 * Multiply by inv(X).
264 *
265  DO i = 1, n
266  work( i ) = work( i ) / x( i )
267  END DO
268  ELSE
269 *
270 * Multiply by inv(X**T).
271 *
272  DO i = 1, n
273  work( i ) = work( i ) / x( i )
274  END DO
275 *
276  IF ( up ) THEN
277  CALL zsytrs( 'U', n, 1, af, ldaf, ipiv,
278  $ work, n, info )
279  ELSE
280  CALL zsytrs( 'L', n, 1, af, ldaf, ipiv,
281  $ work, n, info )
282  END IF
283 *
284 * Multiply by R.
285 *
286  DO i = 1, n
287  work( i ) = work( i ) * rwork( i )
288  END DO
289  END IF
290  GO TO 10
291  END IF
292 *
293 * Compute the estimate of the reciprocal condition number.
294 *
295  IF( ainvnm .NE. 0.0d+0 )
296  $ zla_syrcond_x = 1.0d+0 / ainvnm
297 *
298  RETURN
299 *
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 zsytrs(UPLO, N, NRHS, A, LDA, IPIV, B, LDB, INFO)
ZSYTRS
Definition: zsytrs.f:122
logical function lsame(CA, CB)
LSAME
Definition: lsame.f:55
double precision function zla_syrcond_x(UPLO, N, A, LDA, AF, LDAF, IPIV, X, INFO, WORK, RWORK)
ZLA_SYRCOND_X computes the infinity norm condition number of op(A)*diag(x) for symmetric indefinite m...

Here is the call graph for this function:

Here is the caller graph for this function: