3 SUBROUTINE psgseptst( DESCA, UPLO, N, MATTYPE, IBTYPE, SUBTESTS,
4 $ THRESH, ORDER, ABSTOL, ISEED, A, COPYA, B,
5 $ COPYB, Z, LDA, WIN, WNEW, IFAIL, ICLUSTR,
6 $ GAP, IPREPAD, IPOSTPAD, WORK, LWORK, IWORK,
15 CHARACTER SUBTESTS, UPLO
16 INTEGER IBTYPE, INFO, IPOSTPAD, IPREPAD, LDA, LIWORK,
17 $ LWORK, MATTYPE, N, NOUT, ORDER
21 INTEGER DESCA( * ), ICLUSTR( * ), IFAIL( * ),
22 $ iseed( 4 ), iwork( * )
23 REAL A( LDA, * ), B( LDA, * ), COPYA( LDA, * ),
24 $ COPYB( LDA, * ), GAP( * ), WIN( * ), WNEW( * ),
25 $ work( * ), z( lda, * )
212 INTEGER BLOCK_CYCLIC_2D, DLEN_, DTYPE_, CTXT_, M_, N_,
213 $ MB_, NB_, RSRC_, CSRC_, LLD_
214 PARAMETER ( BLOCK_CYCLIC_2D = 1, dlen_ = 9, dtype_ = 1,
215 $ ctxt_ = 2, m_ = 3, n_ = 4, mb_ = 5, nb_ = 6,
216 $ rsrc_ = 7, csrc_ = 8, lld_ = 9 )
217 REAL ZERO, ONE, TEN, HALF
218 parameter( zero = 0.0e+0, one = 1.0e+0, ten = 10.0e+0,
221 parameter( padval = 19.25e+0 )
223 PARAMETER ( MAXTYP = 22 )
228 CHARACTER JOBZ, RANGE
230 INTEGER CONTEXT, I, IAM, IINFO, IL, IMODE, IN, INDD,
231 $ indwork, isizesubtst, isizesyevx, isizetst,
232 $ itype, iu, j, llwork, lsyevxsize, maxsize,
233 $ mycol, myrow, nb, ngen, nloc, nnodes, np,
234 $ npcol, nprow, nq, res, sizechk, sizemqrleft,
235 $ sizemqrright, sizeqrf, sizeqtq, sizesubtst,
236 $ sizesyevx, sizetms, sizetst, valsize, vecsize
237 REAL ANINV, ANORM, COND, MAXQTQNRM, MAXTSTNRM, OVFL,
238 $ QTQNRM, RTOVFL, RTUNFL, TEMP1, TSTNRM, ULP,
239 $ ULPINV, UNFL, VL, VU
242 INTEGER ISEEDIN( 4 ), KMAGN( MAXTYP ), KMODE( MAXTYP ),
244 DOUBLE PRECISION CTIME( 10 ), WTIME( 10 )
250 EXTERNAL LSAME, NUMROC, PSLAMCH, SLARAN
253 EXTERNAL blacs_gridinfo, blacs_pinfo, igamx2d, igebr2d,
260 INTRINSIC abs, int,
max,
min, mod, real, sqrt
263 DATA ktype / 1, 2, 4, 4, 4, 4, 4, 5, 5, 5, 5, 5, 8,
264 $ 8, 8, 9, 9, 9, 9, 9, 10, 11 /
265 DATA kmagn / 1, 1, 1, 1, 1, 2, 3, 1, 1, 1, 2, 3, 1,
266 $ 2, 3, 1, 1, 1, 2, 3, 1, 1 /
267 DATA kmode / 0, 0, 4, 3, 1, 4, 4, 4, 3, 1, 4, 4, 0,
268 $ 0, 0, 4, 3, 1, 4, 4, 3, 0 /
272 IF( block_cyclic_2d*csrc_*ctxt_*dlen_*dtype_*lld_*mb_*m_*nb_*n_*
277 context = desca( ctxt_ )
280 CALL blacs_pinfo( iam, nnodes )
281 CALL blacs_gridinfo( context, nprow, npcol, myrow, mycol )
287 CALL pslasizegsep( desca, iprepad, ipostpad, sizemqrleft,
288 $ sizemqrright, sizeqrf, sizetms, sizeqtq,
289 $ sizechk, sizesyevx, isizesyevx, sizesubtst,
290 $ isizesubtst, sizetst, isizetst )
292 IF( lwork.LT.sizetst )
THEN
296 CALL igamx2d( context,
'a',
' ', 1, 1, info, 1, 1, 1, -1, -1, 0 )
302 llwork = lwork - indwork + 1
304 ulp = pslamch( context,
'P' )
306 unfl = pslamch( context,
'Safe min' )
308 CALL slabad( unfl, ovfl )
309 rtunfl = sqrt( unfl )
310 rtovfl = sqrt( ovfl )
311 aninv = one / real(
max( 1, n ) )
315 IF( myrow.EQ.0 .AND. mycol.EQ.0 )
THEN
316 CALL igebs2d( context,
'a',
' ', 4, 1, iseed, 4 )
318 CALL igebr2d( context,
'a',
' ', 4, 1, iseed, 4, 0, 0 )
320 iseedin( 1 ) = iseed( 1 )
321 iseedin( 2 ) = iseed( 2 )
322 iseedin( 3 ) = iseed( 3 )
323 iseedin( 4 ) = iseed( 4 )
342 itype = ktype( mattype )
343 imode = kmode( mattype )
347 GO TO ( 10, 20, 30 )kmagn( mattype )
354 anorm = ( rtovfl*ulp )*aninv
358 anorm = rtunfl*n*ulpinv
362 IF( mattype.LE.15 )
THEN
365 cond = ulpinv*aninv / ten
373 IF( itype.EQ.1 )
THEN
378 work( indd+i-1 ) = zero
380 CALL pslaset(
'All', n, n, zero, zero, copya, 1, 1, desca )
383 ELSE IF( itype.EQ.2 )
THEN
388 work( indd+i-1 ) = one
390 CALL pslaset(
'All', n, n, zero, one, copya, 1, 1, desca )
393 ELSE IF( itype.EQ.4 )
THEN
397 CALL psfillpad( desca( ctxt_ ), sizetms, 1, work( indwork ),
398 $ sizetms, iprepad, ipostpad, padval+1.0e+0 )
400 CALL pslatms( n, n,
'S', iseed,
'S', work( indd ), imode,
401 $ cond, anorm, 0, 0,
'N', copya, 1, 1, desca,
402 $ order, work( indwork+iprepad ), sizetms,
406 CALL pschekpad( desca( ctxt_ ),
'PSLATMS1-WORK', sizetms, 1,
407 $ work( indwork ), sizetms, iprepad, ipostpad,
410 ELSE IF( itype.EQ.5 )
THEN
414 CALL psfillpad( desca( ctxt_ ), sizetms, 1, work( indwork ),
415 $ sizetms, iprepad, ipostpad, padval+2.0e+0 )
417 CALL pslatms( n, n,
'S', iseed,
'S', work( indd ), imode,
418 $ cond, anorm, n, n,
'N', copya, 1, 1, desca,
419 $ order, work( indwork+iprepad ), sizetms,
422 CALL pschekpad( desca( ctxt_ ),
'PSLATMS2-WORK', sizetms, 1,
423 $ work( indwork ), sizetms, iprepad, ipostpad,
428 ELSE IF( itype.EQ.8 )
THEN
432 np = numroc( n, desca( mb_ ), myrow, 0, nprow )
433 nq = numroc( n, desca( nb_ ), mycol, 0, npcol )
434 CALL psmatgen( desca( ctxt_ ),
'S',
'N', n, n, desca( mb_ ),
435 $ desca( nb_ ), copya, desca( lld_ ),
436 $ desca( rsrc_ ), desca( csrc_ ), iseed( 1 ),
437 $ 0, np, 0, nq, myrow, mycol, nprow, npcol )
441 ELSE IF( itype.EQ.9 )
THEN
446 CALL psfillpad( desca( ctxt_ ), sizetms, 1, work( indwork ),
447 $ sizetms, iprepad, ipostpad, padval+3.0e+0 )
449 CALL pslatms( n, n,
'S', iseed,
'S', work( indd ), imode,
450 $ cond, anorm, n, n,
'N', copya, 1, 1, desca,
451 $ order, work( indwork+iprepad ), sizetms,
456 CALL pschekpad( desca( ctxt_ ),
'PSLATMS3-WORK', sizetms, 1,
457 $ work( indwork ), sizetms, iprepad, ipostpad,
460 ELSE IF( itype.EQ.10 )
THEN
465 CALL pslaset(
'All', n, n, zero, zero, copya, 1, 1, desca )
466 np = numroc( n, desca( mb_ ), 0, 0, nprow )
467 nq = numroc( n, desca( nb_ ), 0, 0, npcol )
473 in =
min( 1+int( slaran( iseed )*real( nloc ) ), n-ngen )
475 CALL slatms( in, in,
'S', iseed,
'P', work( indd ),
476 $ imode, cond, anorm, 1, 1,
'N', a, lda,
477 $ work( indwork ), iinfo )
480 temp1 = abs( a( i-1, i ) ) /
481 $ sqrt( abs( a( i-1, i-1 )*a( i, i ) ) )
482 IF( temp1.GT.half )
THEN
483 a( i-1, i ) = half*sqrt( abs( a( i-1, i-1 )*a( i,
485 a( i, i-1 ) = a( i-1, i )
488 CALL pselset( copya, ngen+1, ngen+1, desca, a( 1, 1 ) )
490 CALL pselset( copya, ngen+i, ngen+i, desca,
492 CALL pselset( copya, ngen+i-1, ngen+i, desca,
494 CALL pselset( copya, ngen+i, ngen+i-1, desca,
502 ELSE IF( itype.EQ.11 )
THEN
511 in =
min( j, n-ngen )
513 work( indd+ngen+i ) = temp1
522 CALL psfillpad( desca( ctxt_ ), sizetms, 1, work( indwork ),
523 $ sizetms, iprepad, ipostpad, padval+4.0e+0 )
525 CALL pslatms( n, n,
'S', iseed,
'S', work( indd ), imode,
526 $ cond, anorm, 0, 0,
'N', copya, 1, 1, desca,
527 $ order, work( indwork+iprepad ), sizetms,
530 CALL pschekpad( desca( ctxt_ ),
'PSLATMS4-WORK', sizetms, 1,
531 $ work( indwork ), sizetms, iprepad, ipostpad,
543 $
CALL slasrt(
'I', n, work( indd ), iinfo )
547 CALL psfillpad( desca( ctxt_ ), sizetms, 1, work( indwork ),
548 $ sizetms, iprepad, ipostpad, padval+3.3e+0 )
554 iseed( 4 ) = mod( iseed( 4 )+257, 4096 )
555 iseed( 3 ) = mod( iseed( 3 )+192, 4096 )
556 iseed( 2 ) = mod( iseed( 2 )+35, 4096 )
557 iseed( 1 ) = mod( iseed( 1 )+128, 4096 )
558 CALL pslatms( n, n,
'S', iseed,
'P', work( indd ), 3, ten,
559 $ anorm, n, n,
'N', copyb, 1, 1, desca, order,
560 $ work( indwork+iprepad ), sizetms, iinfo )
562 CALL pschekpad( desca( ctxt_ ),
'PSLATMS5-WORK', sizetms, 1,
563 $ work( indwork ), sizetms, iprepad, ipostpad,
575 $ iseed, work( indd ), maxsize, vecsize,
578 lsyevxsize =
min( maxsize, lwork )
581 CALL psgsepsubtst( wknown, ibtype,
'v',
'a', uplo, n, vl, vu,
582 $ il, iu, thresh, abstol, a, copya, b, copyb,
583 $ z, 1, 1, desca, work( indd ), win, ifail,
584 $ iclustr, gap, iprepad, ipostpad,
585 $ work( indwork ), llwork, lsyevxsize, iwork,
586 $ isizesyevx, res, tstnrm, qtqnrm, nout )
593 IF( thresh.LE.zero )
THEN
596 ELSE IF( res.NE.0 )
THEN
602 IF( thresh.GT.zero .AND. lsame( subtests,
'Y' ) )
THEN
611 $ iseed, win( 1+iprepad ), maxsize,
616 CALL psgsepsubtst( .true., ibtype, jobz, range, uplo, n, vl,
617 $ vu, il, iu, thresh, abstol, a, copya, b,
618 $ copyb, z, 1, 1, desca, win( 1+iprepad ),
619 $ wnew, ifail, iclustr, gap, iprepad,
620 $ ipostpad, work( indwork ), llwork,
621 $ lsyevxsize, iwork, isizesyevx, res,
622 $ tstnrm, qtqnrm, nout )
625 passed =
'FAILED stest 1'
626 maxtstnrm =
max( tstnrm, maxtstnrm )
627 maxqtqnrm =
max( qtqnrm, maxqtqnrm )
638 $ iseed, win( 1+iprepad ), maxsize,
641 lsyevxsize = vecsize + int( slaran( iseed )*
642 $ real( maxsize-vecsize ) )
644 CALL psgsepsubtst( .true., ibtype, jobz, range, uplo, n, vl,
645 $ vu, il, iu, thresh, abstol, a, copya, b,
646 $ copyb, z, 1, 1, desca, win( 1+iprepad ),
647 $ wnew, ifail, iclustr, gap, iprepad,
648 $ ipostpad, work( indwork ), llwork,
649 $ lsyevxsize, iwork, isizesyevx, res,
650 $ tstnrm, qtqnrm, nout )
653 passed =
'FAILED stest 2'
654 maxtstnrm =
max( tstnrm, maxtstnrm )
655 maxqtqnrm =
max( qtqnrm, maxqtqnrm )
667 $ iseed, win( 1+iprepad ), maxsize,
671 CALL psgsepsubtst( .true., ibtype, jobz, range, uplo, n, vl,
672 $ vu, il, iu, thresh, abstol, a, copya, b,
673 $ copyb, z, 1, 1, desca, win( 1+iprepad ),
674 $ wnew, ifail, iclustr, gap, iprepad,
675 $ ipostpad, work( indwork ), llwork,
676 $ lsyevxsize, iwork, isizesyevx, res,
677 $ tstnrm, qtqnrm, nout )
680 maxtstnrm =
max( tstnrm, maxtstnrm )
681 maxqtqnrm =
max( qtqnrm, maxqtqnrm )
682 passed =
'FAILED stest 3'
699 $ iseed, win( 1+iprepad ), maxsize,
704 CALL psgsepsubtst( .true., ibtype, jobz, range, uplo, n, vl,
705 $ vu, il, iu, thresh, abstol, a, copya, b,
706 $ copyb, z, 1, 1, desca, win( 1+iprepad ),
707 $ wnew, ifail, iclustr, gap, iprepad,
708 $ ipostpad, work( indwork ), llwork,
709 $ lsyevxsize, iwork, isizesyevx, res,
710 $ tstnrm, qtqnrm, nout )
713 maxtstnrm =
max( tstnrm, maxtstnrm )
714 maxqtqnrm =
max( qtqnrm, maxqtqnrm )
715 passed =
'FAILED stest 4'
732 $ iseed, win( 1+iprepad ), maxsize,
737 CALL psgsepsubtst( .true., ibtype, jobz, range, uplo, n, vl,
738 $ vu, il, iu, thresh, abstol, a, copya, b,
739 $ copyb, z, 1, 1, desca, win( 1+iprepad ),
740 $ wnew, ifail, iclustr, gap, iprepad,
741 $ ipostpad, work( indwork ), llwork,
742 $ lsyevxsize, iwork, isizesyevx, res,
743 $ tstnrm, qtqnrm, nout )
746 maxtstnrm =
max( tstnrm, maxtstnrm )
747 maxqtqnrm =
max( qtqnrm, maxqtqnrm )
748 passed =
'FAILED stest 5'
764 $ iseed, win( 1+iprepad ), maxsize,
769 CALL psgsepsubtst( .true., ibtype, jobz, range, uplo, n, vl,
770 $ vu, il, iu, thresh, abstol, a, copya, b,
771 $ copyb, z, 1, 1, desca, win( 1+iprepad ),
772 $ wnew, ifail, iclustr, gap, iprepad,
773 $ ipostpad, work( indwork ), llwork,
774 $ lsyevxsize, iwork, isizesyevx, res,
775 $ tstnrm, qtqnrm, nout )
778 maxtstnrm =
max( tstnrm, maxtstnrm )
779 maxqtqnrm =
max( qtqnrm, maxqtqnrm )
780 passed =
'FAILED stest 6'
796 $ iseed, win( 1+iprepad ), maxsize,
798 lsyevxsize = vecsize + int( slaran( iseed )*
799 $ real( maxsize-vecsize ) )
801 CALL psgsepsubtst( .true., ibtype, jobz, range, uplo, n, vl,
802 $ vu, il, iu, thresh, abstol, a, copya, b,
803 $ copyb, z, 1, 1, desca, win( 1+iprepad ),
804 $ wnew, ifail, iclustr, gap, iprepad,
805 $ ipostpad, work( indwork ), llwork,
806 $ lsyevxsize, iwork, isizesyevx, res,
807 $ tstnrm, qtqnrm, nout )
810 maxtstnrm =
max( tstnrm, maxtstnrm )
811 maxqtqnrm =
max( qtqnrm, maxqtqnrm )
812 passed =
'FAILED stest 7'
828 $ iseed, win( 1+iprepad ), maxsize,
833 CALL psgsepsubtst( .true., ibtype, jobz, range, uplo, n, vl,
834 $ vu, il, iu, thresh, abstol, a, copya, b,
835 $ copyb, z, 1, 1, desca, win( 1+iprepad ),
836 $ wnew, ifail, iclustr, gap, iprepad,
837 $ ipostpad, work( indwork ), llwork,
838 $ lsyevxsize, iwork, isizesyevx, res,
839 $ tstnrm, qtqnrm, nout )
842 maxtstnrm =
max( tstnrm, maxtstnrm )
843 maxqtqnrm =
max( qtqnrm, maxqtqnrm )
844 passed =
'FAILED stest 8'
860 $ iseed, win( 1+iprepad ), maxsize,
865 CALL psgsepsubtst( .true., ibtype, jobz, range, uplo, n, vl,
866 $ vu, il, iu, thresh, abstol, a, copya, b,
867 $ copyb, z, 1, 1, desca, win( 1+iprepad ),
868 $ wnew, ifail, iclustr, gap, iprepad,
869 $ ipostpad, work( indwork ), llwork,
870 $ lsyevxsize, iwork, isizesyevx, res,
871 $ tstnrm, qtqnrm, nout )
874 maxtstnrm =
max( tstnrm, maxtstnrm )
875 maxqtqnrm =
max( qtqnrm, maxqtqnrm )
876 passed =
'FAILED stest 9'
893 $ iseed, win( 1+iprepad ), maxsize,
898 CALL psgsepsubtst( .true., ibtype, jobz, range, uplo, n, vl,
899 $ vu, il, iu, thresh, abstol, a, copya, b,
900 $ copyb, z, 1, 1, desca, win( 1+iprepad ),
901 $ wnew, ifail, iclustr, gap, iprepad,
902 $ ipostpad, work( indwork ), llwork,
903 $ lsyevxsize, iwork, isizesyevx, res,
904 $ tstnrm, qtqnrm, nout )
907 maxtstnrm =
max( tstnrm, maxtstnrm )
908 maxqtqnrm =
max( qtqnrm, maxqtqnrm )
909 passed =
'FAILED stest10'
927 $ iseed, win( 1+iprepad ), maxsize,
930 lsyevxsize = vecsize + int( slaran( iseed )*
931 $ real( maxsize-vecsize ) )
933 CALL psgsepsubtst( .true., ibtype, jobz, range, uplo, n, vl,
934 $ vu, il, iu, thresh, abstol, a, copya, b,
935 $ copyb, z, 1, 1, desca, win( 1+iprepad ),
936 $ wnew, ifail, iclustr, gap, iprepad,
937 $ ipostpad, work( indwork ), llwork,
938 $ lsyevxsize, iwork, isizesyevx, res,
939 $ tstnrm, qtqnrm, nout )
942 maxtstnrm =
max( tstnrm, maxtstnrm )
943 maxqtqnrm =
max( qtqnrm, maxqtqnrm )
944 passed =
'FAILED stest11'
961 $ iseed, win( 1+iprepad ), maxsize,
966 CALL psgsepsubtst( .true., ibtype, jobz, range, uplo, n, vl,
967 $ vu, il, iu, thresh, abstol, a, copya, b,
968 $ copyb, z, 1, 1, desca, win( 1+iprepad ),
969 $ wnew, ifail, iclustr, gap, iprepad,
970 $ ipostpad, work( indwork ), llwork,
971 $ lsyevxsize, iwork, isizesyevx, res,
972 $ tstnrm, qtqnrm, nout )
975 maxtstnrm =
max( tstnrm, maxtstnrm )
976 maxqtqnrm =
max( qtqnrm, maxqtqnrm )
977 passed =
'FAILED stest12'
995 $ iseed, win( 1+iprepad ), maxsize,
998 lsyevxsize = valsize + int( slaran( iseed )*
999 $ real( vecsize-valsize ) )
1001 CALL psgsepsubtst( .true., ibtype, jobz, range, uplo, n, vl,
1002 $ vu, il, iu, thresh, abstol, a, copya, b,
1003 $ copyb, z, 1, 1, desca, win( 1+iprepad ),
1004 $ wnew, ifail, iclustr, gap, iprepad,
1005 $ ipostpad, work( indwork ), llwork,
1006 $ lsyevxsize, iwork, isizesyevx, res,
1007 $ tstnrm, qtqnrm, nout )
1010 maxtstnrm =
max( tstnrm, maxtstnrm )
1011 maxqtqnrm =
max( qtqnrm, maxqtqnrm )
1012 passed =
'FAILED stest13'
1020 CALL igamx2d( context,
'All',
' ', 1, 1, info, 1, -1, -1, -1, -1,
1023 IF( info.EQ.1 )
THEN
1025 WRITE( nout, fmt = 9994 )
'C '
1026 WRITE( nout, fmt = 9993 )iseedin( 1 )
1027 WRITE( nout, fmt = 9992 )iseedin( 2 )
1028 WRITE( nout, fmt = 9991 )iseedin( 3 )
1029 WRITE( nout, fmt = 9990 )iseedin( 4 )
1030 IF( lsame( uplo,
'L' ) )
THEN
1031 WRITE( nout, fmt = 9994 )
' UPLO= ''L'' '
1033 WRITE( nout, fmt = 9994 )
' UPLO= ''U'' '
1035 IF( lsame( subtests,
'Y' ) )
THEN
1036 WRITE( nout, fmt = 9994 )
' SUBTESTS= ''Y'' '
1038 WRITE( nout, fmt = 9994 )
' SUBTESTS= ''N'' '
1040 WRITE( nout, fmt = 9989 )n
1041 WRITE( nout, fmt = 9988 )nprow
1042 WRITE( nout, fmt = 9987 )npcol
1043 WRITE( nout, fmt = 9986 )nb
1044 WRITE( nout, fmt = 9985 )mattype
1045 WRITE( nout, fmt = 9984 )ibtype
1046 WRITE( nout, fmt = 9982 )abstol
1047 WRITE( nout, fmt = 9981 )thresh
1048 WRITE( nout, fmt = 9994 )
'C '
1052 CALL slcombine( context,
'All',
'>',
'W', 6, 1, wtime )
1053 CALL slcombine( context,
'All',
'>',
'C', 6, 1, ctime )
1055 IF( info.EQ.0 .OR. info.EQ.1 )
THEN
1056 IF( wtime( 1 ).GE.0.0 )
THEN
1057 WRITE( nout, fmt = 9999 )n, nb, nprow, npcol, mattype,
1058 $ ibtype, subtests, wtime( 1 ), ctime( 1 ), maxtstnrm,
1061 WRITE( nout, fmt = 9998 )n, nb, nprow, npcol, mattype,
1062 $ ibtype, subtests, ctime( 1 ), maxtstnrm, passed
1064 ELSE IF( info.EQ.2 )
THEN
1065 IF( wtime( 1 ).GE.0.0 )
THEN
1066 WRITE( nout, fmt = 9997 )n, nb, nprow, npcol, mattype,
1067 $ ibtype, subtests, wtime( 1 ), ctime( 1 )
1069 WRITE( nout, fmt = 9996 )n, nb, nprow, npcol, mattype,
1070 $ ibtype, subtests, ctime( 1 )
1072 ELSE IF( info.EQ.3 )
THEN
1073 WRITE( nout, fmt = 9995 )n, nb, nprow, npcol, mattype,
1081 9999
FORMAT( 1x, i5, 1x, i3, 1x, i3, 1x, i3, 1x, i3, 3x, i3, 4x, a1,
1082 $ 1x, f8.2, 1x, f8.2, 1x, g9.2, 1x, a14 )
1083 9998
FORMAT( 1x, i5, 1x, i3, 1x, i3, 1x, i3, 1x, i3, 3x, i3, 4x, a1,
1084 $ 1x, 8x, 1x, f8.2, 1x, g9.2, a14 )
1085 9997
FORMAT( 1x, i5, 1x, i3, 1x, i3, 1x, i3, 1x, i3, 3x, i3, 4x, a1,
1086 $ 1x, f8.2, 1x, f8.2, 11x,
'Bypassed' )
1087 9996
FORMAT( 1x, i5, 1x, i3, 1x, i3, 1x, i3, 1x, i3, 3x, i3, 4x, a1,
1088 $ 1x, 8x, 1x, f8.2, 11x,
'Bypassed' )
1089 9995
FORMAT( 1x, i5, 1x, i3, 1x, i3, 1x, i3, 1x, i3, 3x, i3, 4x, a1,
1090 $ 22x,
'Bad MEMORY parameters' )
1092 9993
FORMAT(
' ISEED( 1 ) =', i8 )
1093 9992
FORMAT(
' ISEED( 2 ) =', i8 )
1094 9991
FORMAT(
' ISEED( 3 ) =', i8 )
1095 9990
FORMAT(
' ISEED( 4 ) =', i8 )
1096 9989
FORMAT(
' N=', i8 )
1097 9988
FORMAT(
' NPROW=', i8 )
1098 9987
FORMAT(
' NPCOL=', i8 )
1099 9986
FORMAT(
' NB=', i8 )
1100 9985
FORMAT(
' MATTYPE=', i8 )
1101 9984
FORMAT(
' IBTYPE=', i8 )
1102 9983
FORMAT(
' SUBTESTS=', a1 )
1103 9982
FORMAT(
' ABSTOL=', d16.6 )
1104 9981
FORMAT(
' THRESH=', d16.6 )
1105 9980
FORMAT(
' Increase TOTMEM in PSGSEPDRIVER' )