450 SUBROUTINE ddrvsx( NSIZES, NN, NTYPES, DOTYPE, ISEED, THRESH,
451 $ NIUNIT, NOUNIT, A, LDA, H, HT, WR, WI, WRT,
452 $ WIT, WRTMP, WITMP, VS, LDVS, VS1, RESULT, WORK,
453 $ LWORK, IWORK, BWORK, INFO )
460 INTEGER INFO, LDA, LDVS, LWORK, NIUNIT, NOUNIT, NSIZES,
462 DOUBLE PRECISION THRESH
465 LOGICAL BWORK( * ), DOTYPE( * )
466 INTEGER ISEED( 4 ), IWORK( * ), NN( * )
467 DOUBLE PRECISION A( LDA, * ), H( LDA, * ), HT( LDA, * ),
468 $ result( 17 ), vs( ldvs, * ), vs1( ldvs, * ),
469 $ wi( * ), wit( * ), witmp( * ), work( * ),
470 $ wr( * ), wrt( * ), wrtmp( * )
476 DOUBLE PRECISION ZERO, ONE
477 PARAMETER ( ZERO = 0.0d0, one = 1.0d0 )
479 parameter( maxtyp = 21 )
484 INTEGER I, IINFO, IMODE, ITYPE, IWK, J, JCOL, JSIZE,
485 $ jtype, mtypes, n, nerrs, nfail, nmax, nnwork,
486 $ nslct, ntest, ntestf, ntestt
487 DOUBLE PRECISION ANORM, COND, CONDS, OVFL, RCDEIN, RCDVIN,
488 $ RTULP, RTULPI, ULP, ULPINV, UNFL
491 CHARACTER ADUMMA( 1 )
492 INTEGER IDUMMA( 1 ), IOLDSD( 4 ), ISLCT( 20 ),
493 $ KCONDS( MAXTYP ), KMAGN( MAXTYP ),
494 $ kmode( maxtyp ), ktype( maxtyp )
498 DOUBLE PRECISION SELWI( 20 ), SELWR( 20 )
501 INTEGER SELDIM, SELOPT
504 COMMON / sslct / selopt, seldim, selval, selwr, selwi
507 DOUBLE PRECISION DLAMCH
515 INTRINSIC abs, max, min, sqrt
518 DATA ktype / 1, 2, 3, 5*4, 4*6, 6*6, 3*9 /
519 DATA kmagn / 3*1, 1, 1, 1, 2, 3, 4*1, 1, 1, 1, 1, 2,
521 DATA kmode / 3*0, 4, 3, 1, 4, 4, 4, 3, 1, 5, 4, 3,
522 $ 1, 5, 5, 5, 4, 3, 1 /
523 DATA kconds / 3*0, 5*0, 4*1, 6*2, 3*0 /
527 path( 1: 1 ) =
'Double precision'
545 nmax = max( nmax, nn( j ) )
552 IF( nsizes.LT.0 )
THEN
554 ELSE IF( badnn )
THEN
556 ELSE IF( ntypes.LT.0 )
THEN
558 ELSE IF( thresh.LT.zero )
THEN
560 ELSE IF( niunit.LE.0 )
THEN
562 ELSE IF( nounit.LE.0 )
THEN
564 ELSE IF( lda.LT.1 .OR. lda.LT.nmax )
THEN
566 ELSE IF( ldvs.LT.1 .OR. ldvs.LT.nmax )
THEN
568 ELSE IF( max( 3*nmax, 2*nmax**2 ).GT.lwork )
THEN
573 CALL xerbla(
'DDRVSX', -info )
579 IF( nsizes.EQ.0 .OR. ntypes.EQ.0 )
584 unfl = dlamch(
'Safe minimum' )
586 ulp = dlamch(
'Precision' )
595 DO 140 jsize = 1, nsizes
597 IF( nsizes.NE.1 )
THEN
598 mtypes = min( maxtyp, ntypes )
600 mtypes = min( maxtyp+1, ntypes )
603 DO 130 jtype = 1, mtypes
604 IF( .NOT.dotype( jtype ) )
610 ioldsd( j ) = iseed( j )
629 IF( mtypes.GT.maxtyp )
632 itype = ktype( jtype )
633 imode = kmode( jtype )
637 GO TO ( 30, 40, 50 )kmagn( jtype )
653 CALL dlaset(
'Full', lda, n, zero, zero, a, lda )
661 IF( itype.EQ.1 )
THEN
664 ELSE IF( itype.EQ.2 )
THEN
669 a( jcol, jcol ) = anorm
672 ELSE IF( itype.EQ.3 )
THEN
677 a( jcol, jcol ) = anorm
679 $ a( jcol, jcol-1 ) = one
682 ELSE IF( itype.EQ.4 )
THEN
686 CALL dlatms( n, n,
'S', iseed,
'S', work, imode, cond,
687 $ anorm, 0, 0,
'N', a, lda, work( n+1 ),
690 ELSE IF( itype.EQ.5 )
THEN
694 CALL dlatms( n, n,
'S', iseed,
'S', work, imode, cond,
695 $ anorm, n, n,
'N', a, lda, work( n+1 ),
698 ELSE IF( itype.EQ.6 )
THEN
702 IF( kconds( jtype ).EQ.1 )
THEN
704 ELSE IF( kconds( jtype ).EQ.2 )
THEN
711 CALL dlatme( n,
'S', iseed, work, imode, cond, one,
712 $ adumma,
'T',
'T',
'T', work( n+1 ), 4,
713 $ conds, n, n, anorm, a, lda, work( 2*n+1 ),
716 ELSE IF( itype.EQ.7 )
THEN
720 CALL dlatmr( n, n,
'S', iseed,
'S', work, 6, one, one,
721 $
'T',
'N', work( n+1 ), 1, one,
722 $ work( 2*n+1 ), 1, one,
'N', idumma, 0, 0,
723 $ zero, anorm,
'NO', a, lda, iwork, iinfo )
725 ELSE IF( itype.EQ.8 )
THEN
729 CALL dlatmr( n, n,
'S', iseed,
'S', work, 6, one, one,
730 $
'T',
'N', work( n+1 ), 1, one,
731 $ work( 2*n+1 ), 1, one,
'N', idumma, n, n,
732 $ zero, anorm,
'NO', a, lda, iwork, iinfo )
734 ELSE IF( itype.EQ.9 )
THEN
738 CALL dlatmr( n, n,
'S', iseed,
'N', work, 6, one, one,
739 $
'T',
'N', work( n+1 ), 1, one,
740 $ work( 2*n+1 ), 1, one,
'N', idumma, n, n,
741 $ zero, anorm,
'NO', a, lda, iwork, iinfo )
743 CALL dlaset(
'Full', 2, n, zero, zero, a, lda )
744 CALL dlaset(
'Full', n-3, 1, zero, zero, a( 3, 1 ),
746 CALL dlaset(
'Full', n-3, 2, zero, zero, a( 3, n-1 ),
748 CALL dlaset(
'Full', 1, n, zero, zero, a( n, 1 ),
752 ELSE IF( itype.EQ.10 )
THEN
756 CALL dlatmr( n, n,
'S', iseed,
'N', work, 6, one, one,
757 $
'T',
'N', work( n+1 ), 1, one,
758 $ work( 2*n+1 ), 1, one,
'N', idumma, n, 0,
759 $ zero, anorm,
'NO', a, lda, iwork, iinfo )
766 IF( iinfo.NE.0 )
THEN
767 WRITE( nounit, fmt = 9991 )
'Generator', iinfo, n, jtype,
781 nnwork = max( 3*n, 2*n*n )
783 nnwork = max( nnwork, 1 )
785 CALL dget24( .false., jtype, thresh, ioldsd, nounit, n,
786 $ a, lda, h, ht, wr, wi, wrt, wit, wrtmp,
787 $ witmp, vs, ldvs, vs1, rcdein, rcdvin, nslct,
788 $ islct, result, work, nnwork, iwork, bwork,
796 IF( result( j ).GE.zero )
798 IF( result( j ).GE.thresh )
803 $ ntestf = ntestf + 1
804 IF( ntestf.EQ.1 )
THEN
805 WRITE( nounit, fmt = 9999 )path
806 WRITE( nounit, fmt = 9998 )
807 WRITE( nounit, fmt = 9997 )
808 WRITE( nounit, fmt = 9996 )
809 WRITE( nounit, fmt = 9995 )thresh
810 WRITE( nounit, fmt = 9994 )
815 IF( result( j ).GE.thresh )
THEN
816 WRITE( nounit, fmt = 9993 )n, iwk, ioldsd, jtype,
821 nerrs = nerrs + nfail
822 ntestt = ntestt + ntest
835 READ( niunit, fmt = *,
END = 200 )N, nslct
841 $
READ( niunit, fmt = * )( islct( i ), i = 1, nslct )
843 READ( niunit, fmt = * )( a( i, j ), j = 1, n )
845 READ( niunit, fmt = * )rcdein, rcdvin
847 CALL dget24( .true., 22, thresh, iseed, nounit, n, a, lda, h, ht,
848 $ wr, wi, wrt, wit, wrtmp, witmp, vs, ldvs, vs1,
849 $ rcdein, rcdvin, nslct, islct, result, work, lwork,
850 $ iwork, bwork, info )
857 IF( result( j ).GE.zero )
859 IF( result( j ).GE.thresh )
864 $ ntestf = ntestf + 1
865 IF( ntestf.EQ.1 )
THEN
866 WRITE( nounit, fmt = 9999 )path
867 WRITE( nounit, fmt = 9998 )
868 WRITE( nounit, fmt = 9997 )
869 WRITE( nounit, fmt = 9996 )
870 WRITE( nounit, fmt = 9995 )thresh
871 WRITE( nounit, fmt = 9994 )
875 IF( result( j ).GE.thresh )
THEN
876 WRITE( nounit, fmt = 9992 )n, jtype, j, result( j )
880 nerrs = nerrs + nfail
881 ntestt = ntestt + ntest
887 CALL dlasum( path, nounit, nerrs, ntestt )
889 9999
FORMAT( / 1x, a3,
' -- Real Schur Form Decomposition Expert ',
890 $
'Driver', /
' Matrix types (see DDRVSX for details):' )
892 9998
FORMAT( /
' Special Matrices:', /
' 1=Zero matrix. ',
893 $
' ',
' 5=Diagonal: geometr. spaced entries.',
894 $ /
' 2=Identity matrix. ',
' 6=Diagona',
895 $
'l: clustered entries.', /
' 3=Transposed Jordan block. ',
896 $
' ',
' 7=Diagonal: large, evenly spaced.', /
' ',
897 $
'4=Diagonal: evenly spaced entries. ',
' 8=Diagonal: s',
898 $
'mall, evenly spaced.' )
899 9997
FORMAT(
' Dense, Non-Symmetric Matrices:', /
' 9=Well-cond., ev',
900 $
'enly spaced eigenvals.',
' 14=Ill-cond., geomet. spaced e',
901 $
'igenals.', /
' 10=Well-cond., geom. spaced eigenvals. ',
902 $
' 15=Ill-conditioned, clustered e.vals.', /
' 11=Well-cond',
903 $
'itioned, clustered e.vals. ',
' 16=Ill-cond., random comp',
904 $
'lex ', /
' 12=Well-cond., random complex ',
' ',
905 $
' 17=Ill-cond., large rand. complx ', /
' 13=Ill-condi',
906 $
'tioned, evenly spaced. ',
' 18=Ill-cond., small rand.',
908 9996
FORMAT(
' 19=Matrix with random O(1) entries. ',
' 21=Matrix ',
909 $
'with small random entries.', /
' 20=Matrix with large ran',
910 $
'dom entries. ', / )
911 9995
FORMAT(
' Tests performed with test threshold =', f8.2,
912 $ /
' ( A denotes A on input and T denotes A on output)',
913 $ / /
' 1 = 0 if T in Schur form (no sort), ',
914 $
' 1/ulp otherwise', /
915 $
' 2 = | A - VS T transpose(VS) | / ( n |A| ulp ) (no sort)',
916 $ /
' 3 = | I - VS transpose(VS) | / ( n ulp ) (no sort) ', /
917 $
' 4 = 0 if WR+sqrt(-1)*WI are eigenvalues of T (no sort),',
918 $
' 1/ulp otherwise', /
919 $
' 5 = 0 if T same no matter if VS computed (no sort),',
920 $
' 1/ulp otherwise', /
921 $
' 6 = 0 if WR, WI same no matter if VS computed (no sort)',
922 $
', 1/ulp otherwise' )
923 9994
FORMAT(
' 7 = 0 if T in Schur form (sort), ',
' 1/ulp otherwise',
924 $ /
' 8 = | A - VS T transpose(VS) | / ( n |A| ulp ) (sort)',
925 $ /
' 9 = | I - VS transpose(VS) | / ( n ulp ) (sort) ',
926 $ /
' 10 = 0 if WR+sqrt(-1)*WI are eigenvalues of T (sort),',
927 $
' 1/ulp otherwise', /
928 $
' 11 = 0 if T same no matter what else computed (sort),',
929 $
' 1/ulp otherwise', /
930 $
' 12 = 0 if WR, WI same no matter what else computed ',
931 $
'(sort), 1/ulp otherwise', /
932 $
' 13 = 0 if sorting successful, 1/ulp otherwise',
933 $ /
' 14 = 0 if RCONDE same no matter what else computed,',
934 $
' 1/ulp otherwise', /
935 $
' 15 = 0 if RCONDv same no matter what else computed,',
936 $
' 1/ulp otherwise', /
937 $
' 16 = | RCONDE - RCONDE(precomputed) | / cond(RCONDE),',
938 $ /
' 17 = | RCONDV - RCONDV(precomputed) | / cond(RCONDV),' )
939 9993
FORMAT(
' N=', i5,
', IWK=', i2,
', seed=', 4( i4,
',' ),
940 $
' type ', i2,
', test(', i2,
')=', g10.3 )
941 9992
FORMAT(
' N=', i5,
', input example =', i3,
', test(', i2,
')=',
943 9991
FORMAT(
' DDRVSX: ', a,
' returned INFO=', i6,
'.', / 9x,
'N=',
944 $ i6,
', JTYPE=', i6,
', ISEED=(', 3( i5,
',' ), i5,
')' )