LAPACK  3.6.1
LAPACK: Linear Algebra PACKage
subroutine zdrgvx ( integer  NSIZE,
double precision  THRESH,
integer  NIN,
integer  NOUT,
complex*16, dimension( lda, * )  A,
integer  LDA,
complex*16, dimension( lda, * )  B,
complex*16, dimension( lda, * )  AI,
complex*16, dimension( lda, * )  BI,
complex*16, dimension( * )  ALPHA,
complex*16, dimension( * )  BETA,
complex*16, dimension( lda, * )  VL,
complex*16, dimension( lda, * )  VR,
integer  ILO,
integer  IHI,
double precision, dimension( * )  LSCALE,
double precision, dimension( * )  RSCALE,
double precision, dimension( * )  S,
double precision, dimension( * )  DTRU,
double precision, dimension( * )  DIF,
double precision, dimension( * )  DIFTRU,
complex*16, dimension( * )  WORK,
integer  LWORK,
double precision, dimension( * )  RWORK,
integer, dimension( * )  IWORK,
integer  LIWORK,
double precision, dimension( 4 )  RESULT,
logical, dimension( * )  BWORK,
integer  INFO 
)

ZDRGVX

Purpose:
 ZDRGVX checks the nonsymmetric generalized eigenvalue problem
 expert driver ZGGEVX.

 ZGGEVX computes the generalized eigenvalues, (optionally) the left
 and/or right eigenvectors, (optionally) computes a balancing
 transformation to improve the conditioning, and (optionally)
 reciprocal condition numbers for the eigenvalues and eigenvectors.

 When ZDRGVX is called with NSIZE > 0, two types of test matrix pairs
 are generated by the subroutine DLATM6 and test the driver ZGGEVX.
 The test matrices have the known exact condition numbers for
 eigenvalues. For the condition numbers of the eigenvectors
 corresponding the first and last eigenvalues are also know
 ``exactly'' (see ZLATM6).
 For each matrix pair, the following tests will be performed and
 compared with the threshold THRESH.

 (1) max over all left eigenvalue/-vector pairs (beta/alpha,l) of

    | l**H * (beta A - alpha B) | / ( ulp max( |beta A|, |alpha B| ) )

     where l**H is the conjugate tranpose of l.

 (2) max over all right eigenvalue/-vector pairs (beta/alpha,r) of

       | (beta A - alpha B) r | / ( ulp max( |beta A|, |alpha B| ) )

 (3) The condition number S(i) of eigenvalues computed by ZGGEVX
     differs less than a factor THRESH from the exact S(i) (see
     ZLATM6).

 (4) DIF(i) computed by ZTGSNA differs less than a factor 10*THRESH
     from the exact value (for the 1st and 5th vectors only).

 Test Matrices
 =============

 Two kinds of test matrix pairs
          (A, B) = inverse(YH) * (Da, Db) * inverse(X)
 are used in the tests:

 1: Da = 1+a   0    0    0    0    Db = 1   0   0   0   0
          0   2+a   0    0    0         0   1   0   0   0
          0    0   3+a   0    0         0   0   1   0   0
          0    0    0   4+a   0         0   0   0   1   0
          0    0    0    0   5+a ,      0   0   0   0   1 , and

 2: Da =  1   -1    0    0    0    Db = 1   0   0   0   0
          1    1    0    0    0         0   1   0   0   0
          0    0    1    0    0         0   0   1   0   0
          0    0    0   1+a  1+b        0   0   0   1   0
          0    0    0  -1-b  1+a ,      0   0   0   0   1 .

 In both cases the same inverse(YH) and inverse(X) are used to compute
 (A, B), giving the exact eigenvectors to (A,B) as (YH, X):

 YH:  =  1    0   -y    y   -y    X =  1   0  -x  -x   x
         0    1   -y    y   -y         0   1   x  -x  -x
         0    0    1    0    0         0   0   1   0   0
         0    0    0    1    0         0   0   0   1   0
         0    0    0    0    1,        0   0   0   0   1 , where

 a, b, x and y will have all values independently of each other from
 { sqrt(sqrt(ULP)),  0.1,  1,  10,  1/sqrt(sqrt(ULP)) }.
