126 parameter( nmax = 132 )
128 parameter( maxin = 12 )
130 parameter( maxrhs = 16 )
132 parameter( matmax = 30 )
134 parameter( nin = 5, nout = 6 )
136 parameter( kdmax = nmax+( nmax+1 ) / 4 )
139 LOGICAL fatal, tstchk, tstdrv, tsterr
145 INTEGER i, ic, j, k, la, lafac, lda, , nm, nmats, nn,
146 $ nnb, nnb2, nns, nrhs, , nrank,
147 $ vers_major, vers_minor, vers_patch
148 REAL eps, s1, s2, threq, thresh
151 LOGICAL dotype( matmax )
152 INTEGER iwork( 25*nmax ), mval( maxin ),
153 $ nbval( maxin ), nbval2( maxin ),
154 $ nsval( maxin ), nval( maxin ), nxval( maxin ),
155 $ rankval( maxin ), piv( nmax )
160 INTEGER allocatestatus
161 REAL,
DIMENSION(:),
ALLOCATABLE :: rwork
162 COMPLEX,
DIMENSION(:,:),
ALLOCATABLE :: a, b, work
188 INTEGER iparms( 100 )
191 COMMON / claenv / iparms
192 COMMON / infoc / infot, nunit, ok, lerr
193 COMMON / srnamc / srnamt
196 DATA threq / 2.0 / , intstr /
'0123456789' /
200 ALLOCATE ( a( ( kdmax+1 )*nmax, 7 ), stat = allocatestatus )
201 IF (allocatestatus /= 0) stop
"*** Not enough memory ***"
202 ALLOCATE ( b( nmax*maxrhs, 4 ), stat = allocatestatus )
203 IF (allocatestatus /= 0) stop
"*** Not enough memory ***"
204 ALLOCATE ( work( nmax, nmax+maxrhs+10 ), stat = allocatestatus )
205 IF (allocatestatus /= 0) stop
"*** Not enough memory ***"
206 ALLOCATE ( rwork( 150*nmax+2*maxrhs ), stat = allocatestatus )
207 IF (allocatestatus /= 0) stop
"*** Not enough memory ***"
221 CALL ilaver( vers_major, vers_minor, vers_patch )
222 WRITE( nout, fmt = 9994 ) vers_major, vers_minor, vers_patch
226 READ( nin, fmt = * )nm
228 WRITE( nout, fmt = 9996 )
' NM ', nm, 1
231 ELSE IF( nm.GT.maxin )
THEN
232 WRITE( nout, fmt = 9995 )
' NM ', nm, maxin
236 READ( nin, fmt = * )( mval( i ), i = 1, nm )
238 IF( mval( i ).LT.0 )
THEN
239 WRITE( nout, fmt = 9996 )
' M ', mval( i ), 0
241 ELSE IF( mval( i ).GT.nmax )
THEN
242 WRITE( nout, fmt = 9995 )
' M ', mval( i ), nmax
247 $
WRITE( nout, fmt = 9993 )'m
', ( MVAL( I ), I = 1, NM )
251 READ( NIN, FMT = * )NN
253 WRITE( NOUT, FMT = 9996 )' nn
', NN, 1
256.GT.
ELSE IF( NNMAXIN ) THEN
257 WRITE( NOUT, FMT = 9995 )' nn
', NN, MAXIN
261 READ( NIN, FMT = * )( NVAL( I ), I = 1, NN )
263.LT.
IF( NVAL( I )0 ) THEN
264 WRITE( NOUT, FMT = 9996 )' n
', NVAL( I ), 0
266.GT.
ELSE IF( NVAL( I )NMAX ) THEN
267 WRITE( NOUT, FMT = 9995 )' n
', NVAL( I ), NMAX
272 $ WRITE( NOUT, FMT = 9993 )'n
', ( NVAL( I ), I = 1, NN )
276 READ( NIN, FMT = * )NNS
278 WRITE( NOUT, FMT = 9996 )' nns
', NNS, 1
281.GT.
ELSE IF( NNSMAXIN ) THEN
282 WRITE( NOUT, FMT = 9995 )' nns
', NNS, MAXIN
286 READ( NIN, FMT = * )( NSVAL( I ), I = 1, NNS )
288.LT.
IF( NSVAL( I )0 ) THEN
289 WRITE( NOUT, FMT = 9996 )'nrhs
', NSVAL( I ), 0
291.GT.
ELSE IF( NSVAL( I )MAXRHS ) THEN
292 WRITE( NOUT, FMT = 9995 )'nrhs
', NSVAL( I ), MAXRHS
297 $ WRITE( NOUT, FMT = 9993 )'nrhs
', ( NSVAL( I ), I = 1, NNS )
301 READ( NIN, FMT = * )NNB
303 WRITE( NOUT, FMT = 9996 )'nnb
', NNB, 1
306.GT.
ELSE IF( NNBMAXIN ) THEN
307 WRITE( NOUT, FMT = 9995 )'nnb
', NNB, MAXIN
311 READ( NIN, FMT = * )( NBVAL( I ), I = 1, NNB )
313.LT.
IF( NBVAL( I )0 ) THEN
314 WRITE( NOUT, FMT = 9996 )' nb
', NBVAL( I ), 0
319 $ WRITE( NOUT, FMT = 9993 )'nb
', ( NBVAL( I ), I = 1, NNB )
327.EQ.
IF( NBNBVAL2( J ) )
336 READ( NIN, FMT = * )( NXVAL( I ), I = 1, NNB )
338.LT.
IF( NXVAL( I )0 ) THEN
339 WRITE( NOUT, FMT = 9996 )' nx
', NXVAL( I ), 0
344 $ WRITE( NOUT, FMT = 9993 )'nx
', ( NXVAL( I ), I = 1, NNB )
348 READ( NIN, FMT = * )NRANK
350 WRITE( NOUT, FMT = 9996 )' nrank
', NRANK, 1
353.GT.
ELSE IF( NNMAXIN ) THEN
354 WRITE( NOUT, FMT = 9995 )' nrank
', NRANK, MAXIN
358 READ( NIN, FMT = * )( RANKVAL( I ), I = 1, NRANK )
360.LT.
IF( RANKVAL( I )0 ) THEN
361 WRITE( NOUT, FMT = 9996 )' rank
', RANKVAL( I ), 0
363.GT.
ELSE IF( RANKVAL( I )100 ) THEN
364 WRITE( NOUT, FMT = 9995 )' rank ', rankval( i ), 100
369 $
WRITE( nout, fmt = 9993 )
'RANK % OF N',
370 $ ( rankval( i ), i = 1, nrank )
374 READ( nin, fmt = * )thresh
375 WRITE( nout, fmt = 9992 )thresh
379 READ( nin, fmt = * )tstchk
383 READ( nin, fmt = * )tstdrv
387 READ( nin, fmt = * )tsterr
390 WRITE( nout, fmt = 9999 )
396 eps =
slamch(
'Underflow threshold' )
397 WRITE( nout, fmt = 9991 )
'underflow', eps
398 eps =
slamch(
'Overflow threshold' )
399 WRITE( nout, fmt = 9991 )
'overflow ', eps
401 WRITE( nout, fmt = 9991 )
'precision', eps
402 WRITE( nout, fmt = * )
409 READ( nin, fmt =
'(A72)',
END = 140 )aline
417 IF( aline( i: i ).EQ.
' ' )
423 IF( c1.EQ.intstr( k: k ) )
THEN
430 nmats = nmats*10 + ic
441 IF( .NOT.
lsame( c1,
'Complex precision' ) )
THEN
442 WRITE( nout, fmt = 9990 )path
444 ELSE IF( nmats.LE.0 )
THEN
448 WRITE( nout, fmt = 9989 )path
450 ELSE IF(
lsamen( 2, c2,
'GE' ) )
THEN
455 CALL alareq( path, nmats, dotype, ntypes, nin, nout )
458 CALL cchkge( dotype, nm, mval, nn, nval, nnb2, nbval2, nns,
459 $ nsval, thresh, tsterr, lda, a( 1, 1 ),
460 $ a( 1, 2 ), a( 1, 3 ), b( 1, 1 ), b( 1, 2 ),
461 $ b( 1, 3 ), work, rwork, iwork, nout )
463 WRITE( nout, fmt = 9989 )path
467 CALL cdrvge( dotype, nn, nval, nrhs, thresh, tsterr, lda,
468 $ a( 1, 1 ), a( 1, 2 ), a( 1, 3 ), b( 1, 1 ),
469 $ b( 1, 2 ), b( 1, 3 ), b( 1, 4 ), s, work,
470 $ rwork, iwork, nout )
472 WRITE( nout, fmt = 9988 )path
475 ELSE IF(
lsamen( 2, c2,
'GB' ) )
THEN
479 la = ( 2*kdmax+1 )*nmax
480 lafac = ( 3*kdmax+1 )*nmax
482 CALL alareq( path, nmats, dotype, ntypes, nin, nout )
485 CALL cchkgb( dotype, nm, mval, nn, nval, nnb2, nbval2, nns,
486 $ nsval, thresh, tsterr, a( 1, 1 ), la,
487 $ a( 1, 3 ), lafac, b( 1, 1 ), b( 1, 2 ),
488 $ b( 1, 3 ), work, rwork, iwork, nout )
490 WRITE( nout, fmt = 9989 )path
494 CALL cdrvgb( dotype, nn, nval, nrhs, thresh, tsterr,
495 $ a( 1, 1 ), la, a( 1, 3 ), lafac, a( 1, 6 ),
496 $ b( 1, 1 ), b( 1, 2 ), b( 1, 3 ), b( 1, 4 ), s,
497 $ work, rwork, iwork, nout )
499 WRITE( nout, fmt = 9988 )path
502 ELSE IF(
lsamen( 2, c2,
'GT' ) )
THEN
507 CALL alareq( path, nmats, dotype, ntypes, nin, nout )
510 CALL cchkgt( dotype, nn, nval, nns, nsval, thresh, tsterr,
511 $ a( 1, 1 ), a( 1, 2 ), b( 1, 1 ), b( 1, 2 ),
512 $ b( 1, 3 ), work, rwork, iwork, nout )
514 WRITE( nout, fmt = 9989 )path
518 CALL cdrvgt( dotype, nn, nval, nrhs, thresh, tsterr,
519 $ a( 1, 1 ), a( 1, 2 ), b( 1, 1 ), b( 1, 2 ),
520 $ b( 1, 3 ), work, rwork, iwork, nout )
522 WRITE( nout, fmt = 9988 )path
525 ELSE IF(
lsamen( 2, c2,
'PO' ) )
THEN
530 CALL alareq( path, nmats, dotype, ntypes, nin, nout )
533 CALL cchkpo( dotype, nn, nval, nnb2, nbval2, nns, nsval,
534 $ thresh, tsterr, lda, a( 1, 1 ), a( 1, 2 ),
535 $ a( 1, 3 ), b( 1, 1 ), b( 1, 2 ), b( 1, 3 ),
536 $ work, rwork, nout )
538 WRITE( nout, fmt = 9989 )path
542 CALL cdrvpo( dotype, nn, nval, nrhs, thresh, tsterr, lda,
543 $ a( 1, 1 ), a( 1, 2 ), a( 1, 3 ), b( 1, 1 ),
544 $ b( 1, 2 ), b( 1, 3 ), b( 1, 4 ), s, work,
547 WRITE( nout, fmt = 9988 )path
550 ELSE IF(
lsamen( 2, c2,
'PS' ) )
THEN
559 CALL cchkps( dotype, nn, nval, nnb2, nbval2, nrank,
560 $ rankval, thresh, tsterr, lda, a( 1, 1 ),
561 $ a( 1, 2 ), a( 1, 3 ), piv, work, rwork,
564 WRITE( nout, fmt = 9989 )path
567 ELSE IF(
lsamen( 2, c2,
'PP' ) )
THEN
572 CALL alareq( path, nmats, dotype, ntypes, nin, nout )
575 CALL cchkpp( dotype, nn, nval, nns, nsval, thresh, tsterr,
576 $ lda, a( 1, 1 ), a( 1, 2 ), a( 1, 3 ),
577 $ b( 1, 1 ), b( 1, 2 ), b( 1, 3 ), work, rwork,
580 WRITE( nout, fmt = 9989 )path
584 CALL cdrvpp( dotype, nn, nval, nrhs, thresh, tsterr, lda,
585 $ a( 1, 1 ), a( 1, 2 ), a( 1, 3 ), b( 1, 1 ),
586 $ b( 1, 2 ), b( 1, 3 ), b( 1, 4 ), s, work,
589 WRITE( nout, fmt = 9988 )path
592 ELSE IF(
lsamen( 2, c2,
'PB' ) )
THEN
597 CALL alareq( path, nmats, dotype, ntypes, nin
600 CALL cchkpb( dotype, nn, nval, nnb2, nbval2, nns, nsval,
601 $ thresh, tsterr, lda, a( 1, 1 ), a( 1, 2 ),
602 $ a( 1, 3 ), b( 1, 1 ), b( 1, 2 ), b( 1, 3 ),
603 $ work, rwork, nout )
605 WRITE( nout, fmt = 9989 )path
609 CALL cdrvpb( dotype, nn, nval, nrhs, thresh, tsterr, lda,
610 $ a( 1, 1 ), a( 1, 2 ), a( 1, 3 ), b( 1, 1 ),
611 $ b( 1, 2 ), b( 1, 3 ), b( 1, 4 ), s, work,
614 WRITE( nout, fmt = 9988 )path
617 ELSE IF(
lsamen( 2, c2,
'PT' ) )
THEN
622 CALL alareq( path, nmats, dotype, ntypes, nin, nout )
625 CALL cchkpt( dotype, nn, nval, nns, nsval, thresh, tsterr,
626 $ a( 1, 1 ), s, a( 1, 2 ), b( 1, 1 ), b( 1, 2 ),
627 $ b( 1, 3 ), work, rwork, nout )
629 WRITE( nout, fmt = 9989 )path
633 CALL cdrvpt( dotype, nn, nval, nrhs, thresh, tsterr,
634 $ a( 1, 1 ), s, a( 1, 2 ), b( 1, 1 ), b( 1, 2
635 $ b( 1, 3 ), work, rwork, nout )
637 WRITE( nout, fmt = 9988 )path
640 ELSE IF(
lsamen( 2, c2,
'HE' ) )
THEN
646 CALL alareq( path, nmats, dotype, ntypes, nin, nout )
649 CALL cchkhe( dotype, nn, nval, nnb2, nbval2, nns, nsval,
650 $ thresh, tsterr, lda, a( 1, 1 ), a( 1, 2 ),
651 $ a( 1, 3 ), b( 1, 1 ), b( 1, 2 ), b( 1, 3 ),
652 $ work, rwork, iwork, nout )
654 WRITE( nout, fmt = 9989 )path
658 CALL cdrvhe( dotype, nn, nval, nrhs, thresh, tsterr, lda,
659 $ a( 1, 1 ), a( 1, 2 ), a( 1, 3 ), b( 1, 1 ),
660 $ b( 1, 2 ), b( 1, 3 ), work, rwork, iwork,
663 WRITE( nout, fmt = 9988 )path
666 ELSE IF(
lsamen( 2, c2,
'HR' ) )
THEN
672 CALL alareq( path, nmats, dotype, ntypes, nin, nout )
675 CALL cchkhe_rook(dotype, nn, nval, nnb2, nbval2, nns, nsval,
676 $ thresh, tsterr, lda, a( 1, 1 ), a( 1, 2 ),
677 $ a( 1, 3 ), b( 1, 1 ), b( 1, 2 ), b( 1, 3 ),
678 $ work, rwork, iwork, nout )
680 WRITE( nout, fmt = 9989 )path
684 CALL cdrvhe_rook( dotype, nn, nval, nrhs, thresh, tsterr,
685 $ lda, a( 1, 1 ), a( 1, 2 ), a( 1, 3 ),
686 $ b( 1, 1 ), b( 1, 2 ), b( 1, 3 ), work,
687 $ rwork, iwork, nout )
689 WRITE( nout, fmt = 9988 )path
692 ELSE IF(
lsamen( 2, c2
'HK'THEN
699 CALL alareq( path, nmats, dotype, ntypes, nin, nout )
702 CALL cchkhe_rk( dotype, nn, nval, nnb2, nbval2, nns, nsval,
703 $ thresh, tsterr, lda, a( 1, 1 ), a( 1, 2 ),
704 $ e, a( 1, 3 ), b( 1, 1 ), b( 1, 2 ),
705 $ b( 1, 3 ), work, rwork, iwork, nout )
707 WRITE( nout, fmt = 9989 )path
711 CALL cdrvhe_rk( dotype, nn, nval, nrhs, thresh, tsterr,
712 $ lda, a( 1, 1 ), a( 1, 2 ), e, a( 1, 3 ),
713 $ b( 1, 1 ), b( 1, 2 ), b( 1, 3 ), work,
714 $ rwork, iwork, nout )
716 WRITE( nout, fmt = 9988
719 ELSE IF(
lsamen( 2, c2,
'HA' ) )
THEN
725 CALL alareq( path, nmats, dotype, ntypes, nin, nout )
728 CALL cchkhe_aa( dotype, nn, nval, nnb2, nbval2, nns,
729 $ nsval, thresh, tsterr, lda,
730 $ a( 1, 1 ), a( 1, 2 ), a( 1, 3 ),
731 $ b( 1, 1 ), b( 1, 2 ), b( 1, 3 ),
732 $ work, rwork, iwork, nout )
734 WRITE( nout, fmt = 9989 )path
738 CALL cdrvhe_aa( dotype, nn, nval, nrhs, thresh, tsterr,
739 $ lda, a( 1, 1 ), a( 1, 2 ), a( 1, 3 ),
740 $ b( 1, 1 ), b( 1, 2 ), b( 1, 3 ),
741 $ work, rwork, iwork, nout )
743 WRITE( nout, fmt = 9988 )path
746 ELSE IF(
lsamen( 2, c2,
'H2'THEN
752 CALL alareq( path, nmats, dotype, ntypes, nin, nout )
756 $ nns, nsval, thresh, tsterr, lda,
757 $ a( 1, 1 ), a( 1, 2 ), a( 1, 3 ),
758 $ b( 1, 1 ), b( 1, 2 ), b( 1, 3 ),
759 $ work, rwork, iwork, nout )
761 WRITE( nout, fmt = 9989 )path
766 $ dotype, nn, nval, nrhs, thresh, tsterr,
767 $ lda, a( 1, 1 ), a( 1, 2 ), a( 1, 3 ),
768 $ b( 1, 1 ), b( 1, 2 ), b( 1, 3 ),
769 $ work, rwork, iwork, nout )
771 WRITE( nout, fmt = 9988 )path
774 ELSE IF(
lsamen( 2, c2,
'HP' ) )
THEN
780 CALL alareq( path, nmats, dotype, ntypes, nin, nout )
783 CALL cchkhp( dotype, nn, nval
784 $ lda, a( 1, 1 ), a( 1, 2 ), a( 1, 3 ),
785 $ b( 1, 1 ), b( 1, 2 ), b( 1, 3 ), work, rwork
788 WRITE( nout, fmt = 9989 )path
792 CALL cdrvhp( dotype, nn, nval, nrhs, thresh, tsterr, lda,
793 $ a( 1, 1 ), a( 1, 2 ), a( 1, 3 ), b( 1, 1 ),
794 $ b( 1, 2 ), b( 1, 3 ), work, rwork
797 WRITE( nout, fmt = 9988 )path
800 ELSE IF(
lsamen( 2, c2,
'SY' ) )
THEN
806 CALL alareq( path, nmats, dotype, ntypes, nin, nout )
809 CALL cchksy( dotype, nn, nval, nnb2, nbval2, nns, nsval,
810 $ thresh, tsterr, lda, a( 1, 1 ), a( 1, 2 ),
811 $ a( 1, 3 ), b( 1, 1 ), b( 1, 2 ), b( 1, 3 ),
812 $ work, rwork, iwork, nout )
814 WRITE( nout, fmt = 9989 )path
818 CALL cdrvsy( dotype, nn, nval, nrhs, thresh, tsterr, lda,
819 $ a( 1, 1 ), a( 1, 2 ), a( 1, 3 ), b( 1, 1 ),
820 $ b( 1, 2 ), b( 1, 3 ), work, rwork, iwork,
823 WRITE( nout, fmt = 9988 )path
826 ELSE IF(
lsamen( 2, c2,
'SR' ) )
THEN
832 CALL alareq( path, nmats, dotype, ntypes, nin, nout )
835 CALL cchksy_rook(dotype, nn, nval, nnb2, nbval2, nns, nsval,
836 $ thresh, tsterr, lda, a( 1, 1 ), a( 1, 2 ),
837 $ a( 1, 3 ), b( 1, 1 ), b( 1, 2 ), b( 1, 3 ),
838 $ work, rwork, iwork, nout )
840 WRITE( nout, fmt = 9989 )path
844 CALL cdrvsy_rook( dotype, nn, nval, nrhs, thresh, tsterr,
845 $ lda, a( 1, 1 ), a( 1, 2 ), a( 1, 3 ),
846 $ b( 1, 1 ), b( 1, 2 ), b( 1, 3 ), work,
847 $ rwork, iwork, nout )
849 WRITE( nout, fmt = 9988 )path
852 ELSE IF(
lsamen( 2, c2,
'SK' ) )
THEN
859 CALL alareq( path, nmats, dotype, ntypes, nin, nout )
862 CALL cchksy_rk( dotype, nn, nval, nnb2, nbval2, nns, nsval,
863 $ thresh, tsterr, lda, a( 1, 1 ), a( 1, 2 ),
864 $ e, a( 1, 3 ), b( 1, 1 ), b( 1, 2 ),
865 $ b( 1, 3 ), work, rwork, iwork, nout )
867 WRITE( nout, fmt = 9989 )path
871 CALL cdrvsy_rk( dotype, nn, nval, nrhs, thresh, tsterr,
872 $ lda, a( 1, 1 ), a( 1, 2 ), e, a( 1, 3 ),
873 $ b( 1, 1 ), b( 1, 2 ), b( 1, 3 ), work,
874 $ rwork, iwork, nout )
876 WRITE( nout, fmt = 9988 )path
879 ELSE IF(
lsamen( 2, c2,
'SA' ) )
THEN
884 CALL alareq( path, nmats, dotype, ntypes, nin, nout )
887 CALL cchksy_aa( dotype, nn, nval, nnb2, nbval2, nns, nsval,
888 $ thresh, tsterr, lda, a( 1, 1 ), a( 1, 2 ),
889 $ a( 1, 3 ), b( 1, 1 ), b( 1, 2 ),
890 $ b( 1, 3 ), work, rwork, iwork, nout )
892 WRITE( nout, fmt = 9989 )path
896 CALL cdrvsy_aa( dotype, nn, nval, nrhs, thresh, tsterr,
897 $ lda, a( 1, 1 ), a( 1, 2 ), a( 1, 3 ),
898 $ b( 1, 1 ), b( 1, 2 ), b( 1, 3 ), work,
899 $ rwork, iwork, nout )
901 WRITE( nout, fmt = 9988 )path
904 ELSE IF(
lsamen( 2, c2,
'S2' ) )
THEN
910 CALL alareq( path, nmats, dotype, ntypes, nin, nout )
914 $ nsval, thresh, tsterr, lda,
915 $ a( 1, 1 ), a( 1, 2 ), a( 1, 3 ),
916 $ b( 1, 1 ), b( 1, 2 ), b( 1, 3 ),
917 $ work, rwork, iwork, nout )
919 WRITE( nout, fmt = 9989 )path
924 $ dotype, nn, nval, nrhs, thresh, tsterr,
926 $ b( 1, 1 ), b( 1, 2 ), b( 1, 3 ), work,
927 $ rwork, iwork, nout )
929 WRITE( nout, fmt = 9988 )path
932 ELSE IF(
lsamen( 2, c2,
'SP' ) )
THEN
938 CALL alareq( path, nmats, dotype, ntypes, nin, nout )
941 CALL cchksp( dotype, nn, nval, nns, nsval, thresh, tsterr,
942 $ lda, a( 1, 1 ), a( 1, 2 ), a( 1, 3 ),
943 $ b( 1, 1 ), b( 1, 2 ), b( 1, 3 ), work, rwork,
946 WRITE( nout, fmt = 9989 )path
950 CALL cdrvsp( dotype, nn, nval, nrhs, thresh, tsterr, lda,
951 $ a( 1, 1 ), a( 1, 2 ), a( 1, 3 ), b( 1, 1 ),
952 $ b( 1, 2 ), b( 1, 3 ), work, rwork, iwork,
955 WRITE( nout, fmt = 9988 )path
958 ELSE IF(
lsamen( 2, c2,
'TR' ) )
THEN
963 CALL alareq( path, nmats, dotype, ntypes, nin, nout )
966 CALL cchktr( dotype, nn, nval, nnb2, nbval2, nns, nsval,
967 $ thresh, tsterr, lda, a( 1, 1 ), a( 1, 2 ),
968 $ b( 1, 1 ), b( 1, 2 ), b( 1, 3 ), work, rwork,
971 WRITE( nout, fmt = 9989 )path
974 ELSE IF(
lsamen( 2, c2,
'TP' ) )
THEN
979 CALL alareq( path, nmats, dotype, ntypes, nin, nout )
982 CALL cchktp( dotype, nn, nval, nns, nsval, thresh, tsterr,
983 $ lda, a( 1, 1 ), a( 1, 2 ), b( 1, 1 ),
984 $ b( 1, 2 ), b( 1, 3 ), work, rwork, nout
986 WRITE( nout, fmt = 9989 )path
989 ELSE IF(
lsamen( 2, c2,
'TB' ) )
THEN
994 CALL alareq( path, nmats, dotype, ntypes, nin, nout )
997 CALL cchktb( dotype, nn, nval, nns, nsval, thresh, tsterr,
998 $ lda, a( 1, 1 ), a( 1, 2 ), b( 1, 1 ),
999 $ b( 1, 2 ), b( 1, 3 ), work, rwork, nout )
1001 WRITE( nout, fmt = 9989 )path
1004 ELSE IF(
lsamen( 2, c2,
'QR' ) )
THEN
1009 CALL alareq( path, nmats, dotype, ntypes, nin, nout )
1012 CALL cchkqr( dotype, nm, mval, nn, nval, nnb, nbval, nxval,
1013 $ nrhs, thresh, tsterr, nmax, a( 1, 1 ),
1014 $ a( 1, 2 ), a( 1, 3 ), a( 1, 4 ), a( 1, 5 ),
1015 $ b( 1, 1 ), b( 1, 2 ), b( 1, 3 ), b( 1, 4 ),
1016 $ work, rwork, iwork, nout )
1018 WRITE( nout, fmt = 9989 )path
1021 ELSE IF(
lsamen( 2, c2,
'LQ' ) )
THEN
1026 CALL alareq( path, nmats, dotype, ntypes, nin, nout )
1029 CALL cchklq( dotype, nm, mval, nn, nval, nnb, nbval, nxval,
1030 $ nrhs, thresh, tsterr, nmax, a( 1, 1 ),
1031 $ a( 1, 2 ), a( 1, 3 ), a( 1, 4 ), a( 1, 5 ),
1032 $ b( 1, 1 ), b( 1, 2 ), b( 1, 3 ), b( 1, 4 ),
1033 $ work, rwork, nout )
1035 WRITE( nout, fmt = 9989 )path
1038 ELSE IF(
lsamen( 2, c2,
'QL' ) )
THEN
1046 CALL cchkql( dotype, nm, mval, nn, nval, nnb, nbval, nxval,
1047 $ nrhs, thresh, tsterr, nmax, a( 1, 1 ),
1048 $ a( 1, 2 ), a( 1, 3 ), a( 1, 4 ), a( 1, 5 ),
1049 $ b( 1, 1 ), b( 1, 2 ), b( 1, 3 ), b( 1, 4 ),
1050 $ work, rwork, nout )
1052 WRITE( nout, fmt = 9989 )path
1055 ELSE IF(
lsamen( 2, c2,
'RQ' ) )
THEN
1060 CALL alareq( path, nmats, dotype, ntypes, nin, nout )
1063 CALL cchkrq( dotype, nm, mval, nn, nval, nnb, nbval, nxval,
1064 $ nrhs, thresh, tsterr, nmax, a( 1, 1 ),
1065 $ a( 1, 2 ), a( 1, 3 ), a( 1, 4 ), a( 1, 5 ),
1066 $ b( 1, 1 ), b( 1, 2 ), b( 1, 3 ), b( 1, 4 ),
1067 $ work, rwork, iwork, nout )
1069 WRITE( nout, fmt = 9989 )path
1072 ELSE IF(
lsamen( 2, c2,
'EQ' ) )
THEN
1078 CALL cchkeq( threq, nout )
1080 WRITE( nout, fmt = 9989 )path
1083 ELSE IF(
lsamen( 2, c2,
'TZ' ) )
THEN
1088 CALL alareq( path, nmats, dotype, ntypes, nin, nout )
1091 CALL cchktz( dotype, nm, mval, nn, nval, thresh, tsterr,
1092 $ a( 1, 1 ), a( 1, 2 ), s( 1 ),
1093 $ b( 1, 1 ), work, rwork, nout )
1095 WRITE( nout, fmt = 9989 )path
1098 ELSE IF(
lsamen( 2, c2,
'QP' ) )
THEN
1103 CALL alareq( path, nmats, dotype, ntypes, nin, nout )
1106 CALL cchkq3( dotype, nm, mval, nn, nval, nnb, nbval, nxval,
1107 $ thresh, a( 1, 1 ), a( 1, 2 ), s( 1 ),
1108 $ b( 1, 1 ), work, rwork, iwork, nout )
1110 WRITE( nout, fmt = 9989 )path
1113 ELSE IF(
lsamen( 2, c2,
'LS' ) )
THEN
1118 CALL alareq( path, nmats, dotype, ntypes, nin, nout )
1121 CALL cdrvls( dotype, nm, mval, nn, nval, nns, nsval, nnb,
1122 $ nbval, nxval, thresh, tsterr, a( 1, 1 ),
1123 $ a( 1, 2 ), a( 1, 3 ), a( 1, 4 ), a( 1, 5 ),
1124 $ s( 1 ), s( nmax+1 ), nout )
1126 WRITE( nout, fmt = 9989 )path
1129 ELSE IF(
lsamen( 2, c2,
'QT' ) )
THEN
1134 CALL cchkqrt( thresh, tsterr, nm, mval, nn, nval, nnb,
1137 WRITE( nout, fmt = 9989 )path
1140 ELSE IF(
lsamen( 2, c2,
'QX' ) )
THEN
1145 CALL cchkqrtp( thresh, tsterr, nm, mval, nn, nval, nnb,
1148 WRITE( nout, fmt = 9989 )path
1151 ELSE IF(
lsamen( 2, c2,
'TQ' ) )
THEN
1156 CALL cchklqt( thresh, tsterr, nm, mval, nn, nval, nnb,
1159 WRITE( nout, fmt = 9989 )path
1162 ELSE IF(
lsamen( 2, c2,
'XQ' ) )
THEN
1167 CALL cchklqtp( thresh, tsterr, nm, mval, nn, nval, nnb,
1170 WRITE( nout, fmt = 9989 )path
1173 ELSE IF(
lsamen( 2, c2,
'TS' ) )
THEN
1178 CALL cchktsqr( thresh, tsterr, nm, mval, nn, nval, nnb,
1181 WRITE( nout, fmt = 9989 )path
1184 ELSE IF(
lsamen( 2, c2,
'HH' ) )
THEN
1189 CALL cchkunhr_col( thresh, tsterr, nm, mval, nn, nval, nnb,
1192 WRITE( nout, fmt = 9989 ) path
1197 WRITE( nout, fmt = 9990 )path
1209 WRITE( nout, fmt = 9998 )
1210 WRITE( nout, fmt = 9997 )s2 - s1
1212 DEALLOCATE (a, stat = allocatestatus)
1213 DEALLOCATE (b, stat = allocatestatus)
1214 DEALLOCATE (work, stat = allocatestatus)
1215 DEALLOCATE (rwork, stat = allocatestatus)
1217 9999
FORMAT( /
' Execution not attempted due to input errors' )
1218 9998
FORMAT( /
' End of tests' )
1219 9997
FORMAT(
' Total time used = ', f12.2,
' seconds', / )
1220 9996
FORMAT(
' Invalid input value: ', a4,
'=', i6,
'; must be >=',
1222 9995
FORMAT(
' Invalid input value: ', a4,
'=', i6,
'; must be <=',
1224 9994
FORMAT(
' Tests of the COMPLEX LAPACK routines ',
1225 $ /
' LAPACK VERSION ', i1,
'.', i1,
'.', i1,
1226 $ / /
' The following parameter values will be used:' )
1227 9993
FORMAT( 4x, a4,
': ', 10i6, / 11x, 10i6 )
1228 9992
FORMAT( / ' routines pass computational tests
if test ratio is
',
1229 $ 'less than
', F8.2, / )
1230 9991 FORMAT( ' relative machine
', A, ' is taken to be
', E16.6 )
1231 9990 FORMAT( / 1X, A3, ': unrecognized path name
' )
1232 9989 FORMAT( / 1X, A3, ' routines were not tested
' )
1233 9988 FORMAT( / 1X, A3, ' driver routines were not tested
' )
logical function lsamen(n, ca, cb)
LSAMEN
logical function lsame(ca, cb)
LSAME
subroutine alareq(path, nmats, dotype, ntypes, nin, nout)
ALAREQ
subroutine cchklq(dotype, nm, mval, nn, nval, nnb, nbval, nxval, nrhs, thresh, tsterr, nmax, a, af, aq, al, ac, b, x, xact, tau, work, rwork, nout)
CCHKLQ
subroutine cchkunhr_col(thresh, tsterr, nm, mval, nn, nval, nnb, nbval, nout)
CCHKUNHR_COL
subroutine cdrvsp(dotype, nn, nval, nrhs, thresh, tsterr, nmax, a, afac, ainv, b, x, xact, work, rwork, iwork, nout)
CDRVSP
subroutine cchkqr(dotype, nm, mval, nn, nval, nnb, nbval, nxval, nrhs, thresh, tsterr, nmax, a, af, aq, ar, ac, b, x, xact, tau, work, rwork, iwork, nout)
CCHKQR
subroutine cdrvhe_aa_2stage(dotype, nn, nval, nrhs, thresh, tsterr, nmax, a, afac, ainv, b, x, xact, work, rwork, iwork, nout)
CDRVHE_AA_2STAGE
subroutine cchksy_rook(dotype, nn, nval, nnb, nbval, nns, nsval, thresh, tsterr, nmax, a, afac, ainv, b, x, xact, work, rwork, iwork, nout)
CCHKSY_ROOK
subroutine cchkhe_aa_2stage(dotype, nn, nval, nnb, nbval, nns, nsval, thresh, tsterr, nmax, a, afac, ainv, b, x, xact, work, rwork, iwork, nout)
CCHKHE_AA_2STAGE
subroutine cchkpt(dotype, nn, nval, nns, nsval, thresh, tsterr, a, d, e, b, x, xact, work, rwork, nout)
CCHKPT
subroutine cchksy(dotype, nn, nval, nnb, nbval, nns, nsval, thresh, tsterr, nmax, a, afac, ainv, b, x, xact, work, rwork, iwork, nout)
CCHKSY
subroutine cchkgb(dotype, nm, mval, nn, nval, nnb, nbval, nns, nsval, thresh, tsterr, a, la, afac, lafac, b, x, xact, work, rwork, iwork, nout)
CCHKGB
subroutine cchkhe_aa(dotype, nn, nval, nnb, nbval, nns, nsval, thresh, tsterr, nmax, a, afac, ainv, b, x, xact, work, rwork, iwork, nout)
CCHKHE_AA
subroutine cdrvpp(dotype, nn, nval, nrhs, thresh, tsterr, nmax, a, afac, asav, b, bsav, x, xact, s, work, rwork, nout)
CDRVPP
subroutine cchkhe(dotype, nn, nval, nnb, nbval, nns, nsval, thresh, tsterr, nmax, a, afac, ainv, b, x, xact, work, rwork, iwork, nout)
CCHKHE
subroutine cchktz(dotype, nm, mval, nn, nval, thresh, tsterr, a, copya, s, tau, work, rwork, nout)
CCHKTZ
subroutine cdrvpo(dotype, nn, nval, nrhs, thresh, tsterr, nmax, a, afac, asav, b, bsav, x, xact, s, work, rwork, nout)
CDRVPO
subroutine cchksy_aa(dotype, nn, nval, nnb, nbval, nns, nsval, thresh, tsterr, nmax, a, afac, ainv, b, x, xact, work, rwork, iwork, nout)
CCHKSY_AA
subroutine cchkpp(dotype, nn, nval, nns, nsval, thresh, tsterr, nmax, a, afac, ainv, b, x, xact, work, rwork, nout)
CCHKPP
subroutine cchksp(dotype, nn, nval, nns, nsval, thresh, tsterr, nmax, a, afac, ainv, b, x, xact, work, rwork, iwork, nout)
CCHKSP
subroutine cdrvsy(dotype, nn, nval, nrhs, thresh, tsterr, nmax, a, afac, ainv, b, x, xact, work, rwork, iwork, nout)
CDRVSY
subroutine cdrvhe(dotype, nn, nval, nrhs, thresh, tsterr, nmax, a, afac, ainv, b, x, xact, work, rwork, iwork, nout)
CDRVHE
subroutine cchkql(dotype, nm, mval, nn, nval, nnb, nbval, nxval, nrhs, thresh, tsterr, nmax, a, af, aq, al, ac, b, x, xact, tau, work, rwork, nout)
CCHKQL
subroutine cchksy_rk(dotype, nn, nval, nnb, nbval, nns, nsval, thresh, tsterr, nmax, a, afac, e, ainv, b, x, xact, work, rwork, iwork, nout)
CCHKSY_RK
subroutine cdrvgt(dotype, nn, nval, nrhs, thresh, tsterr, a, af, b, x, xact, work, rwork, iwork, nout)
CDRVGT
subroutine cchkhe_rook(dotype, nn, nval, nnb, nbval, nns, nsval, thresh, tsterr, nmax, a, afac, ainv, b, x, xact, work, rwork, iwork, nout)
CCHKHE_ROOK
subroutine cdrvls(dotype, nm, mval, nn, nval, nns, nsval, nnb, nbval, nxval, thresh, tsterr, a, copya, b, copyb, c, s, copys, nout)
CDRVLS
subroutine cchkqrt(thresh, tsterr, nm, mval, nn, nval, nnb, nbval, nout)
CCHKQRT
subroutine cchkq3(dotype, nm, mval, nn, nval, nnb, nbval, nxval, thresh, a, copya, s, tau, work, rwork, iwork, nout)
CCHKQ3
subroutine cchkpo(dotype, nn, nval, nnb, nbval, nns, nsval, thresh, tsterr, nmax, a, afac, ainv, b, x, xact, work, rwork, nout)
CCHKPO
subroutine cdrvhe_aa(dotype, nn, nval, nrhs, thresh, tsterr, nmax, a, afac, ainv, b, x, xact, work, rwork, iwork, nout)
CDRVHE_AA
subroutine cchkeq(thresh, nout)
CCHKEQ
subroutine cdrvgb(dotype, nn, nval, nrhs, thresh, tsterr, a, la, afb, lafb, asav, b, bsav, x, xact, s, work, rwork, iwork, nout)
CDRVGB
subroutine cdrvhp(dotype, nn, nval, nrhs, thresh, tsterr, nmax, a, afac, ainv, b, x, xact, work, rwork, iwork, nout)
CDRVHP
subroutine cdrvsy_rk(dotype, nn, nval, nrhs, thresh, tsterr, nmax, a, afac, e, ainv, b, x, xact, work, rwork, iwork, nout)
CDRVSY_RK
subroutine cchksy_aa_2stage(dotype, nn, nval, nnb, nbval, nns, nsval, thresh, tsterr, nmax, a, afac, ainv, b, x, xact, work, rwork, iwork, nout)
CCHKSY_AA_2STAGE
subroutine cdrvge(dotype, nn, nval, nrhs, thresh, tsterr, nmax, a, afac, asav, b, bsav, x, xact, s, work, rwork, iwork, nout)
CDRVGE
subroutine cdrvpb(dotype, nn, nval, nrhs, thresh, tsterr, nmax, a, afac, asav, b, bsav, x, xact, s, work, rwork, nout)
CDRVPB
subroutine cchkrq(dotype, nm, mval, nn, nval, nnb, nbval, nxval, nrhs, thresh, tsterr, nmax, a, af, aq, ar, ac, b, x, xact, tau, work, rwork, iwork, nout)
CCHKRQ
subroutine cchkqrtp(thresh, tsterr, nm, mval, nn, nval, nnb, nbval, nout)
CCHKQRTP
subroutine cchktr(dotype, nn, nval, nnb, nbval, nns, nsval, thresh, tsterr, nmax, a, ainv, b, x, xact, work, rwork, nout)
CCHKTR
subroutine cchktp(dotype, nn, nval, nns, nsval, thresh, tsterr, nmax, ap, ainvp, b, x, xact, work, rwork, nout)
CCHKTP
subroutine cdrvhe_rk(dotype, nn, nval, nrhs, thresh, tsterr, nmax, a, afac, e, ainv, b, x, xact, work, rwork, iwork, nout)
CDRVHE_RK
subroutine cdrvsy_aa(dotype, nn, nval, nrhs, thresh, tsterr, nmax, a, afac, ainv, b, x, xact, work, rwork, iwork, nout)
CDRVSY_AA
subroutine cchkpb(dotype, nn, nval, nnb, nbval, nns, nsval, thresh, tsterr, nmax, a, afac, ainv, b, x, xact, work, rwork, nout)
CCHKPB
subroutine cchkgt(dotype, nn, nval, nns, nsval, thresh, tsterr, a, af, b, x, xact, work, rwork, iwork, nout)
CCHKGT
subroutine cdrvhe_rook(dotype, nn, nval, nrhs, thresh, tsterr, nmax, a, afac, ainv, b, x, xact, work, rwork, iwork, nout)
CDRVHE_ROOK
subroutine cdrvpt(dotype, nn, nval, nrhs, thresh, tsterr, a, d, e, b, x, xact, work, rwork, nout)
CDRVPT
subroutine cdrvsy_aa_2stage(dotype, nn, nval, nrhs, thresh, tsterr, nmax, a, afac, ainv, b, x, xact, work, rwork, iwork, nout)
CDRVSY_AA_2STAGE
subroutine cchkhe_rk(dotype, nn, nval, nnb, nbval, nns, nsval, thresh, tsterr, nmax, a, afac, e, ainv, b, x, xact, work, rwork, iwork, nout)
CCHKHE_RK
subroutine cchkhp(dotype, nn, nval, nns, nsval, thresh, tsterr, nmax, a, afac, ainv, b, x, xact, work, rwork, iwork, nout)
CCHKHP
subroutine cchkps(dotype, nn, nval, nnb, nbval, nrank, rankval, thresh, tsterr, nmax, a, afac, perm, piv, work, rwork, nout)
CCHKPS
subroutine cchktb(dotype, nn, nval, nns, nsval, thresh, tsterr, nmax, ab, ainv, b, x, xact, work, rwork, nout)
CCHKTB
subroutine cchkge(dotype, nm, mval, nn, nval, nnb, nbval, nns, nsval, thresh, tsterr, nmax, a, afac, ainv, b, x, xact, work, rwork, iwork, nout)
CCHKGE
subroutine cdrvsy_rook(dotype, nn, nval, nrhs, thresh, tsterr, nmax, a, afac, ainv, b, x, xact, work, rwork, iwork, nout)
CDRVSY_ROOK
subroutine cchktsqr(thresh, tsterr, nm, mval, nn, nval, nnb, nbval, nout)
CCHKQRT
subroutine cchklqt(thresh, tsterr, nm, mval, nn, nval, nnb, nbval, nout)
CCHKLQT
subroutine cchklqtp(thresh, tsterr, nm, mval, nn, nval, nnb, nbval, nout)
CCHKLQTP
subroutine ilaver(vers_major, vers_minor, vers_patch)
ILAVER returns the LAPACK version.
real function slamch(cmach)
SLAMCH
real function second()
SECOND Using ETIME