LAPACK  3.6.1
LAPACK: Linear Algebra PACKage
double precision function zla_gercond_x ( character  TRANS,
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_GERCOND_X computes the infinity norm condition number of op(A)*diag(x) for general matrices.

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

Purpose:
    ZLA_GERCOND_X computes the infinity norm condition number of
    op(A) * diag(X) where X is a COMPLEX*16 vector.
Parameters
[in]TRANS
          TRANS is CHARACTER*1
     Specifies the form of the system of equations:
       = 'N':  A * X = B     (No transpose)
       = 'T':  A**T * X = B  (Transpose)
       = 'C':  A**H * X = B  (Conjugate Transpose = Transpose)
[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 factors L and U from the factorization
     A = P*L*U as computed by ZGETRF.
[in]LDAF
          LDAF is INTEGER
     The leading dimension of the array AF.  LDAF >= max(1,N).
[in]IPIV
          IPIV is INTEGER array, dimension (N)
     The pivot indices from the factorization A = P*L*U
     as computed by ZGETRF; row i of the matrix was interchanged
     with row IPIV(i).
[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 138 of file zla_gercond_x.f.

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

Here is the call graph for this function:

Here is the caller graph for this function: