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

◆ cla_gercond_c()

real function cla_gercond_c ( character  trans,
integer  n,
complex, dimension( lda, * )  a,
integer  lda,
complex, dimension( ldaf, * )  af,
integer  ldaf,
integer, dimension( * )  ipiv,
real, dimension( * )  c,
logical  capply,
integer  info,
complex, dimension( * )  work,
real, dimension( * )  rwork 
)

CLA_GERCOND_C computes the infinity norm condition number of op(A)*inv(diag(c)) for general matrices.

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

Purpose:
    CLA_GERCOND_C computes the infinity norm condition number of
    op(A) * inv(diag(C)) where C is a REAL 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]C
          C is REAL array, dimension (N)
     The vector C in the formula op(A) * inv(diag(C)).
[in]CAPPLY
          CAPPLY is LOGICAL
     If .TRUE. then access the vector C in the formula above.
[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 140 of file cla_gercond_c.f.

142*
143* -- LAPACK computational routine --
144* -- LAPACK is a software package provided by Univ. of Tennessee, --
145* -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
146*
147* .. Scalar Arguments ..
148 CHARACTER TRANS
149 LOGICAL CAPPLY
150 INTEGER N, LDA, LDAF, INFO
151* ..
152* .. Array Arguments ..
153 INTEGER IPIV( * )
154 COMPLEX A( LDA, * ), AF( LDAF, * ), WORK( * )
155 REAL C( * ), RWORK( * )
156* ..
157*
158* =====================================================================
159*
160* .. Local Scalars ..
161 LOGICAL NOTRANS
162 INTEGER KASE, I, J
163 REAL AINVNM, ANORM, TMP
164 COMPLEX ZDUM
165* ..
166* .. Local Arrays ..
167 INTEGER ISAVE( 3 )
168* ..
169* .. External Functions ..
170 LOGICAL LSAME
171 EXTERNAL lsame
172* ..
173* .. External Subroutines ..
174 EXTERNAL clacn2, cgetrs, xerbla
175* ..
176* .. Intrinsic Functions ..
177 INTRINSIC abs, max, real, aimag
178* ..
179* .. Statement Functions ..
180 REAL CABS1
181* ..
182* .. Statement Function Definitions ..
183 cabs1( zdum ) = abs( real( zdum ) ) + abs( aimag( zdum ) )
184* ..
185* .. Executable Statements ..
186 cla_gercond_c = 0.0e+0
187*
188 info = 0
189 notrans = lsame( trans, 'N' )
190 IF ( .NOT. notrans .AND. .NOT. lsame( trans, 'T' ) .AND. .NOT.
191 $ lsame( trans, 'C' ) ) THEN
192 info = -1
193 ELSE IF( n.LT.0 ) THEN
194 info = -2
195 ELSE IF( lda.LT.max( 1, n ) ) THEN
196 info = -4
197 ELSE IF( ldaf.LT.max( 1, n ) ) THEN
198 info = -6
199 END IF
200 IF( info.NE.0 ) THEN
201 CALL xerbla( 'CLA_GERCOND_C', -info )
202 RETURN
203 END IF
204*
205* Compute norm of op(A)*op2(C).
206*
207 anorm = 0.0e+0
208 IF ( notrans ) THEN
209 DO i = 1, n
210 tmp = 0.0e+0
211 IF ( capply ) THEN
212 DO j = 1, n
213 tmp = tmp + cabs1( a( i, j ) ) / c( j )
214 END DO
215 ELSE
216 DO j = 1, n
217 tmp = tmp + cabs1( a( i, j ) )
218 END DO
219 END IF
220 rwork( i ) = tmp
221 anorm = max( anorm, tmp )
222 END DO
223 ELSE
224 DO i = 1, n
225 tmp = 0.0e+0
226 IF ( capply ) THEN
227 DO j = 1, n
228 tmp = tmp + cabs1( a( j, i ) ) / c( j )
229 END DO
230 ELSE
231 DO j = 1, n
232 tmp = tmp + cabs1( a( j, i ) )
233 END DO
234 END IF
235 rwork( i ) = tmp
236 anorm = max( anorm, tmp )
237 END DO
238 END IF
239*
240* Quick return if possible.
241*
242 IF( n.EQ.0 ) THEN
243 cla_gercond_c = 1.0e+0
244 RETURN
245 ELSE IF( anorm .EQ. 0.0e+0 ) THEN
246 RETURN
247 END IF
248*
249* Estimate the norm of inv(op(A)).
250*
251 ainvnm = 0.0e+0
252*
253 kase = 0
254 10 CONTINUE
255 CALL clacn2( n, work( n+1 ), work, ainvnm, kase, isave )
256 IF( kase.NE.0 ) THEN
257 IF( kase.EQ.2 ) THEN
258*
259* Multiply by R.
260*
261 DO i = 1, n
262 work( i ) = work( i ) * rwork( i )
263 END DO
264*
265 IF (notrans) THEN
266 CALL cgetrs( 'No transpose', n, 1, af, ldaf, ipiv,
267 $ work, n, info )
268 ELSE
269 CALL cgetrs( 'Conjugate transpose', n, 1, af, ldaf, ipiv,
270 $ work, n, info )
271 ENDIF
272*
273* Multiply by inv(C).
274*
275 IF ( capply ) THEN
276 DO i = 1, n
277 work( i ) = work( i ) * c( i )
278 END DO
279 END IF
280 ELSE
281*
282* Multiply by inv(C**H).
283*
284 IF ( capply ) THEN
285 DO i = 1, n
286 work( i ) = work( i ) * c( i )
287 END DO
288 END IF
289*
290 IF ( notrans ) THEN
291 CALL cgetrs( 'Conjugate transpose', n, 1, af, ldaf, ipiv,
292 $ work, n, info )
293 ELSE
294 CALL cgetrs( 'No transpose', n, 1, af, ldaf, ipiv,
295 $ work, n, info )
296 END IF
297*
298* Multiply by R.
299*
300 DO i = 1, n
301 work( i ) = work( i ) * rwork( i )
302 END DO
303 END IF
304 GO TO 10
305 END IF
306*
307* Compute the estimate of the reciprocal condition number.
308*
309 IF( ainvnm .NE. 0.0e+0 )
310 $ cla_gercond_c = 1.0e+0 / ainvnm
311*
312 RETURN
313*
314* End of CLA_GERCOND_C
315*
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_c(trans, n, a, lda, af, ldaf, ipiv, c, capply, info, work, rwork)
CLA_GERCOND_C computes the infinity norm condition number of op(A)*inv(diag(c)) 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: