433 SUBROUTINE zdrvsx( NSIZES, NN, NTYPES, DOTYPE, ISEED, THRESH,
434 $ niunit, nounit, a, lda, h, ht, w, wt, wtmp, vs,
435 $ ldvs, vs1, result, work, lwork, rwork, bwork,
444 INTEGER INFO, LDA, LDVS, LWORK, NIUNIT, NOUNIT, NSIZES,
446 DOUBLE PRECISION THRESH
449 LOGICAL BWORK( * ), DOTYPE( * )
450 INTEGER ISEED( 4 ), NN( * )
451 DOUBLE PRECISION RESULT( 17 ), RWORK( * )
452 COMPLEX*16 A( lda, * ), H( lda, * ), HT( lda, * ),
453 $ vs( ldvs, * ), vs1( ldvs, * ), w( * ),
454 $ work( * ), wt( * ), wtmp( * )
461 parameter ( czero = ( 0.0d+0, 0.0d+0 ) )
463 parameter ( cone = ( 1.0d+0, 0.0d+0 ) )
464 DOUBLE PRECISION ZERO, ONE
465 parameter ( zero = 0.0d+0, one = 1.0d+0 )
467 parameter ( maxtyp = 21 )
472 INTEGER I, IINFO, IMODE, ISRT, ITYPE, IWK, J, JCOL,
473 $ jsize, jtype, mtypes, n, nerrs, nfail, nmax,
474 $ nnwork, nslct, ntest, ntestf, ntestt
475 DOUBLE PRECISION ANORM, COND, CONDS, OVFL, RCDEIN, RCDVIN,
476 $ rtulp, rtulpi, ulp, ulpinv, unfl
479 INTEGER IDUMMA( 1 ), IOLDSD( 4 ), ISLCT( 20 ),
480 $ kconds( maxtyp ), kmagn( maxtyp ),
481 $ kmode( maxtyp ), ktype( maxtyp )
485 DOUBLE PRECISION SELWI( 20 ), SELWR( 20 )
488 INTEGER SELDIM, SELOPT
491 COMMON / sslct / selopt, seldim, selval, selwr, selwi
494 DOUBLE PRECISION DLAMCH
502 INTRINSIC abs, max, min, sqrt
505 DATA ktype / 1, 2, 3, 5*4, 4*6, 6*6, 3*9 /
506 DATA kmagn / 3*1, 1, 1, 1, 2, 3, 4*1, 1, 1, 1, 1, 2,
508 DATA kmode / 3*0, 4, 3, 1, 4, 4, 4, 3, 1, 5, 4, 3,
509 $ 1, 5, 5, 5, 4, 3, 1 /
510 DATA kconds / 3*0, 5*0, 4*1, 6*2, 3*0 /
514 path( 1: 1 ) =
'Zomplex precision'
532 nmax = max( nmax, nn( j ) )
539 IF( nsizes.LT.0 )
THEN
541 ELSE IF( badnn )
THEN
543 ELSE IF( ntypes.LT.0 )
THEN
545 ELSE IF( thresh.LT.zero )
THEN
547 ELSE IF( niunit.LE.0 )
THEN
549 ELSE IF( nounit.LE.0 )
THEN
551 ELSE IF( lda.LT.1 .OR. lda.LT.nmax )
THEN
553 ELSE IF( ldvs.LT.1 .OR. ldvs.LT.nmax )
THEN
555 ELSE IF( max( 3*nmax, 2*nmax**2 ).GT.lwork )
THEN
560 CALL xerbla(
'ZDRVSX', -info )
566 IF( nsizes.EQ.0 .OR. ntypes.EQ.0 )
571 unfl = dlamch(
'Safe minimum' )
574 ulp = dlamch(
'Precision' )
583 DO 140 jsize = 1, nsizes
585 IF( nsizes.NE.1 )
THEN
586 mtypes = min( maxtyp, ntypes )
588 mtypes = min( maxtyp+1, ntypes )
591 DO 130 jtype = 1, mtypes
592 IF( .NOT.dotype( jtype ) )
598 ioldsd( j ) = iseed( j )
617 IF( mtypes.GT.maxtyp )
620 itype = ktype( jtype )
621 imode = kmode( jtype )
625 GO TO ( 30, 40, 50 )kmagn( jtype )
641 CALL zlaset(
'Full', lda, n, czero, czero, a, lda )
647 IF( itype.EQ.1 )
THEN
653 ELSE IF( itype.EQ.2 )
THEN
658 a( jcol, jcol ) = anorm
661 ELSE IF( itype.EQ.3 )
THEN
666 a( jcol, jcol ) = anorm
668 $ a( jcol, jcol-1 ) = cone
671 ELSE IF( itype.EQ.4 )
THEN
675 CALL zlatms( n, n,
'S', iseed,
'H', rwork, imode, cond,
676 $ anorm, 0, 0,
'N', a, lda, work( n+1 ),
679 ELSE IF( itype.EQ.5 )
THEN
683 CALL zlatms( n, n,
'S', iseed,
'H', rwork, imode, cond,
684 $ anorm, n, n,
'N', a, lda, work( n+1 ),
687 ELSE IF( itype.EQ.6 )
THEN
691 IF( kconds( jtype ).EQ.1 )
THEN
693 ELSE IF( kconds( jtype ).EQ.2 )
THEN
699 CALL zlatme( n,
'D', iseed, work, imode, cond, cone,
700 $
'T',
'T',
'T', rwork, 4, conds, n, n, anorm,
701 $ a, lda, work( 2*n+1 ), iinfo )
703 ELSE IF( itype.EQ.7 )
THEN
707 CALL zlatmr( n, n,
'D', iseed,
'N', work, 6, one, cone,
708 $
'T',
'N', work( n+1 ), 1, one,
709 $ work( 2*n+1 ), 1, one,
'N', idumma, 0, 0,
710 $ zero, anorm,
'NO', a, lda, idumma, iinfo )
712 ELSE IF( itype.EQ.8 )
THEN
716 CALL zlatmr( n, n,
'D', iseed,
'H', work, 6, one, cone,
717 $
'T',
'N', work( n+1 ), 1, one,
718 $ work( 2*n+1 ), 1, one,
'N', idumma, n, n,
719 $ zero, anorm,
'NO', a, lda, idumma, iinfo )
721 ELSE IF( itype.EQ.9 )
THEN
725 CALL zlatmr( n, n,
'D', iseed,
'N', work, 6, one, cone,
726 $
'T',
'N', work( n+1 ), 1, one,
727 $ work( 2*n+1 ), 1, one,
'N', idumma, n, n,
728 $ zero, anorm,
'NO', a, lda, idumma, iinfo )
730 CALL zlaset(
'Full', 2, n, czero, czero, a, lda )
731 CALL zlaset(
'Full', n-3, 1, czero, czero, a( 3, 1 ),
733 CALL zlaset(
'Full', n-3, 2, czero, czero,
735 CALL zlaset(
'Full', 1, n, czero, czero, a( n, 1 ),
739 ELSE IF( itype.EQ.10 )
THEN
743 CALL zlatmr( n, n,
'D', iseed,
'N', work, 6, one, cone,
744 $
'T',
'N', work( n+1 ), 1, one,
745 $ work( 2*n+1 ), 1, one,
'N', idumma, n, 0,
746 $ zero, anorm,
'NO', a, lda, idumma, iinfo )
753 IF( iinfo.NE.0 )
THEN
754 WRITE( nounit, fmt = 9991 )
'Generator', iinfo, n, jtype,
768 nnwork = max( 2*n, n*( n+1 ) / 2 )
770 nnwork = max( nnwork, 1 )
772 CALL zget24( .false., jtype, thresh, ioldsd, nounit, n,
773 $ a, lda, h, ht, w, wt, wtmp, vs, ldvs, vs1,
774 $ rcdein, rcdvin, nslct, islct, 0, result,
775 $ work, nnwork, rwork, bwork, info )
782 IF( result( j ).GE.zero )
784 IF( result( j ).GE.thresh )
789 $ ntestf = ntestf + 1
790 IF( ntestf.EQ.1 )
THEN
791 WRITE( nounit, fmt = 9999 )path
792 WRITE( nounit, fmt = 9998 )
793 WRITE( nounit, fmt = 9997 )
794 WRITE( nounit, fmt = 9996 )
795 WRITE( nounit, fmt = 9995 )thresh
796 WRITE( nounit, fmt = 9994 )
801 IF( result( j ).GE.thresh )
THEN
802 WRITE( nounit, fmt = 9993 )n, iwk, ioldsd, jtype,
807 nerrs = nerrs + nfail
808 ntestt = ntestt + ntest
821 READ( niunit, fmt = *, end = 200 )n, nslct, isrt
826 READ( niunit, fmt = * )( islct( i ), i = 1, nslct )
828 READ( niunit, fmt = * )( a( i, j ), j = 1, n )
830 READ( niunit, fmt = * )rcdein, rcdvin
832 CALL zget24( .true., 22, thresh, iseed, nounit, n, a, lda, h, ht,
833 $ w, wt, wtmp, vs, ldvs, vs1, rcdein, rcdvin, nslct,
834 $ islct, isrt, result, work, lwork, rwork, bwork,
842 IF( result( j ).GE.zero )
844 IF( result( j ).GE.thresh )
849 $ ntestf = ntestf + 1
850 IF( ntestf.EQ.1 )
THEN
851 WRITE( nounit, fmt = 9999 )path
852 WRITE( nounit, fmt = 9998 )
853 WRITE( nounit, fmt = 9997 )
854 WRITE( nounit, fmt = 9996 )
855 WRITE( nounit, fmt = 9995 )thresh
856 WRITE( nounit, fmt = 9994 )
860 IF( result( j ).GE.thresh )
THEN
861 WRITE( nounit, fmt = 9992 )n, jtype, j, result( j )
865 nerrs = nerrs + nfail
866 ntestt = ntestt + ntest
872 CALL dlasum( path, nounit, nerrs, ntestt )
874 9999
FORMAT( / 1x, a3,
' -- Complex Schur Form Decomposition Expert ',
875 $
'Driver', /
' Matrix types (see ZDRVSX for details): ' )
877 9998
FORMAT( /
' Special Matrices:', /
' 1=Zero matrix. ',
878 $
' ',
' 5=Diagonal: geometr. spaced entries.',
879 $ /
' 2=Identity matrix. ',
' 6=Diagona',
880 $
'l: clustered entries.', /
' 3=Transposed Jordan block. ',
881 $
' ',
' 7=Diagonal: large, evenly spaced.', /
' ',
882 $
'4=Diagonal: evenly spaced entries. ',
' 8=Diagonal: s',
883 $
'mall, evenly spaced.' )
884 9997
FORMAT(
' Dense, Non-Symmetric Matrices:', /
' 9=Well-cond., ev',
885 $
'enly spaced eigenvals.',
' 14=Ill-cond., geomet. spaced e',
886 $
'igenals.', /
' 10=Well-cond., geom. spaced eigenvals. ',
887 $
' 15=Ill-conditioned, clustered e.vals.', /
' 11=Well-cond',
888 $
'itioned, clustered e.vals. ',
' 16=Ill-cond., random comp',
889 $
'lex ', /
' 12=Well-cond., random complex ',
' ',
890 $
' 17=Ill-cond., large rand. complx ', /
' 13=Ill-condi',
891 $
'tioned, evenly spaced. ',
' 18=Ill-cond., small rand.',
893 9996
FORMAT(
' 19=Matrix with random O(1) entries. ',
' 21=Matrix ',
894 $
'with small random entries.', /
' 20=Matrix with large ran',
895 $
'dom entries. ', / )
896 9995
FORMAT(
' Tests performed with test threshold =', f8.2,
897 $ /
' ( A denotes A on input and T denotes A on output)',
898 $ / /
' 1 = 0 if T in Schur form (no sort), ',
899 $
' 1/ulp otherwise', /
900 $
' 2 = | A - VS T transpose(VS) | / ( n |A| ulp ) (no sort)',
901 $ /
' 3 = | I - VS transpose(VS) | / ( n ulp ) (no sort) ',
902 $ /
' 4 = 0 if W are eigenvalues of T (no sort),',
903 $
' 1/ulp otherwise', /
904 $
' 5 = 0 if T same no matter if VS computed (no sort),',
905 $
' 1/ulp otherwise', /
906 $
' 6 = 0 if W same no matter if VS computed (no sort)',
907 $
', 1/ulp otherwise' )
908 9994
FORMAT(
' 7 = 0 if T in Schur form (sort), ',
' 1/ulp otherwise',
909 $ /
' 8 = | A - VS T transpose(VS) | / ( n |A| ulp ) (sort)',
910 $ /
' 9 = | I - VS transpose(VS) | / ( n ulp ) (sort) ',
911 $ /
' 10 = 0 if W are eigenvalues of T (sort),',
912 $
' 1/ulp otherwise', /
913 $
' 11 = 0 if T same no matter what else computed (sort),',
914 $
' 1/ulp otherwise', /
915 $
' 12 = 0 if W same no matter what else computed ',
916 $
'(sort), 1/ulp otherwise', /
917 $
' 13 = 0 if sorting successful, 1/ulp otherwise',
918 $ /
' 14 = 0 if RCONDE same no matter what else computed,',
919 $
' 1/ulp otherwise', /
920 $
' 15 = 0 if RCONDv same no matter what else computed,',
921 $
' 1/ulp otherwise', /
922 $
' 16 = | RCONDE - RCONDE(precomputed) | / cond(RCONDE),',
923 $ /
' 17 = | RCONDV - RCONDV(precomputed) | / cond(RCONDV),' )
924 9993
FORMAT(
' N=', i5,
', IWK=', i2,
', seed=', 4( i4,
',' ),
925 $
' type ', i2,
', test(', i2,
')=', g10.3 )
926 9992
FORMAT(
' N=', i5,
', input example =', i3,
', test(', i2,
')=',
928 9991
FORMAT(
' ZDRVSX: ', a,
' returned INFO=', i6,
'.', / 9x,
'N=',
929 $ i6,
', JTYPE=', i6,
', ISEED=(', 3( i5,
',' ), i5,
')' )
subroutine zlatmr(M, N, DIST, ISEED, SYM, D, MODE, COND, DMAX, RSIGN, GRADE, DL, MODEL, CONDL, DR, MODER, CONDR, PIVTNG, IPIVOT, KL, KU, SPARSE, ANORM, PACK, A, LDA, IWORK, INFO)
ZLATMR
subroutine zlaset(UPLO, M, N, ALPHA, BETA, A, LDA)
ZLASET initializes the off-diagonal elements and the diagonal elements of a matrix to given values...
subroutine zget24(COMP, JTYPE, THRESH, ISEED, NOUNIT, N, A, LDA, H, HT, W, WT, WTMP, VS, LDVS, VS1, RCDEIN, RCDVIN, NSLCT, ISLCT, ISRT, RESULT, WORK, LWORK, RWORK, BWORK, INFO)
ZGET24
subroutine zdrvsx(NSIZES, NN, NTYPES, DOTYPE, ISEED, THRESH, NIUNIT, NOUNIT, A, LDA, H, HT, W, WT, WTMP, VS, LDVS, VS1, RESULT, WORK, LWORK, RWORK, BWORK, INFO)
ZDRVSX
subroutine xerbla(SRNAME, INFO)
XERBLA
subroutine dlabad(SMALL, LARGE)
DLABAD
subroutine zlatme(N, DIST, ISEED, D, MODE, COND, DMAX, RSIGN, UPPER, SIM, DS, MODES, CONDS, KL, KU, ANORM, A, LDA, WORK, INFO)
ZLATME
subroutine dlasum(TYPE, IOUNIT, IE, NRUN)
DLASUM
subroutine zlatms(M, N, DIST, ISEED, SYM, D, MODE, COND, DMAX, KL, KU, PACK, A, LDA, WORK, INFO)
ZLATMS