214 SUBROUTINE cggev3( JOBVL, JOBVR, N, A, LDA, B, LDB, ALPHA, BETA,
215 $ VL, LDVL, VR, LDVR, WORK, LWORK, RWORK, INFO )
222 CHARACTER JOBVL, JOBVR
223 INTEGER INFO, LDA, LDB, LDVL, LDVR, LWORK, N
227 COMPLEX A( LDA, * ), ALPHA( * ), B( LDB, * ),
228 $ beta( * ), vl( ldvl, * ), vr( ldvr, * ),
236 parameter( zero = 0.0e0, one = 1.0e0 )
238 parameter( czero = ( 0.0e0, 0.0e0 ),
239 $ cone = ( 1.0e0, 0.0e0 ) )
242 LOGICAL ILASCL, ILBSCL, ILV, ILVL, ILVR, LQUERY
244 INTEGER ICOLS, IERR, IHI, IJOBVL, IJOBVR, ILEFT, ILO,
245 $ in, iright, irows, irwrk, itau, iwrk, jc, jr,
247 REAL ANRM, ANRMTO, BIGNUM, BNRM, BNRMTO, EPS,
261 EXTERNAL lsame, clange, slamch
264 INTRINSIC abs, aimag, max, real, sqrt
270 abs1( x ) = abs( real( x ) ) + abs( aimag( x ) )
276 IF( lsame( jobvl,
'N' ) )
THEN
279 ELSE IF( lsame( jobvl,
'V' ) )
THEN
287 IF( lsame( jobvr,
'N' ) )
THEN
290 ELSE IF( lsame( jobvr,
'V' ) )
THEN
302 lquery = ( lwork.EQ.-1 )
303 IF( ijobvl.LE.0 )
THEN
305 ELSE IF( ijobvr.LE.0 )
THEN
307 ELSE IF( n.LT.0 )
THEN
309 ELSE IF( lda.LT.max( 1, n ) )
THEN
311 ELSE IF( ldb.LT.max( 1, n ) )
THEN
313 ELSE IF( ldvl.LT.1 .OR. ( ilvl .AND. ldvl.LT.n ) )
THEN
315 ELSE IF( ldvr.LT.1 .OR. ( ilvr .AND. ldvr.LT.n ) )
THEN
317 ELSE IF( lwork.LT.max( 1, 2*n ) .AND. .NOT.lquery )
THEN
324 CALL cgeqrf( n, n, b, ldb, work, work, -1, ierr )
325 lwkopt = max( n, n+int( work( 1 ) ) )
326 CALL cunmqr(
'L',
'C', n, n, n, b, ldb, work, a, lda, work,
328 lwkopt = max( lwkopt, n+int( work( 1 ) ) )
330 CALL cungqr( n, n, n, vl, ldvl, work, work, -1, ierr )
331 lwkopt = max( lwkopt, n+int( work( 1 ) ) )
334 CALL cgghd3( jobvl, jobvr, n, 1, n, a, lda, b, ldb, vl,
335 $ ldvl, vr, ldvr, work, -1, ierr )
336 lwkopt = max( lwkopt, n+int( work( 1 ) ) )
337 CALL claqz0(
'S', jobvl, jobvr, n, 1, n, a, lda, b, ldb,
338 $ alpha, beta, vl, ldvl, vr, ldvr, work, -1,
340 lwkopt = max( lwkopt, n+int( work( 1 ) ) )
342 CALL cgghd3(
'N',
'N', n, 1, n, a, lda, b, ldb, vl, ldvl,
343 $ vr, ldvr, work, -1, ierr )
344 lwkopt = max( lwkopt, n+int( work( 1 ) ) )
345 CALL claqz0(
'E', jobvl, jobvr, n, 1, n, a, lda, b, ldb,
346 $ alpha, beta, vl, ldvl, vr, ldvr, work, -1,
348 lwkopt = max( lwkopt, n+int( work( 1 ) ) )
350 work( 1 ) = cmplx( lwkopt )
354 CALL xerbla(
'CGGEV3 ', -info )
356 ELSE IF( lquery )
THEN
367 eps = slamch(
'E' )*slamch(
'B' )
368 smlnum = slamch(
'S' )
369 bignum = one / smlnum
370 smlnum = sqrt( smlnum ) / eps
371 bignum = one / smlnum
375 anrm = clange(
'M', n, n, a, lda, rwork )
377 IF( anrm.GT.zero .AND. anrm.LT.smlnum )
THEN
380 ELSE IF( anrm.GT.bignum )
THEN
385 $
CALL clascl(
'G', 0, 0, anrm, anrmto, n, n, a, lda, ierr )
389 bnrm = clange(
'M', n, n, b, ldb, rwork )
391 IF( bnrm.GT.zero .AND. bnrm.LT.smlnum )
THEN
394 ELSE IF( bnrm.GT.bignum )
THEN
399 $
CALL clascl(
'G', 0, 0, bnrm, bnrmto, n, n, b, ldb, ierr )
406 CALL cggbal(
'P', n, a, lda, b, ldb, ilo, ihi, rwork( ileft ),
407 $ rwork( iright ), rwork( irwrk ), ierr )
411 irows = ihi + 1 - ilo
419 CALL cgeqrf( irows, icols, b( ilo, ilo ), ldb, work( itau ),
420 $ work( iwrk ), lwork+1-iwrk, ierr )
424 CALL cunmqr(
'L',
'C', irows, icols, irows, b( ilo, ilo ), ldb,
425 $ work( itau ), a( ilo, ilo ), lda, work( iwrk ),
426 $ lwork+1-iwrk, ierr )
431 CALL claset(
'Full', n, n, czero, cone, vl, ldvl )
432 IF( irows.GT.1 )
THEN
433 CALL clacpy(
'L', irows-1, irows-1, b( ilo+1, ilo ), ldb,
434 $ vl( ilo+1, ilo ), ldvl )
436 CALL cungqr( irows, irows, irows, vl( ilo, ilo ), ldvl,
437 $ work( itau ), work( iwrk ), lwork+1-iwrk, ierr )
443 $
CALL claset(
'Full', n, n, czero, cone, vr, ldvr )
451 CALL cgghd3( jobvl, jobvr, n, ilo, ihi, a, lda, b, ldb, vl,
452 $ ldvl, vr, ldvr, work( iwrk ), lwork+1-iwrk,
455 CALL cgghd3(
'N',
'N', irows, 1, irows, a( ilo, ilo ), lda,
456 $ b( ilo, ilo ), ldb, vl, ldvl, vr, ldvr,
457 $ work( iwrk ), lwork+1-iwrk, ierr )
469 CALL claqz0( chtemp, jobvl, jobvr, n, ilo, ihi, a, lda, b, ldb,
470 $ alpha, beta, vl, ldvl, vr, ldvr, work( iwrk ),
471 $ lwork+1-iwrk, rwork( irwrk ), 0, ierr )
473 IF( ierr.GT.0 .AND. ierr.LE.n )
THEN
475 ELSE IF( ierr.GT.n .AND. ierr.LE.2*n )
THEN
496 CALL ctgevc( chtemp,
'B', ldumma, n, a, lda, b, ldb, vl, ldvl,
497 $ vr, ldvr, n, in, work( iwrk ), rwork( irwrk ),
507 CALL cggbak(
'P',
'L', n, ilo, ihi, rwork( ileft ),
508 $ rwork( iright ), n, vl, ldvl, ierr )
512 temp = max( temp, abs1( vl( jr, jc ) ) )
518 vl( jr, jc ) = vl( jr, jc )*temp
523 CALL cggbak(
'P',
'R', n, ilo, ihi, rwork( ileft ),
524 $ rwork( iright ), n, vr, ldvr, ierr )
528 temp = max( temp, abs1( vr( jr, jc ) ) )
534 vr( jr, jc ) = vr( jr, jc )*temp
545 $
CALL clascl(
'G', 0, 0, anrmto, anrm, n, 1, alpha, n, ierr )
548 $
CALL clascl(
'G', 0, 0, bnrmto, bnrm, n, 1, beta, n, ierr )
550 work( 1 ) = cmplx( lwkopt )
subroutine xerbla(srname, info)
subroutine cgeqrf(m, n, a, lda, tau, work, lwork, info)
CGEQRF
subroutine cggbak(job, side, n, ilo, ihi, lscale, rscale, m, v, ldv, info)
CGGBAK
subroutine cggbal(job, n, a, lda, b, ldb, ilo, ihi, lscale, rscale, work, info)
CGGBAL
subroutine cggev3(jobvl, jobvr, n, a, lda, b, ldb, alpha, beta, vl, ldvl, vr, ldvr, work, lwork, rwork, info)
CGGEV3 computes the eigenvalues and, optionally, the left and/or right eigenvectors for GE matrices (...
subroutine cgghd3(compq, compz, n, ilo, ihi, a, lda, b, ldb, q, ldq, z, ldz, work, lwork, info)
CGGHD3
subroutine clacpy(uplo, m, n, a, lda, b, ldb)
CLACPY copies all or part of one two-dimensional array to another.
recursive subroutine claqz0(wants, wantq, wantz, n, ilo, ihi, a, lda, b, ldb, alpha, beta, q, ldq, z, ldz, work, lwork, rwork, rec, info)
CLAQZ0
subroutine clascl(type, kl, ku, cfrom, cto, m, n, a, lda, info)
CLASCL multiplies a general rectangular matrix by a real scalar defined as cto/cfrom.
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 ctgevc(side, howmny, select, n, s, lds, p, ldp, vl, ldvl, vr, ldvr, mm, m, work, rwork, info)
CTGEVC
subroutine cungqr(m, n, k, a, lda, tau, work, lwork, info)
CUNGQR
subroutine cunmqr(side, trans, m, n, k, a, lda, tau, c, ldc, work, lwork, info)
CUNMQR