281 SUBROUTINE chgeqz( JOB, COMPQ, COMPZ, N, ILO, IHI, H, LDH, T, LDT,
282 $ ALPHA, BETA, Q, LDQ, Z, LDZ, WORK, LWORK,
290 CHARACTER COMPQ, COMPZ, JOB
291 INTEGER IHI, ILO, INFO, LDH, LDQ, LDT, LDZ, LWORK, N
295 COMPLEX ALPHA( * ), BETA( * ), H( LDH, * ),
296 $ q( ldq, * ), t( ldt, * ), work( * ),
304 PARAMETER ( CZERO = ( 0.0e+0, 0.0e+0 ),
305 $ cone = ( 1.0e+0, 0.0e+0 ) )
307 PARAMETER ( ZERO = 0.0e+0, one = 1.0e+0 )
309 parameter( half = 0.5e+0 )
312 LOGICAL ILAZR2, ILAZRO, ILQ, ILSCHR, ILZ, LQUERY
313 INTEGER ICOMPQ, ICOMPZ, IFIRST, IFRSTM, IITER, ILAST,
314 $ ilastm, in, ischur, istart, j, jc, jch, jiter,
316 REAL ABSB, ANORM, ASCALE, ATOL, BNORM, BSCALE, BTOL,
317 $ C, SAFMIN, TEMP, TEMP2, TEMPR, ULP
318 COMPLEX ABI22, AD11, AD12, AD21, AD22, CTEMP, CTEMP2,
319 $ CTEMP3, ESHIFT, S, SHIFT, SIGNBC,
326 EXTERNAL cladiv, lsame, clanhs, slamch
332 INTRINSIC abs, aimag, cmplx, conjg, max, min, real, sqrt
338 abs1( x ) = abs( real( x ) ) + abs( aimag( x ) )
344 IF( lsame( job,
'E' ) )
THEN
347 ELSE IF( lsame( job,
'S' ) )
THEN
355 IF( lsame( compq,
'N' ) )
THEN
358 ELSE IF( lsame( compq,
'V' ) )
THEN
361 ELSE IF( lsame( compq,
'I' ) )
THEN
369 IF( lsame( compz,
'N' ) )
THEN
372 ELSE IF( lsame( compz,
'V' ) )
THEN
375 ELSE IF( lsame( compz,
'I' ) )
THEN
386 work( 1 ) = max( 1, n )
387 lquery = ( lwork.EQ.-1 )
388 IF( ischur.EQ.0 )
THEN
390 ELSE IF( icompq.EQ.0 )
THEN
392 ELSE IF( icompz.EQ.0 )
THEN
394 ELSE IF( n.LT.0 )
THEN
396 ELSE IF( ilo.LT.1 )
THEN
398 ELSE IF( ihi.GT.n .OR. ihi.LT.ilo-1 )
THEN
400 ELSE IF( ldh.LT.n )
THEN
402 ELSE IF( ldt.LT.n )
THEN
404 ELSE IF( ldq.LT.1 .OR. ( ilq .AND. ldq.LT.n ) )
THEN
406 ELSE IF( ldz.LT.1 .OR. ( ilz .AND. ldz.LT.n ) )
THEN
408 ELSE IF( lwork.LT.max( 1, n ) .AND. .NOT.lquery )
THEN
412 CALL xerbla(
'CHGEQZ', -info )
414 ELSE IF( lquery )
THEN
422 work( 1 ) = cmplx( 1 )
429 $
CALL claset(
'Full', n, n, czero, cone, q, ldq )
431 $
CALL claset(
'Full', n, n, czero, cone, z, ldz )
436 safmin = slamch(
'S' )
437 ulp = slamch(
'E' )*slamch(
'B' )
438 anorm = clanhs(
'F', in, h( ilo, ilo ), ldh, rwork )
439 bnorm = clanhs(
'F', in, t( ilo, ilo ), ldt, rwork )
440 atol = max( safmin, ulp*anorm )
441 btol = max( safmin, ulp*bnorm )
442 ascale = one / max( safmin, anorm )
443 bscale = one / max( safmin, bnorm )
449 absb = abs( t( j, j ) )
450 IF( absb.GT.safmin )
THEN
451 signbc = conjg( t( j, j ) / absb )
454 CALL cscal( j-1, signbc, t( 1, j ), 1 )
455 CALL cscal( j, signbc, h( 1, j ), 1 )
457 CALL cscal( 1, signbc, h( j, j ), 1 )
460 $
CALL cscal( n, signbc, z( 1, j ), 1 )
464 alpha( j ) = h( j, j )
465 beta( j ) = t( j, j )
498 maxit = 30*( ihi-ilo+1 )
500 DO 170 jiter = 1, maxit
515 IF( ilast.EQ.ilo )
THEN
518 IF( abs1( h( ilast, ilast-1 ) ).LE.max( safmin, ulp*(
519 $ abs1( h( ilast, ilast ) ) + abs1( h( ilast-1, ilast-1 )
521 h( ilast, ilast-1 ) = czero
526 IF( abs( t( ilast, ilast ) ).LE.btol )
THEN
527 t( ilast, ilast ) = czero
533 DO 40 j = ilast - 1, ilo, -1
540 IF( abs1( h( j, j-1 ) ).LE.max( safmin, ulp*(
541 $ abs1( h( j, j ) ) + abs1( h( j-1, j-1 ) )
552 IF( abs( t( j, j ) ).LT.btol )
THEN
558 IF( .NOT.ilazro )
THEN
559 IF( abs1( h( j, j-1 ) )*( ascale*abs1( h( j+1,
560 $ j ) ) ).LE.abs1( h( j, j ) )*( ascale*atol ) )
570 IF( ilazro .OR. ilazr2 )
THEN
571 DO 20 jch = j, ilast - 1
572 ctemp = h( jch, jch )
573 CALL clartg( ctemp, h( jch+1, jch ), c, s,
575 h( jch+1, jch ) = czero
576 CALL crot( ilastm-jch, h( jch, jch+1 ), ldh,
577 $ h( jch+1, jch+1 ), ldh, c, s )
578 CALL crot( ilastm-jch, t( jch, jch+1 ), ldt,
579 $ t( jch+1, jch+1 ), ldt, c, s )
581 $
CALL crot( n, q( 1, jch ), 1, q( 1, jch+1 ), 1,
584 $ h( jch, jch-1 ) = h( jch, jch-1 )*c
586 IF( abs1( t( jch+1, jch+1 ) ).GE.btol )
THEN
587 IF( jch+1.GE.ilast )
THEN
594 t( jch+1, jch+1 ) = czero
602 DO 30 jch = j, ilast - 1
603 ctemp = t( jch, jch+1 )
604 CALL clartg( ctemp, t( jch+1, jch+1 ), c, s,
606 t( jch+1, jch+1 ) = czero
607 IF( jch.LT.ilastm-1 )
608 $
CALL crot( ilastm-jch-1, t( jch, jch+2 ), ldt,
609 $ t( jch+1, jch+2 ), ldt, c, s )
610 CALL crot( ilastm-jch+2, h( jch, jch-1 ), ldh,
611 $ h( jch+1, jch-1 ), ldh, c, s )
613 $
CALL crot( n, q( 1, jch ), 1, q( 1, jch+1 ), 1,
615 ctemp = h( jch+1, jch )
616 CALL clartg( ctemp, h( jch+1, jch-1 ), c, s,
618 h( jch+1, jch-1 ) = czero
619 CALL crot( jch+1-ifrstm, h( ifrstm, jch ), 1,
620 $ h( ifrstm, jch-1 ), 1, c, s )
621 CALL crot( jch-ifrstm, t( ifrstm, jch ), 1,
622 $ t( ifrstm, jch-1 ), 1, c, s )
624 $
CALL crot( n, z( 1, jch ), 1, z( 1, jch-1 ), 1,
629 ELSE IF( ilazro )
THEN
650 ctemp = h( ilast, ilast )
651 CALL clartg( ctemp, h( ilast, ilast-1 ), c, s,
652 $ h( ilast, ilast ) )
653 h( ilast, ilast-1 ) = czero
654 CALL crot( ilast-ifrstm, h( ifrstm, ilast ), 1,
655 $ h( ifrstm, ilast-1 ), 1, c, s )
656 CALL crot( ilast-ifrstm, t( ifrstm, ilast ), 1,
657 $ t( ifrstm, ilast-1 ), 1, c, s )
659 $
CALL crot( n, z( 1, ilast ), 1, z( 1, ilast-1 ), 1, c, s )
664 absb = abs( t( ilast, ilast ) )
665 IF( absb.GT.safmin )
THEN
666 signbc = conjg( t( ilast, ilast ) / absb )
667 t( ilast, ilast ) = absb
669 CALL cscal( ilast-ifrstm, signbc, t( ifrstm, ilast ), 1 )
670 CALL cscal( ilast+1-ifrstm, signbc, h( ifrstm, ilast ),
673 CALL cscal( 1, signbc, h( ilast, ilast ), 1 )
676 $
CALL cscal( n, signbc, z( 1, ilast ), 1 )
678 t( ilast, ilast ) = czero
680 alpha( ilast ) = h( ilast, ilast )
681 beta( ilast ) = t( ilast, ilast )
693 IF( .NOT.ilschr )
THEN
695 IF( ifrstm.GT.ilast )
707 IF( .NOT.ilschr )
THEN
717 IF( ( iiter / 10 )*10.NE.iiter )
THEN
726 u12 = ( bscale*t( ilast-1, ilast ) ) /
727 $ ( bscale*t( ilast, ilast ) )
728 ad11 = ( ascale*h( ilast-1, ilast-1 ) ) /
729 $ ( bscale*t( ilast-1, ilast-1 ) )
730 ad21 = ( ascale*h( ilast, ilast-1 ) ) /
731 $ ( bscale*t( ilast-1, ilast-1 ) )
732 ad12 = ( ascale*h( ilast-1, ilast ) ) /
733 $ ( bscale*t( ilast, ilast ) )
734 ad22 = ( ascale*h( ilast, ilast ) ) /
735 $ ( bscale*t( ilast, ilast ) )
736 abi22 = ad22 - u12*ad21
737 abi12 = ad12 - u12*ad11
740 ctemp = sqrt( abi12 )*sqrt( ad21 )
742 IF( ctemp.NE.zero )
THEN
743 x = half*( ad11-shift )
745 temp = max( temp, abs1( x ) )
746 y = temp*sqrt( ( x / temp )**2+( ctemp / temp )**2 )
747 IF( temp2.GT.zero )
THEN
748 IF( real( x / temp2 )*real( y )+
749 $ aimag( x / temp2 )*aimag( y ).LT.zero )y = -y
751 shift = shift - ctemp*cladiv( ctemp, ( x+y ) )
757 IF( ( iiter / 20 )*20.EQ.iiter .AND.
758 $ bscale*abs1(t( ilast, ilast )).GT.safmin )
THEN
759 eshift = eshift + ( ascale*h( ilast,
760 $ ilast ) )/( bscale*t( ilast, ilast ) )
762 eshift = eshift + ( ascale*h( ilast,
763 $ ilast-1 ) )/( bscale*t( ilast-1, ilast-1 ) )
770 DO 80 j = ilast - 1, ifirst + 1, -1
772 ctemp = ascale*h( j, j ) - shift*( bscale*t( j, j ) )
774 temp2 = ascale*abs1( h( j+1, j ) )
775 tempr = max( temp, temp2 )
776 IF( tempr.LT.one .AND. tempr.NE.zero )
THEN
778 temp2 = temp2 / tempr
780 IF( abs1( h( j, j-1 ) )*temp2.LE.temp*atol )
785 ctemp = ascale*h( ifirst, ifirst ) -
786 $ shift*( bscale*t( ifirst, ifirst ) )
793 ctemp2 = ascale*h( istart+1, istart )
794 CALL clartg( ctemp, ctemp2, c, s, ctemp3 )
798 DO 150 j = istart, ilast - 1
799 IF( j.GT.istart )
THEN
801 CALL clartg( ctemp, h( j+1, j-1 ), c, s, h( j, j-1 ) )
802 h( j+1, j-1 ) = czero
805 DO 100 jc = j, ilastm
806 ctemp = c*h( j, jc ) + s*h( j+1, jc )
807 h( j+1, jc ) = -conjg( s )*h( j, jc ) + c*h( j+1, jc )
809 ctemp2 = c*t( j, jc ) + s*t( j+1, jc )
810 t( j+1, jc ) = -conjg( s )*t( j, jc ) + c*t( j+1, jc )
815 ctemp = c*q( jr, j ) + conjg( s )*q( jr, j+1 )
816 q( jr, j+1 ) = -s*q( jr, j ) + c*q( jr, j+1 )
821 ctemp = t( j+1, j+1 )
822 CALL clartg( ctemp, t( j+1, j ), c, s, t( j+1, j+1 ) )
825 DO 120 jr = ifrstm, min( j+2, ilast )
826 ctemp = c*h( jr, j+1 ) + s*h( jr, j )
827 h( jr, j ) = -conjg( s )*h( jr, j+1 ) + c*h( jr, j )
830 DO 130 jr = ifrstm, j
831 ctemp = c*t( jr, j+1 ) + s*t( jr, j )
832 t( jr, j ) = -conjg( s )*t( jr, j+1 ) + c*t( jr, j )
837 ctemp = c*z( jr, j+1 ) + s*z( jr, j )
838 z( jr, j ) = -conjg( s )*z( jr, j+1 ) + c*z( jr, j )
860 DO 200 j = 1, ilo - 1
861 absb = abs( t( j, j ) )
862 IF( absb.GT.safmin )
THEN
863 signbc = conjg( t( j, j ) / absb )
866 CALL cscal( j-1, signbc, t( 1, j ), 1 )
867 CALL cscal( j, signbc, h( 1, j ), 1 )
869 CALL cscal( 1, signbc, h( j, j ), 1 )
872 $
CALL cscal( n, signbc, z( 1, j ), 1 )
876 alpha( j ) = h( j, j )
877 beta( j ) = t( j, j )
887 work( 1 ) = cmplx( n )
subroutine xerbla(srname, info)
subroutine chgeqz(job, compq, compz, n, ilo, ihi, h, ldh, t, ldt, alpha, beta, q, ldq, z, ldz, work, lwork, rwork, info)
CHGEQZ
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.
subroutine cscal(n, ca, cx, incx)
CSCAL