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

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

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

Purpose:
    CLA_SYRCOND_X Computes the infinity norm condition number of
    op(A) * diag(X) where X is a COMPLEX 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 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 array, dimension (LDAF,N)
     The block diagonal matrix D and the multipliers used to
     obtain the factor U or L as computed by CSYTRF.
[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 CSYTRF.
[in]X
          X is COMPLEX 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 array, dimension (2*N).
     Workspace.
[in]RWORK
          RWORK is REAL array, dimension (N).
     Workspace.
Author
Univ. of Tennessee
Univ. of California Berkeley
Univ. of Colorado Denver
NAG Ltd.
Date
September 2012

Definition at line 133 of file cla_syrcond_x.f.

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

Here is the call graph for this function:

Here is the caller graph for this function: