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

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

Purpose:
    CLA_GERCOND_X computes the infinity norm condition number of
    op(A) * diag(X) where X is a COMPLEX 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 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 factors L and U from the factorization
     A = P*L*U as computed by CGETRF.
[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 CGETRF; row i of the matrix was interchanged
     with row IPIV(i).
[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 137 of file cla_gercond_x.f.

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