LAPACK 3.12.0
LAPACK: Linear Algebra PACKage
Loading...
Searching...
No Matches

◆ cla_gercond_x()

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.
[out]WORK
          WORK is COMPLEX array, dimension (2*N).
     Workspace.
[out]RWORK
          RWORK is REAL array, dimension (N).
     Workspace.
Author
Univ. of Tennessee
Univ. of California Berkeley
Univ. of Colorado Denver
NAG Ltd.

Definition at line 133 of file cla_gercond_x.f.

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