202 SUBROUTINE cgghrd( COMPQ, COMPZ, N, ILO, IHI, A, LDA, B, LDB, Q,
203 $ LDQ, Z, LDZ, INFO )
210 CHARACTER COMPQ, COMPZ
211 INTEGER IHI, ILO, INFO, LDA, LDB, LDQ, LDZ, N
214 COMPLEX A( LDA, * ), B( LDB, * ), Q( LDQ, * ),
222 parameter( cone = ( 1.0e+0, 0.0e+0 ),
223 $ czero = ( 0.0e+0, 0.0e+0 ) )
227 INTEGER ICOMPQ, ICOMPZ, JCOL, JROW
245 IF( lsame( compq,
'N' ) )
THEN
248 ELSE IF( lsame( compq,
'V' ) )
THEN
251 ELSE IF( lsame( compq,
'I' ) )
THEN
260 IF( lsame( compz,
'N' ) )
THEN
263 ELSE IF( lsame( compz,
'V' ) )
THEN
266 ELSE IF( lsame( compz,
'I' ) )
THEN
276 IF( icompq.LE.0 )
THEN
278 ELSE IF( icompz.LE.0 )
THEN
280 ELSE IF( n.LT.0 )
THEN
282 ELSE IF( ilo.LT.1 )
THEN
284 ELSE IF( ihi.GT.n .OR. ihi.LT.ilo-1 )
THEN
286 ELSE IF( lda.LT.max( 1, n ) )
THEN
288 ELSE IF( ldb.LT.max( 1, n ) )
THEN
290 ELSE IF( ( ilq .AND. ldq.LT.n ) .OR. ldq.LT.1 )
THEN
292 ELSE IF( ( ilz .AND. ldz.LT.n ) .OR. ldz.LT.1 )
THEN
296 CALL xerbla(
'CGGHRD', -info )
303 $
CALL claset(
'Full', n, n, czero, cone, q, ldq )
305 $
CALL claset(
'Full', n, n, czero, cone, z, ldz )
314 DO 20 jcol = 1, n - 1
315 DO 10 jrow = jcol + 1, n
316 b( jrow, jcol ) = czero
322 DO 40 jcol = ilo, ihi - 2
324 DO 30 jrow = ihi, jcol + 2, -1
328 ctemp = a( jrow-1, jcol )
329 CALL clartg( ctemp, a( jrow, jcol ), c, s,
330 $ a( jrow-1, jcol ) )
331 a( jrow, jcol ) = czero
332 CALL crot( n-jcol, a( jrow-1, jcol+1 ), lda,
333 $ a( jrow, jcol+1 ), lda, c, s )
334 CALL crot( n+2-jrow, b( jrow-1, jrow-1 ), ldb,
335 $ b( jrow, jrow-1 ), ldb, c, s )
337 $
CALL crot( n, q( 1, jrow-1 ), 1, q( 1, jrow ), 1, c,
342 ctemp = b( jrow, jrow )
343 CALL clartg( ctemp, b( jrow, jrow-1 ), c, s,
345 b( jrow, jrow-1 ) = czero
346 CALL crot( ihi, a( 1, jrow ), 1, a( 1, jrow-1 ), 1, c, s )
347 CALL crot( jrow-1, b( 1, jrow ), 1, b( 1, jrow-1 ), 1, c,
350 $
CALL crot( n, z( 1, jrow ), 1, z( 1, jrow-1 ), 1, c, s )
subroutine xerbla(srname, info)
subroutine cgghrd(compq, compz, n, ilo, ihi, a, lda, b, ldb, q, ldq, z, ldz, info)
CGGHRD
subroutine clartg(f, g, c, s, r)
CLARTG generates a plane rotation with real cosine and complex sine.
subroutine claset(uplo, m, n, alpha, beta, a, lda)
CLASET initializes the off-diagonal elements and the diagonal elements of a matrix to given values.
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.