171 SUBROUTINE claqz1( ILQ, ILZ, K, ISTARTM, ISTOPM, IHI, A, LDA, B,
172 $ LDB, NQ, QSTART, Q, LDQ, NZ, ZSTART, Z, LDZ )
176 LOGICAL,
INTENT( IN ) :: ILQ, ILZ
177 INTEGER,
INTENT( IN ) :: K, LDA, LDB, LDQ, LDZ, ISTARTM, ISTOPM,
178 $ nq, nz, qstart, zstart, ihi
179 COMPLEX :: A( LDA, * ), B( LDB, * ), Q( LDQ, * ), Z( LDZ, * )
183 parameter( czero = ( 0.0, 0.0 ), cone = ( 1.0, 0.0 ) )
184 REAL :: ZERO, ONE, HALF
185 parameter( zero = 0.0, one = 1.0, half = 0.5 )
194 IF( k+1 .EQ. ihi )
THEN
198 CALL clartg( b( ihi, ihi ), b( ihi, ihi-1 ), c, s, temp )
200 b( ihi, ihi-1 ) = czero
201 CALL crot( ihi-istartm, b( istartm, ihi ), 1, b( istartm,
203 CALL crot( ihi-istartm+1, a( istartm, ihi ), 1, a( istartm,
206 CALL crot( nz, z( 1, ihi-zstart+1 ), 1, z( 1, ihi-1-zstart+
217 CALL clartg( b( k+1, k+1 ), b( k+1, k ), c, s, temp )
220 CALL crot( k+2-istartm+1, a( istartm, k+1 ), 1, a( istartm,
222 CALL crot( k-istartm+1, b( istartm, k+1 ), 1, b( istartm, k ),
225 CALL crot( nz, z( 1, k+1-zstart+1 ), 1, z( 1, k-zstart+1 ),
231 CALL clartg( a( k+1, k ), a( k+2, k ), c, s, temp )
234 CALL crot( istopm-k, a( k+1, k+1 ), lda, a( k+2, k+1 ), lda, c,
236 CALL crot( istopm-k, b( k+1, k+1 ), ldb, b( k+2, k+1 ), ldb, c,
239 CALL crot( nq, q( 1, k+1-qstart+1 ), 1, q( 1, k+2-qstart+
240 $ 1 ), 1, c, conjg( s ) )
subroutine claqz1(ilq, ilz, k, istartm, istopm, ihi, a, lda, b, ldb, nq, qstart, q, ldq, nz, zstart, z, ldz)
CLAQZ1
subroutine clartg(f, g, c, s, r)
CLARTG generates a plane rotation with real cosine and complex sine.
subroutine crot(n, cx, incx, cy, incy, c, s)
CROT applies a plane rotation with real cosine and complex sine to a pair of complex vectors.