Parameters
[in]NSIZE
          NSIZE is INTEGER
          The number of sizes of matrices to use.  NSIZE must be at
          least zero. If it is zero, no randomly generated matrices
          are tested, but any test matrices read from NIN will be
          tested.  If it is not zero, then N = 5.
[in]THRESH
          THRESH is DOUBLE PRECISION
          A test will count as "failed" if the "error", computed as
          described above, exceeds THRESH.  Note that the error
          is scaled to be O(1), so THRESH should be a reasonably
          small multiple of 1, e.g., 10 or 100.  In particular,
          it should not depend on the precision (single vs. double)
          or the size of the matrix.  It must be at least zero.
[in]NIN
          NIN is INTEGER
          The FORTRAN unit number for reading in the data file of
          problems to solve.
[in]NOUT
          NOUT is INTEGER
          The FORTRAN unit number for printing out error messages
          (e.g., if a routine returns IINFO not equal to 0.)
[out]A
          A is COMPLEX*16 array, dimension (LDA, NSIZE)
          Used to hold the matrix whose eigenvalues are to be
          computed.  On exit, A contains the last matrix actually used.
[in]LDA
          LDA is INTEGER
          The leading dimension of A, B, AI, BI, Ao, and Bo.
          It must be at least 1 and at least NSIZE.
[out]B
          B is COMPLEX*16 array, dimension (LDA, NSIZE)
          Used to hold the matrix whose eigenvalues are to be
          computed.  On exit, B contains the last matrix actually used.
[out]AI
          AI is COMPLEX*16 array, dimension (LDA, NSIZE)
          Copy of A, modified by ZGGEVX.
[out]BI
          BI is COMPLEX*16 array, dimension (LDA, NSIZE)
          Copy of B, modified by ZGGEVX.
[out]ALPHA
          ALPHA is COMPLEX*16 array, dimension (NSIZE)
[out]BETA
          BETA is COMPLEX*16 array, dimension (NSIZE)

          On exit, ALPHA/BETA are the eigenvalues.
[out]VL
          VL is COMPLEX*16 array, dimension (LDA, NSIZE)
          VL holds the left eigenvectors computed by ZGGEVX.
[out]VR
          VR is COMPLEX*16 array, dimension (LDA, NSIZE)
          VR holds the right eigenvectors computed by ZGGEVX.
[out]ILO
                ILO is INTEGER
[out]IHI
                IHI is INTEGER
[out]LSCALE
                LSCALE is DOUBLE PRECISION array, dimension (N)
[out]RSCALE
                RSCALE is DOUBLE PRECISION array, dimension (N)
[out]S
                S is DOUBLE PRECISION array, dimension (N)
[out]DTRU
                DTRU is DOUBLE PRECISION array, dimension (N)
[out]DIF
                DIF is DOUBLE PRECISION array, dimension (N)
[out]DIFTRU
                DIFTRU is DOUBLE PRECISION array, dimension (N)
[out]WORK
          WORK is COMPLEX*16 array, dimension (LWORK)
[in]LWORK
          LWORK is INTEGER
          Leading dimension of WORK.  LWORK >= 2*N*N + 2*N
[out]RWORK
          RWORK is DOUBLE PRECISION array, dimension (6*N)
[out]IWORK
          IWORK is INTEGER array, dimension (LIWORK)
[in]LIWORK
          LIWORK is INTEGER
          Leading dimension of IWORK.  LIWORK >= N+2.
[out]RESULT
                RESULT is DOUBLE PRECISION array, dimension (4)
[out]BWORK
          BWORK is LOGICAL array, dimension (N)
[out]INFO
          INFO is INTEGER
          = 0:  successful exit
          < 0:  if INFO = -i, the i-th argument had an illegal value.
          > 0:  A routine returned an error code.
Author
Univ. of Tennessee
Univ. of California Berkeley
Univ. of Colorado Denver
NAG Ltd.
Date
June 2016

Definition at line 299 of file zdrgvx.f.

