246 SUBROUTINE ctrsna( JOB, HOWMNY, SELECT, N, T, LDT, VL, LDVL, VR,
247 $ LDVR, S, SEP, MM, M, WORK, LDWORK, RWORK,
255 CHARACTER HOWMNY, JOB
256 INTEGER INFO, LDT, LDVL, LDVR, LDWORK, M, MM, N
260 REAL RWORK( * ), S( * ), SEP( * )
261 COMPLEX T( LDT, * ), VL( LDVL, * ), VR( LDVR, * ),
269 PARAMETER ( ZERO = 0.0e+0, one = 1.0+0 )
272 LOGICAL SOMCON, WANTBH, WANTS, WANTSP
274 INTEGER I, IERR, IX, J, K, KASE, KS
275 REAL BIGNUM, EPS, EST, LNRM, RNRM, SCALE, SMLNUM,
288 EXTERNAL lsame, icamax, scnrm2, slamch, cdotc
294 INTRINSIC abs, aimag, max, real
300 cabs1( cdum ) = abs( real( cdum ) ) + abs( aimag( cdum ) )
306 wantbh = lsame( job,
'B' )
307 wants = lsame( job,
'E' ) .OR. wantbh
308 wantsp = lsame( job,
'V' ) .OR. wantbh
310 somcon = lsame( howmny,
'S' )
326 IF( .NOT.wants .AND. .NOT.wantsp )
THEN
328 ELSE IF( .NOT.lsame( howmny,
'A' ) .AND. .NOT.somcon )
THEN
330 ELSE IF( n.LT.0 )
THEN
332 ELSE IF( ldt.LT.max( 1, n ) )
THEN
334 ELSE IF( ldvl.LT.1 .OR. ( wants .AND. ldvl.LT.n ) )
THEN
336 ELSE IF( ldvr.LT.1 .OR. ( wants .AND. ldvr.LT.n ) )
THEN
338 ELSE IF( mm.LT.m )
THEN
340 ELSE IF( ldwork.LT.1 .OR. ( wantsp .AND. ldwork.LT.n ) )
THEN
344 CALL xerbla(
'CTRSNA', -info )
355 IF( .NOT.
SELECT( 1 ) )
361 $ sep( 1 ) = abs( t( 1, 1 ) )
368 smlnum = slamch(
'S' ) / eps
369 bignum = one / smlnum
375 IF( .NOT.
SELECT( k ) )
384 prod = cdotc( n, vr( 1, ks ), 1, vl( 1, ks ), 1 )
385 rnrm = scnrm2( n, vr( 1, ks ), 1 )
386 lnrm = scnrm2( n, vl( 1, ks ), 1 )
387 s( ks ) = abs( prod ) / ( rnrm*lnrm )
399 CALL clacpy(
'Full', n, n, t, ldt, work, ldwork )
400 CALL ctrexc(
'No Q', n, work, ldwork, dummy, 1, k, 1, ierr )
405 work( i, i ) = work( i, i ) - work( 1, 1 )
416 CALL clacn2( n-1, work( 1, n+1 ), work, est, kase, isave )
423 CALL clatrs(
'Upper',
'Conjugate transpose',
424 $
'Nonunit', normin, n-1, work( 2, 2 ),
425 $ ldwork, work, scale, rwork, ierr )
430 CALL clatrs(
'Upper',
'No transpose',
'Nonunit',
431 $ normin, n-1, work( 2, 2 ), ldwork, work,
432 $ scale, rwork, ierr )
435 IF( scale.NE.one )
THEN
440 ix = icamax( n-1, work, 1 )
441 xnorm = cabs1( work( ix, 1 ) )
442 IF( scale.LT.xnorm*smlnum .OR. scale.EQ.zero )
444 CALL csrscl( n, scale, work, 1 )
449 sep( ks ) = one / max( est, smlnum )
subroutine xerbla(srname, info)
subroutine clacn2(n, v, x, est, kase, isave)
CLACN2 estimates the 1-norm of a square matrix, using reverse communication for evaluating matrix-vec...
subroutine clacpy(uplo, m, n, a, lda, b, ldb)
CLACPY copies all or part of one two-dimensional array to another.
subroutine clatrs(uplo, trans, diag, normin, n, a, lda, x, scale, cnorm, info)
CLATRS solves a triangular system of equations with the scale factor set to prevent overflow.
subroutine csrscl(n, sa, sx, incx)
CSRSCL multiplies a vector by the reciprocal of a real scalar.
subroutine ctrexc(compq, n, t, ldt, q, ldq, ifst, ilst, info)
CTREXC
subroutine ctrsna(job, howmny, select, n, t, ldt, vl, ldvl, vr, ldvr, s, sep, mm, m, work, ldwork, rwork, info)
CTRSNA