125 SUBROUTINE ztrexc( COMPQ, N, T, LDT, Q, LDQ, IFST, ILST, INFO )
133 INTEGER IFST, ILST, INFO, LDQ, LDT, N
136 COMPLEX*16 Q( LDQ, * ), T( LDT, * )
143 INTEGER K, M1, M2, M3
145 COMPLEX*16 SN, T11, T22, TEMP
155 INTRINSIC dconjg, max
162 wantq = lsame( compq,
'V' )
163 IF( .NOT.lsame( compq,
'N' ) .AND. .NOT.wantq )
THEN
165 ELSE IF( n.LT.0 )
THEN
167 ELSE IF( ldt.LT.max( 1, n ) )
THEN
169 ELSE IF( ldq.LT.1 .OR. ( wantq .AND. ldq.LT.max( 1, n ) ) )
THEN
171 ELSE IF(( ifst.LT.1 .OR. ifst.GT.n ).AND.( n.GT.0 ))
THEN
173 ELSE IF(( ilst.LT.1 .OR. ilst.GT.n ).AND.( n.GT.0 ))
THEN
177 CALL xerbla(
'ZTREXC', -info )
183 IF( n.LE.1 .OR. ifst.EQ.ilst )
186 IF( ifst.LT.ilst )
THEN
202 DO 10 k = ifst + m1, ilst + m2, m3
211 CALL zlartg( t( k, k+1 ), t22-t11, cs, sn, temp )
216 $
CALL zrot( n-k-1, t( k, k+2 ), ldt, t( k+1, k+2 ), ldt, cs,
218 CALL zrot( k-1, t( 1, k ), 1, t( 1, k+1 ), 1, cs,
228 CALL zrot( n, q( 1, k ), 1, q( 1, k+1 ), 1, cs,
subroutine xerbla(srname, info)
subroutine zlartg(f, g, c, s, r)
ZLARTG generates a plane rotation with real cosine and complex sine.
subroutine zrot(n, cx, incx, cy, incy, c, s)
ZROT applies a plane rotation with real cosine and complex sine to a pair of complex vectors.
subroutine ztrexc(compq, n, t, ldt, q, ldq, ifst, ilst, info)
ZTREXC