299 *
300 * -- LAPACK test routine (version 3.6.1) --
301 * -- LAPACK is a software package provided by Univ. of Tennessee, --
302 * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
303 * June 2016
304 *
305 * .. Scalar Arguments ..
306  INTEGER ihi, ilo, info, lda, liwork, lwork, nin, nout,
307  $ nsize
308  DOUBLE PRECISION thresh
309 * ..
310 * .. Array Arguments ..
311  LOGICAL bwork( * )
312  INTEGER iwork( * )
313  DOUBLE PRECISION dif( * ), diftru( * ), dtru( * ), lscale( * ),
314  $ result( 4 ), rscale( * ), rwork( * ), s( * )
315  COMPLEX*16 a( lda, * ), ai( lda, * ), alpha( * ),
316  $ b( lda, * ), beta( * ), bi( lda, * ),
317  $ vl( lda, * ), vr( lda, * ), work( * )
318 * ..
319 *
320 * =====================================================================
321 *
322 * .. Parameters ..
323  DOUBLE PRECISION zero, one, ten, tnth, half
324  parameter ( zero = 0.0d+0, one = 1.0d+0, ten = 1.0d+1,
325  $ tnth = 1.0d-1, half = 0.5d+0 )
326 * ..
327 * .. Local Scalars ..
328  INTEGER i, iptype, iwa, iwb, iwx, iwy, j, linfo,
329  $ maxwrk, minwrk, n, nerrs, nmax, nptknt, ntestt
330  DOUBLE PRECISION abnorm, anorm, bnorm, ratio1, ratio2, thrsh2,
331  $ ulp, ulpinv
332 * ..
333 * .. Local Arrays ..
334  COMPLEX*16 weight( 5 )
335 * ..
336 * .. External Functions ..
337  INTEGER ilaenv
338  DOUBLE PRECISION dlamch, zlange
339  EXTERNAL ilaenv, dlamch, zlange
340 * ..
341 * .. External Subroutines ..
342  EXTERNAL alasvm, xerbla, zget52, zggevx, zlacpy, zlatm6
343 * ..
344 * .. Intrinsic Functions ..
345  INTRINSIC abs, dcmplx, max, sqrt
346 * ..
347 * .. Executable Statements ..
348 *
349 * Check for errors
350 *
351  info = 0
352 *
353  nmax = 5
354 *
355  IF( nsize.LT.0 ) THEN
356  info = -1
357  ELSE IF( thresh.LT.zero ) THEN
358  info = -2
359  ELSE IF( nin.LE.0 ) THEN
360  info = -3
361  ELSE IF( nout.LE.0 ) THEN
362  info = -4
363  ELSE IF( lda.LT.1 .OR. lda.LT.nmax ) THEN
364  info = -6
365  ELSE IF( liwork.LT.nmax+2 ) THEN
366  info = -26
367  END IF
368 *
369 * Compute workspace
370 * (Note: Comments in the code beginning "Workspace:" describe the
371 * minimal amount of workspace needed at that point in the code,
372 * as well as the preferred amount for good performance.
373 * NB refers to the optimal block size for the immediately
374 * following subroutine, as returned by ILAENV.)
375 *
376  minwrk = 1
377  IF( info.EQ.0 .AND. lwork.GE.1 ) THEN
378  minwrk = 2*nmax*( nmax+1 )
379  maxwrk = nmax*( 1+ilaenv( 1, 'ZGEQRF', ' ', nmax, 1, nmax,
380  $ 0 ) )
381  maxwrk = max( maxwrk, 2*nmax*( nmax+1 ) )
382  work( 1 ) = maxwrk
383  END IF
384 *
385  IF( lwork.LT.minwrk )
386  $ info = -23
387 *
388  IF( info.NE.0 ) THEN
389  CALL xerbla( 'ZDRGVX', -info )
390  RETURN
391  END IF
392 *
393  n = 5
394  ulp = dlamch( 'P' )
395  ulpinv = one / ulp
396  thrsh2 = ten*thresh
397  nerrs = 0
398  nptknt = 0
399  ntestt = 0
400 *
401  IF( nsize.EQ.0 )
402  $ GO TO 90
403 *
404 * Parameters used for generating test matrices.
405 *
406  weight( 1 ) = dcmplx( tnth, zero )
407  weight( 2 ) = dcmplx( half, zero )
408  weight( 3 ) = one
409  weight( 4 ) = one / weight( 2 )
410  weight( 5 ) = one / weight( 1 )
411 *
412  DO 80 iptype = 1, 2
413  DO 70 iwa = 1, 5
414  DO 60 iwb = 1, 5
415  DO 50 iwx = 1, 5
416  DO 40 iwy = 1, 5
417 *
418 * generated a pair of test matrix
419 *
420  CALL zlatm6( iptype, 5, a, lda, b, vr, lda, vl,
421  $ lda, weight( iwa ), weight( iwb ),
422  $ weight( iwx ), weight( iwy ), dtru,
423  $ diftru )
424 *
425 * Compute eigenvalues/eigenvectors of (A, B).
426 * Compute eigenvalue/eigenvector condition numbers
427 * using computed eigenvectors.
428 *
429  CALL zlacpy( 'F', n, n, a, lda, ai, lda )
430  CALL zlacpy( 'F', n, n, b, lda, bi, lda )
431 *
432  CALL zggevx( 'N', 'V', 'V', 'B', n, ai, lda, bi,
433  $ lda, alpha, beta, vl, lda, vr, lda,
434  $ ilo, ihi, lscale, rscale, anorm,
435  $ bnorm, s, dif, work, lwork, rwork,
436  $ iwork, bwork, linfo )
437  IF( linfo.NE.0 ) THEN
438  WRITE( nout, fmt = 9999 )'ZGGEVX', linfo, n,
439  $ iptype, iwa, iwb, iwx, iwy
440  GO TO 30
441  END IF
442 *
443 * Compute the norm(A, B)
444 *
445  CALL zlacpy( 'Full', n, n, ai, lda, work, n )
446  CALL zlacpy( 'Full', n, n, bi, lda, work( n*n+1 ),
447  $ n )
448  abnorm = zlange( 'Fro', n, 2*n, work, n, rwork )
449 *
450 * Tests (1) and (2)
451 *
452  result( 1 ) = zero
453  CALL zget52( .true., n, a, lda, b, lda, vl, lda,
454  $ alpha, beta, work, rwork,
455  $ result( 1 ) )
456  IF( result( 2 ).GT.thresh ) THEN
457  WRITE( nout, fmt = 9998 )'Left', 'ZGGEVX',
458  $ result( 2 ), n, iptype, iwa, iwb, iwx, iwy
459  END IF
460 *
461  result( 2 ) = zero
462  CALL zget52( .false., n, a, lda, b, lda, vr, lda,
463  $ alpha, beta, work, rwork,
464  $ result( 2 ) )
465  IF( result( 3 ).GT.thresh ) THEN
466  WRITE( nout, fmt = 9998 )'Right', 'ZGGEVX',
467  $ result( 3 ), n, iptype, iwa, iwb, iwx, iwy
468  END IF
469 *
470 * Test (3)
471 *
472  result( 3 ) = zero
473  DO 10 i = 1, n
474  IF( s( i ).EQ.zero ) THEN
475  IF( dtru( i ).GT.abnorm*ulp )
476  $ result( 3 ) = ulpinv
477  ELSE IF( dtru( i ).EQ.zero ) THEN
478  IF( s( i ).GT.abnorm*ulp )
479  $ result( 3 ) = ulpinv
480  ELSE
481  rwork( i ) = max( abs( dtru( i ) / s( i ) ),
482  $ abs( s( i ) / dtru( i ) ) )
483  result( 3 ) = max( result( 3 ), rwork( i ) )
484  END IF
485  10 CONTINUE
486 *
487 * Test (4)
488 *
489  result( 4 ) = zero
490  IF( dif( 1 ).EQ.zero ) THEN
491  IF( diftru( 1 ).GT.abnorm*ulp )
492  $ result( 4 ) = ulpinv
493  ELSE IF( diftru( 1 ).EQ.zero ) THEN
494  IF( dif( 1 ).GT.abnorm*ulp )
495  $ result( 4 ) = ulpinv
496  ELSE IF( dif( 5 ).EQ.zero ) THEN
497  IF( diftru( 5 ).GT.abnorm*ulp )
498  $ result( 4 ) = ulpinv
499  ELSE IF( diftru( 5 ).EQ.zero ) THEN
500  IF( dif( 5 ).GT.abnorm*ulp )
501  $ result( 4 ) = ulpinv
502  ELSE
503  ratio1 = max( abs( diftru( 1 ) / dif( 1 ) ),
504  $ abs( dif( 1 ) / diftru( 1 ) ) )
505  ratio2 = max( abs( diftru( 5 ) / dif( 5 ) ),
506  $ abs( dif( 5 ) / diftru( 5 ) ) )
507  result( 4 ) = max( ratio1, ratio2 )
508  END IF
509 *
510  ntestt = ntestt + 4
511 *
512 * Print out tests which fail.
513 *
514  DO 20 j = 1, 4
515  IF( ( result( j ).GE.thrsh2 .AND. j.GE.4 ) .OR.
516  $ ( result( j ).GE.thresh .AND. j.LE.3 ) )
517  $ THEN
518 *
519 * If this is the first test to fail,
520 * print a header to the data file.
521 *
522  IF( nerrs.EQ.0 ) THEN
523  WRITE( nout, fmt = 9997 )'ZXV'
524 *
525 * Print out messages for built-in examples
526 *
527 * Matrix types
528 *
529  WRITE( nout, fmt = 9995 )
530  WRITE( nout, fmt = 9994 )
531  WRITE( nout, fmt = 9993 )
532 *
533 * Tests performed
534 *
535  WRITE( nout, fmt = 9992 )'''',
536  $ 'transpose', ''''
537 *
538  END IF
539  nerrs = nerrs + 1
540  IF( result( j ).LT.10000.0d0 ) THEN
541  WRITE( nout, fmt = 9991 )iptype, iwa,
542  $ iwb, iwx, iwy, j, result( j )
543  ELSE
544  WRITE( nout, fmt = 9990 )iptype, iwa,
545  $ iwb, iwx, iwy, j, result( j )
546  END IF
547  END IF
548  20 CONTINUE
549 *
550  30 CONTINUE
551 *
552  40 CONTINUE
553  50 CONTINUE
554  60 CONTINUE
555  70 CONTINUE
556  80 CONTINUE
557 *
558  GO TO 150
559 *
560  90 CONTINUE
561 *
562 * Read in data from file to check accuracy of condition estimation
563 * Read input data until N=0
564 *
565  READ( nin, fmt = *, end = 150 )n
566  IF( n.EQ.0 )
567  $ GO TO 150
568  DO 100 i = 1, n
569  READ( nin, fmt = * )( a( i, j ), j = 1, n )
570  100 CONTINUE
571  DO 110 i = 1, n
572  READ( nin, fmt = * )( b( i, j ), j = 1, n )
573  110 CONTINUE
574  READ( nin, fmt = * )( dtru( i ), i = 1, n )
575  READ( nin, fmt = * )( diftru( i ), i = 1, n )
576 *
577  nptknt = nptknt + 1
578 *
579 * Compute eigenvalues/eigenvectors of (A, B).
580 * Compute eigenvalue/eigenvector condition numbers
581 * using computed eigenvectors.
582 *
583  CALL zlacpy( 'F', n, n, a, lda, ai, lda )
584  CALL zlacpy( 'F', n, n, b, lda, bi, lda )
585 *
586  CALL zggevx( 'N', 'V', 'V', 'B', n, ai, lda, bi, lda, alpha, beta,
587  $ vl, lda, vr, lda, ilo, ihi, lscale, rscale, anorm,
588  $ bnorm, s, dif, work, lwork, rwork, iwork, bwork,
589  $ linfo )
590 *
591  IF( linfo.NE.0 ) THEN
592  WRITE( nout, fmt = 9987 )'ZGGEVX', linfo, n, nptknt
593  GO TO 140
594  END IF
595 *
596 * Compute the norm(A, B)
597 *
598  CALL zlacpy( 'Full', n, n, ai, lda, work, n )
599  CALL zlacpy( 'Full', n, n, bi, lda, work( n*n+1 ), n )
600  abnorm = zlange( 'Fro', n, 2*n, work, n, rwork )
601 *
602 * Tests (1) and (2)
603 *
604  result( 1 ) = zero
605  CALL zget52( .true., n, a, lda, b, lda, vl, lda, alpha, beta,
606  $ work, rwork, result( 1 ) )
607  IF( result( 2 ).GT.thresh ) THEN
608  WRITE( nout, fmt = 9986 )'Left', 'ZGGEVX', result( 2 ), n,
609  $ nptknt
610  END IF
611 *
612  result( 2 ) = zero
613  CALL zget52( .false., n, a, lda, b, lda, vr, lda, alpha, beta,
614  $ work, rwork, result( 2 ) )
615  IF( result( 3 ).GT.thresh ) THEN
616  WRITE( nout, fmt = 9986 )'Right', 'ZGGEVX', result( 3 ), n,
617  $ nptknt
618  END IF
619 *
620 * Test (3)
621 *
622  result( 3 ) = zero
623  DO 120 i = 1, n
624  IF( s( i ).EQ.zero ) THEN
625  IF( dtru( i ).GT.abnorm*ulp )
626  $ result( 3 ) = ulpinv
627  ELSE IF( dtru( i ).EQ.zero ) THEN
628  IF( s( i ).GT.abnorm*ulp )
629  $ result( 3 ) = ulpinv
630  ELSE
631  rwork( i ) = max( abs( dtru( i ) / s( i ) ),
632  $ abs( s( i ) / dtru( i ) ) )
633  result( 3 ) = max( result( 3 ), rwork( i ) )
634  END IF
635  120 CONTINUE
636 *
637 * Test (4)
638 *
639  result( 4 ) = zero
640  IF( dif( 1 ).EQ.zero ) THEN
641  IF( diftru( 1 ).GT.abnorm*ulp )
642  $ result( 4 ) = ulpinv
643  ELSE IF( diftru( 1 ).EQ.zero ) THEN
644  IF( dif( 1 ).GT.abnorm*ulp )
645  $ result( 4 ) = ulpinv
646  ELSE IF( dif( 5 ).EQ.zero ) THEN
647  IF( diftru( 5 ).GT.abnorm*ulp )
648  $ result( 4 ) = ulpinv
649  ELSE IF( diftru( 5 ).EQ.zero ) THEN
650  IF( dif( 5 ).GT.abnorm*ulp )
651  $ result( 4 ) = ulpinv
652  ELSE
653  ratio1 = max( abs( diftru( 1 ) / dif( 1 ) ),
654  $ abs( dif( 1 ) / diftru( 1 ) ) )
655  ratio2 = max( abs( diftru( 5 ) / dif( 5 ) ),
656  $ abs( dif( 5 ) / diftru( 5 ) ) )
657  result( 4 ) = max( ratio1, ratio2 )
658  END IF
659 *
660  ntestt = ntestt + 4
661 *
662 * Print out tests which fail.
663 *
664  DO 130 j = 1, 4
665  IF( result( j ).GE.thrsh2 ) THEN
666 *
667 * If this is the first test to fail,
668 * print a header to the data file.
669 *
670  IF( nerrs.EQ.0 ) THEN
671  WRITE( nout, fmt = 9997 )'ZXV'
672 *
673 * Print out messages for built-in examples
674 *
675 * Matrix types
676 *
677  WRITE( nout, fmt = 9996 )
678 *
679 * Tests performed
680 *
681  WRITE( nout, fmt = 9992 )'''', 'transpose', ''''
682 *
683  END IF
684  nerrs = nerrs + 1
685  IF( result( j ).LT.10000.0d0 ) THEN
686  WRITE( nout, fmt = 9989 )nptknt, n, j, result( j )
687  ELSE
688  WRITE( nout, fmt = 9988 )nptknt, n, j, result( j )
689  END IF
690  END IF
691  130 CONTINUE
692 *
693  140 CONTINUE
694 *
695  GO TO 90
696  150 CONTINUE
697 *
698 * Summary
699 *
700  CALL alasvm( 'ZXV', nout, nerrs, ntestt, 0 )
701 *
702  work( 1 ) = maxwrk
703 *
704  RETURN
705 *
706  9999 FORMAT( ' ZDRGVX: ', a, ' returned INFO=', i6, '.', / 9x, 'N=',
707  $ i6, ', JTYPE=', i6, ')' )
708 *
709  9998 FORMAT( ' ZDRGVX: ', a, ' Eigenvectors from ', a, ' incorrectly ',
710  $ 'normalized.', / ' Bits of error=', 0p, g10.3, ',', 9x,
711  $ 'N=', i6, ', JTYPE=', i6, ', IWA=', i5, ', IWB=', i5,
712  $ ', IWX=', i5, ', IWY=', i5 )
713 *
714  9997 FORMAT( / 1x, a3, ' -- Complex Expert Eigenvalue/vector',
715  $ ' problem driver' )
716 *
717  9996 FORMAT( 'Input Example' )
718 *
719  9995 FORMAT( ' Matrix types: ', / )
720 *
721  9994 FORMAT( ' TYPE 1: Da is diagonal, Db is identity, ',
722  $ / ' A = Y^(-H) Da X^(-1), B = Y^(-H) Db X^(-1) ',
723  $ / ' YH and X are left and right eigenvectors. ', / )
724 *
725  9993 FORMAT( ' TYPE 2: Da is quasi-diagonal, Db is identity, ',
726  $ / ' A = Y^(-H) Da X^(-1), B = Y^(-H) Db X^(-1) ',
727  $ / ' YH and X are left and right eigenvectors. ', / )
728 *
729  9992 FORMAT( / ' Tests performed: ', / 4x,
730  $ ' a is alpha, b is beta, l is a left eigenvector, ', / 4x,
731  $ ' r is a right eigenvector and ', a, ' means ', a, '.',
732  $ / ' 1 = max | ( b A - a B )', a, ' l | / const.',
733  $ / ' 2 = max | ( b A - a B ) r | / const.',
734  $ / ' 3 = max ( Sest/Stru, Stru/Sest ) ',
735  $ ' over all eigenvalues', /
736  $ ' 4 = max( DIFest/DIFtru, DIFtru/DIFest ) ',
737  $ ' over the 1st and 5th eigenvectors', / )
738 *
739  9991 FORMAT( ' Type=', i2, ',', ' IWA=', i2, ', IWB=', i2, ', IWX=',
740  $ i2, ', IWY=', i2, ', result ', i2, ' is', 0p, f8.2 )
741 *
742  9990 FORMAT( ' Type=', i2, ',', ' IWA=', i2, ', IWB=', i2, ', IWX=',
743  $ i2, ', IWY=', i2, ', result ', i2, ' is', 1p, d10.3 )
744 *
745  9989 FORMAT( ' Input example #', i2, ', matrix order=', i4, ',',
746  $ ' result ', i2, ' is', 0p, f8.2 )
747 *
748  9988 FORMAT( ' Input example #', i2, ', matrix order=', i4, ',',
749  $ ' result ', i2, ' is', 1p, d10.3 )
750 *
751  9987 FORMAT( ' ZDRGVX: ', a, ' returned INFO=', i6, '.', / 9x, 'N=',
752  $ i6, ', Input example #', i2, ')' )
753 *
754  9986 FORMAT( ' ZDRGVX: ', a, ' Eigenvectors from ', a, ' incorrectly ',
755  $ 'normalized.', / ' Bits of error=', 0p, g10.3, ',', 9x,
756  $ 'N=', i6, ', Input Example #', i2, ')' )
757 *
758 * End of ZDRGVX
759 *
subroutine alasvm(TYPE, NOUT, NFAIL, NRUN, NERRS)
ALASVM
Definition: alasvm.f:75
subroutine zlacpy(UPLO, M, N, A, LDA, B, LDB)
ZLACPY copies all or part of one two-dimensional array to another.
Definition: zlacpy.f:105
double precision function dlamch(CMACH)
DLAMCH
Definition: dlamch.f:65
subroutine zlatm6(TYPE, N, A, LDA, B, X, LDX, Y, LDY, ALPHA, BETA, WX, WY, S, DIF)
ZLATM6
Definition: zlatm6.f:176
subroutine zget52(LEFT, N, A, LDA, B, LDB, E, LDE, ALPHA, BETA, WORK, RWORK, RESULT)
ZGET52
Definition: zget52.f:164
subroutine xerbla(SRNAME, INFO)
XERBLA
Definition: xerbla.f:62
subroutine zggevx(BALANC, JOBVL, JOBVR, SENSE, N, A, LDA, B, LDB, ALPHA, BETA, VL, LDVL, VR, LDVR, ILO, IHI, LSCALE, RSCALE, ABNRM, BBNRM, RCONDE, RCONDV, WORK, LWORK, RWORK, IWORK, BWORK, INFO)
ZGGEVX computes the eigenvalues and, optionally, the left and/or right eigenvectors for GE matrices ...
Definition: zggevx.f:376
double precision function zlange(NORM, M, N, A, LDA, WORK)
ZLANGE returns the value of the 1-norm, Frobenius norm, infinity-norm, or the largest absolute value ...
Definition: zlange.f:117
integer function ilaenv(ISPEC, NAME, OPTS, N1, N2, N3, N4)
Definition: tstiee.f:83

Here is the call graph for this function:

Here is the caller graph for this function: