3 SUBROUTINE pzgseptst( 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, RWORK,
7 $ LRWORK, IWORK, LIWORK, NOUT, INFO )
15 CHARACTER SUBTESTS, UPLO
16 INTEGER IBTYPE, INFO, IPOSTPAD, IPREPAD, LDA, LIWORK,
17 $ LRWORK, LWORK, MATTYPE, N, NOUT, ORDER
18 DOUBLE PRECISION ABSTOL, THRESH
21 INTEGER DESCA( * ), ICLUSTR( * ), IFAIL( * ),
22 $ iseed( 4 ), iwork( * )
23 DOUBLE PRECISION GAP( * ), RWORK( * ), WIN( * ), WNEW( * )
24 COMPLEX*16 A( LDA, * ), B( LDA, * ), COPYA( LDA, * ),
25 $ copyb( lda, * ), work( * ), z( lda, * )
218 INTEGER BLOCK_CYCLIC_2D, DLEN_, DTYPE_, CTXT_, M_, N_,
219 $ MB_, NB_, RSRC_, CSRC_, LLD_
220 PARAMETER ( BLOCK_CYCLIC_2D = 1, dlen_ = 9, dtype_ = 1,
221 $ ctxt_ = 2, m_ = 3, n_ = 4, mb_ = 5, nb_ = 6,
222 $ rsrc_ = 7, csrc_ = 8, lld_ = 9 )
223 DOUBLE PRECISION ZERO, ONE, TEN, HALF
224 parameter( zero = 0.0d+0, one = 1.0d+0, ten = 10.0d+0,
227 parameter( padval = ( 19.25d+0, 1.1d+1 ) )
229 PARAMETER ( ZZERO = ( 0.0d+0, 0.0d+0 ) )
231 parameter( zone = ( 1.0d+0, 0.0d+0 ) )
233 parameter( maxtyp = 22 )
238 CHARACTER JOBZ, RANGE
240 INTEGER CONTEXT, I, IAM, IINFO, IL, IMODE, IN, INDD,
241 $ indrwork, indwork, isizeheevx, isizesubtst,
242 $ isizetst, itype, iu, j, lheevxsize, llrwork,
243 $ llwork, maxsize, mycol, myrow, nb, ngen, nloc,
244 $ nnodes, np, npcol, nprow, nq, res, rsizechk,
245 $ rsizeheevx, rsizeqtq, rsizesubtst, rsizetst,
246 $ sizeheevx, sizemqrleft, sizemqrright, sizeqrf,
247 $ sizesubtst, sizetms, sizetst, valsize, vecsize
248 DOUBLE PRECISION ANINV, ANORM, COND, MAXQTQNRM, MAXTSTNRM, OVFL,
249 $ QTQNRM, RTOVFL, RTUNFL, TEMP1, TSTNRM, ULP,
250 $ ULPINV, UNFL, VL, VU
253 INTEGER ISEEDIN( 4 ), KMAGN( MAXTYP ), KMODE( MAXTYP ),
255 DOUBLE PRECISION CTIME( 10 ), WTIME( 10 )
260 DOUBLE PRECISION DLARAN, PDLAMCH
261 EXTERNAL LSAME, NUMROC, DLARAN, PDLAMCH
264 EXTERNAL blacs_gridinfo, blacs_pinfo, dlabad, dlasrt,
271 INTRINSIC abs, dble, int,
max,
min, mod, sqrt
274 DATA ktype / 1, 2, 4, 4, 4, 4, 4, 5, 5, 5, 5, 5, 8,
275 $ 8, 8, 9, 9, 9, 9, 9, 10, 11 /
276 DATA kmagn / 1, 1, 1, 1, 1, 2, 3, 1, 1, 1, 2, 3, 1,
277 $ 2, 3, 1, 1, 1, 2, 3, 1, 1 /
278 DATA kmode / 0, 0, 4, 3, 1, 4, 4, 4, 3, 1, 4, 4, 0,
279 $ 0, 0, 4, 3, 1, 4, 4, 3, 0 /
283 IF( block_cyclic_2d*csrc_*ctxt_*dlen_*dtype_*lld_*mb_*m_*nb_*n_*
288 context = desca( ctxt_ )
291 CALL blacs_pinfo( iam, nnodes )
292 CALL blacs_gridinfo( context, nprow, npcol, myrow, mycol )
298 CALL pzlasizegsep( desca, iprepad, ipostpad, sizemqrleft,
299 $ sizemqrright, sizeqrf, sizetms, rsizeqtq,
300 $ rsizechk, sizeheevx, rsizeheevx, isizeheevx,
301 $ sizesubtst, rsizesubtst, isizesubtst, sizetst,
302 $ rsizetst, isizetst )
304 IF( lrwork.LT.rsizetst )
THEN
308 CALL igamx2d( context,
'a',
' ', 1, 1, info, 1, 1, 1, -1, -1, 0 )
315 llwork = lwork - indwork + 1
316 llrwork = lrwork - indrwork + 1
318 ulp = pdlamch( context,
'P' )
320 unfl = pdlamch( context,
'Safe min' )
322 CALL dlabad( unfl, ovfl )
323 rtunfl = sqrt( unfl )
324 rtovfl = sqrt( ovfl )
325 aninv = one / dble(
max( 1, n ) )
329 IF( myrow.EQ.0 .AND. mycol.EQ.0 )
THEN
330 CALL igebs2d( context,
'a',
' ', 4, 1, iseed, 4 )
332 CALL igebr2d( context,
'a',
' ', 4, 1, iseed, 4, 0, 0 )
334 iseedin( 1 ) = iseed( 1 )
335 iseedin( 2 ) = iseed( 2 )
336 iseedin( 3 ) = iseed( 3 )
337 iseedin( 4 ) = iseed( 4 )
356 itype = ktype( mattype )
357 imode = kmode( mattype )
361 GO TO ( 10, 20, 30 )kmagn( mattype )
368 anorm = ( rtovfl*ulp )*aninv
372 anorm = rtunfl*n*ulpinv
376 IF( mattype.LE.15 )
THEN
379 cond = ulpinv*aninv / ten
387 IF( itype.EQ.1 )
THEN
392 rwork( indd+i-1 ) = zero
394 CALL pzlaset(
'All', n, n, zzero, zzero, copya, 1, 1,
398 ELSE IF( itype.EQ.2 )
THEN
403 rwork( indd+i-1 ) = one
405 CALL pzlaset(
'All', n, n, zzero, zone, copya, 1, 1, desca )
408 ELSE IF( itype.EQ.4 )
THEN
412 CALL pzfillpad( desca( ctxt_ ), sizetms, 1, work( indwork ),
413 $ sizetms, iprepad, ipostpad, padval+1.0d+0 )
415 CALL pzlatms( n, n,
'S', iseed,
'S', rwork( indd ), imode,
416 $ cond, anorm, 0, 0,
'N', copya, 1, 1, desca,
417 $ order, work( indwork+iprepad ), sizetms,
421 CALL pzchekpad( desca( ctxt_ ),
'PZLATMS1-WORK', sizetms, 1,
422 $ work( indwork ), sizetms, iprepad, ipostpad,
425 ELSE IF( itype.EQ.5 )
THEN
429 CALL pzfillpad( desca( ctxt_ ), sizetms, 1, work( indwork ),
430 $ sizetms, iprepad, ipostpad, padval+2.0d+0 )
432 CALL pzlatms( n, n,
'S', iseed,
'S', rwork( indd ), imode,
433 $ cond, anorm, n, n,
'N', copya, 1, 1, desca,
434 $ order, work( indwork+iprepad ), sizetms,
437 CALL pzchekpad( desca( ctxt_ ),
'PZLATMS2-WORK', sizetms, 1,
438 $ work( indwork ), sizetms, iprepad, ipostpad,
443 ELSE IF( itype.EQ.8 )
THEN
447 np = numroc( n, desca( mb_ ), myrow, 0, nprow )
448 nq = numroc( n, desca( nb_ ), mycol, 0, npcol )
449 CALL pzmatgen( desca( ctxt_ ),
'H',
'N', n, n, desca( mb_ ),
450 $ desca( nb_ ), copya, desca( lld_ ),
451 $ desca( rsrc_ ), desca( csrc_ ), iseed( 1 ),
452 $ 0, np, 0, nq, myrow, mycol, nprow, npcol )
456 ELSE IF( itype.EQ.9 )
THEN
461 CALL pzfillpad( desca( ctxt_ ), sizetms, 1, work( indwork ),
462 $ sizetms, iprepad, ipostpad, padval+3.0d+0 )
464 CALL pzlatms( n, n,
'S', iseed,
'S', rwork( indd ), imode,
465 $ cond, anorm, n, n,
'N', copya, 1, 1, desca,
466 $ order, work( indwork+iprepad ), sizetms,
471 CALL pzchekpad( desca( ctxt_ ),
'PZLATMS3-WORK', sizetms, 1,
472 $ work( indwork ), sizetms, iprepad, ipostpad,
475 ELSE IF( itype.EQ.10 )
THEN
480 CALL pzlaset(
'All', n, n, zzero, zzero, copya, 1, 1,
482 np = numroc( n, desca( mb_ ), 0, 0, nprow )
483 nq = numroc( n, desca( nb_ ), 0, 0, npcol )
489 in =
min( 1+int( dlaran( iseed )*dble( nloc ) ), n-ngen )
491 CALL zlatms( in, in,
'S', iseed,
'P', rwork( indd ),
492 $ imode, cond, anorm, 1, 1,
'N', a, lda,
493 $ work( indwork ), iinfo )
496 temp1 = abs( a( i-1, i ) ) /
497 $ sqrt( abs( a( i-1, i-1 )*a( i, i ) ) )
498 IF( temp1.GT.half )
THEN
499 a( i-1, i ) = half*sqrt( abs( a( i-1, i-1 )*a( i,
501 a( i, i-1 ) = a( i-1, i )
504 CALL pzelset( copya, ngen+1, ngen+1, desca, a( 1, 1 ) )
506 CALL pzelset( copya, ngen+i, ngen+i, desca,
508 CALL pzelset( copya, ngen+i-1, ngen+i, desca,
510 CALL pzelset( copya, ngen+i, ngen+i-1, desca,
518 ELSE IF( itype.EQ.11 )
THEN
527 in =
min( j, n-ngen )
529 rwork( indd+ngen+i ) = temp1
538 CALL pzfillpad( desca( ctxt_ ), sizetms, 1, work( indwork ),
539 $ sizetms, iprepad, ipostpad, padval+4.0d+0 )
541 CALL pzlatms( n, n,
'S', iseed,
'S', rwork( indd ), imode,
542 $ cond, anorm, 0, 0,
'N', copya, 1, 1, desca,
543 $ order, work( indwork+iprepad ), sizetms,
546 CALL pzchekpad( desca( ctxt_ ),
'PZLATMS4-WORK', sizetms, 1,
547 $ work( indwork ), sizetms, iprepad, ipostpad,
559 $
CALL dlasrt(
'I', n, rwork( indd ), iinfo )
563 CALL pzfillpad( desca( ctxt_ ), sizetms, 1, work( indwork ),
564 $ sizetms, iprepad, ipostpad, padval+3.3d+0 )
570 iseed( 4 ) = mod( iseed( 4 )+257, 4096 )
571 iseed( 3 ) = mod( iseed( 3 )+192, 4096 )
572 iseed( 2 ) = mod( iseed( 2 )+35, 4096 )
573 iseed( 1 ) = mod( iseed( 1 )+128, 4096 )
574 CALL pzlatms( n, n,
'S', iseed,
'P', rwork( indd ), 3, ten,
575 $ anorm, n, n,
'N', copyb, 1, 1, desca, order,
576 $ work( indwork+iprepad ), sizetms, iinfo )
578 CALL pzchekpad( desca( ctxt_ ),
'PZLATMS5-WORK', sizetms, 1,
579 $ work( indwork ), sizetms, iprepad, ipostpad,
591 $ iseed, rwork( indd ), maxsize, vecsize,
594 lheevxsize =
min( maxsize, lrwork )
597 CALL pzgsepsubtst( wknown, ibtype,
'v',
'a', uplo, n, vl, vu,
598 $ il, iu, thresh, abstol, a, copya, b, copyb,
599 $ z, 1, 1, desca, rwork( indd ), win, ifail,
600 $ iclustr, gap, iprepad, ipostpad,
601 $ work( indwork ), llwork, rwork( indrwork ),
602 $ llrwork, lheevxsize, iwork, isizeheevx, res,
603 $ tstnrm, qtqnrm, nout )
610 IF( thresh.LE.zero )
THEN
613 ELSE IF( res.NE.0 )
THEN
619 IF( thresh.GT.zero .AND. lsame( subtests,
'Y' ) )
THEN
628 $ iseed, win( 1+iprepad ), maxsize,
633 CALL pzgsepsubtst( .true., ibtype, jobz, range, uplo, n, vl,
634 $ vu, il, iu, thresh, abstol, a, copya, b,
635 $ copyb, z, 1, 1, desca, win( 1+iprepad ),
636 $ wnew, ifail, iclustr, gap, iprepad,
637 $ ipostpad, work( indwork ), llwork, rwork,
638 $ lrwork, lheevxsize, iwork, isizeheevx,
639 $ res, tstnrm, qtqnrm, nout )
642 passed =
'FAILED stest 1'
643 maxtstnrm =
max( tstnrm, maxtstnrm )
644 maxqtqnrm =
max( qtqnrm, maxqtqnrm )
655 $ iseed, win( 1+iprepad ), maxsize,
658 lheevxsize = vecsize + int( dlaran( iseed )*
659 $ dble( maxsize-vecsize ) )
661 CALL pzgsepsubtst( .true., ibtype, jobz, range, uplo, n, vl,
662 $ vu, il, iu, thresh, abstol, a, copya, b,
663 $ copyb, z, 1, 1, desca, win( 1+iprepad ),
664 $ wnew, ifail, iclustr, gap, iprepad,
665 $ ipostpad, work( indwork ), llwork, rwork,
666 $ lrwork, lheevxsize, iwork, isizeheevx,
667 $ res, tstnrm, qtqnrm, nout )
670 passed =
'FAILED stest 2'
671 maxtstnrm =
max( tstnrm, maxtstnrm )
672 maxqtqnrm =
max( qtqnrm, maxqtqnrm )
684 $ iseed, win( 1+iprepad ), maxsize,
688 CALL pzgsepsubtst( .true., ibtype, jobz, range, uplo, n, vl,
689 $ vu, il, iu, thresh, abstol, a, copya, b,
690 $ copyb, z, 1, 1, desca, win( 1+iprepad ),
691 $ wnew, ifail, iclustr, gap, iprepad,
692 $ ipostpad, work( indwork ), llwork, rwork,
693 $ lrwork, lheevxsize, iwork, isizeheevx,
694 $ res, tstnrm, qtqnrm, nout )
697 maxtstnrm =
max( tstnrm, maxtstnrm )
698 maxqtqnrm =
max( qtqnrm, maxqtqnrm )
699 passed =
'FAILED stest 3'
716 $ iseed, win( 1+iprepad ), maxsize,
721 CALL pzgsepsubtst( .true., ibtype, jobz, range, uplo, n, vl,
722 $ vu, il, iu, thresh, abstol, a, copya, b,
723 $ copyb, z, 1, 1, desca, win( 1+iprepad ),
724 $ wnew, ifail, iclustr, gap, iprepad,
725 $ ipostpad, work( indwork ), llwork, rwork,
726 $ lrwork, lheevxsize, iwork, isizeheevx,
727 $ res, tstnrm, qtqnrm, nout )
730 maxtstnrm =
max( tstnrm, maxtstnrm )
731 maxqtqnrm =
max( qtqnrm, maxqtqnrm )
732 passed =
'FAILED stest 4'
749 $ iseed, win( 1+iprepad ), maxsize,
754 CALL pzgsepsubtst( .true., ibtype, jobz, range, uplo, n, vl,
755 $ vu, il, iu, thresh, abstol, a, copya, b,
756 $ copyb, z, 1, 1, desca, win( 1+iprepad ),
757 $ wnew, ifail, iclustr, gap, iprepad,
758 $ ipostpad, work( indwork ), llwork, rwork,
759 $ lrwork, lheevxsize, iwork, isizeheevx,
760 $ res, tstnrm, qtqnrm, nout )
763 maxtstnrm =
max( tstnrm, maxtstnrm )
764 maxqtqnrm =
max( qtqnrm, maxqtqnrm )
765 passed =
'FAILED stest 5'
781 $ iseed, win( 1+iprepad ), maxsize,
786 CALL pzgsepsubtst( .true., ibtype, jobz, range, uplo, n, vl,
787 $ vu, il, iu, thresh, abstol, a, copya, b,
788 $ copyb, z, 1, 1, desca, win( 1+iprepad ),
789 $ wnew, ifail, iclustr, gap, iprepad,
790 $ ipostpad, work( indwork ), llwork, rwork,
791 $ lrwork, lheevxsize, iwork, isizeheevx,
792 $ res, tstnrm, qtqnrm, nout )
795 maxtstnrm =
max( tstnrm, maxtstnrm )
796 maxqtqnrm =
max( qtqnrm, maxqtqnrm )
797 passed =
'FAILED stest 6'
813 $ iseed, win( 1+iprepad ), maxsize,
815 lheevxsize = vecsize + int( dlaran( iseed )*
816 $ dble( maxsize-vecsize ) )
818 CALL pzgsepsubtst( .true., ibtype, jobz, range, uplo, n, vl,
819 $ vu, il, iu, thresh, abstol, a, copya, b,
820 $ copyb, z, 1, 1, desca, win( 1+iprepad ),
821 $ wnew, ifail, iclustr, gap, iprepad,
822 $ ipostpad, work( indwork ), llwork, rwork,
823 $ lrwork, lheevxsize, iwork, isizeheevx,
824 $ res, tstnrm, qtqnrm, nout )
827 maxtstnrm =
max( tstnrm, maxtstnrm )
828 maxqtqnrm =
max( qtqnrm, maxqtqnrm )
829 passed =
'FAILED stest 7'
845 $ iseed, win( 1+iprepad ), maxsize,
850 CALL pzgsepsubtst( .true., ibtype, jobz, range, uplo, n, vl,
851 $ vu, il, iu, thresh, abstol, a, copya, b,
852 $ copyb, z, 1, 1, desca, win( 1+iprepad ),
853 $ wnew, ifail, iclustr, gap, iprepad,
854 $ ipostpad, work( indwork ), llwork, rwork,
855 $ lrwork, lheevxsize, iwork, isizeheevx,
856 $ res, tstnrm, qtqnrm, nout )
859 maxtstnrm =
max( tstnrm, maxtstnrm )
860 maxqtqnrm =
max( qtqnrm, maxqtqnrm )
861 passed =
'FAILED stest 8'
877 $ iseed, win( 1+iprepad ), maxsize,
882 CALL pzgsepsubtst( .true., ibtype, jobz, range, uplo, n, vl,
883 $ vu, il, iu, thresh, abstol, a, copya, b,
884 $ copyb, z, 1, 1, desca, win( 1+iprepad ),
885 $ wnew, ifail, iclustr, gap, iprepad,
886 $ ipostpad, work( indwork ), llwork, rwork,
887 $ lrwork, lheevxsize, iwork, isizeheevx,
888 $ res, tstnrm, qtqnrm, nout )
891 maxtstnrm =
max( tstnrm, maxtstnrm )
892 maxqtqnrm =
max( qtqnrm, maxqtqnrm )
893 passed =
'FAILED stest 9'
910 $ iseed, win( 1+iprepad ), maxsize,
915 CALL pzgsepsubtst( .true., ibtype, jobz, range, uplo, n, vl,
916 $ vu, il, iu, thresh, abstol, a, copya, b,
917 $ copyb, z, 1, 1, desca, win( 1+iprepad ),
918 $ wnew, ifail, iclustr, gap, iprepad,
919 $ ipostpad, work( indwork ), llwork, rwork,
920 $ lrwork, lheevxsize, iwork, isizeheevx,
921 $ res, tstnrm, qtqnrm, nout )
924 maxtstnrm =
max( tstnrm, maxtstnrm )
925 maxqtqnrm =
max( qtqnrm, maxqtqnrm )
926 passed =
'FAILED stest10'
944 $ iseed, win( 1+iprepad ), maxsize,
948 CALL pzgsepsubtst( .true., ibtype, jobz, range, uplo, n, vl,
949 $ vu, il, iu, thresh, abstol, a, copya, b,
950 $ copyb, z, 1, 1, desca, win( 1+iprepad ),
951 $ wnew, ifail, iclustr, gap, iprepad,
952 $ ipostpad, work( indwork ), llwork, rwork,
953 $ lrwork, lheevxsize, iwork, isizeheevx,
954 $ res, tstnrm, qtqnrm, nout )
957 maxtstnrm =
max( tstnrm, maxtstnrm )
958 maxqtqnrm =
max( qtqnrm, maxqtqnrm )
959 passed =
'FAILED stest11'
976 $ iseed, win( 1+iprepad ), maxsize,
981 CALL pzgsepsubtst( .true., ibtype, jobz, range, uplo, n, vl,
982 $ vu, il, iu, thresh, abstol, a, copya, b,
983 $ copyb, z, 1, 1, desca, win( 1+iprepad ),
984 $ wnew, ifail, iclustr, gap, iprepad,
985 $ ipostpad, work( indwork ), llwork, rwork,
986 $ lrwork, lheevxsize, iwork, isizeheevx,
987 $ res, tstnrm, qtqnrm, nout )
990 maxtstnrm =
max( tstnrm, maxtstnrm )
991 maxqtqnrm =
max( qtqnrm, maxqtqnrm )
992 passed =
'FAILED stest12'
1001 IF( info.EQ.0 )
THEN
1009 CALL pzlasizeheevx( .true., range, n, desca, vl, vu, il, iu,
1010 $ iseed, win( 1+iprepad ), maxsize,
1011 $ vecsize, valsize )
1014 CALL pzgsepsubtst( .true., ibtype, jobz, range, uplo, n, vl,
1015 $ vu, il, iu, thresh, abstol, a, copya, b,
1016 $ copyb, z, 1, 1, desca, win( 1+iprepad ),
1017 $ wnew, ifail, iclustr, gap, iprepad,
1018 $ ipostpad, work( indwork ), llwork, rwork,
1019 $ lrwork, lheevxsize, iwork, isizeheevx,
1020 $ res, tstnrm, qtqnrm, nout )
1023 maxtstnrm =
max( tstnrm, maxtstnrm )
1024 maxqtqnrm =
max( qtqnrm, maxqtqnrm )
1025 passed =
'FAILED stest13'
1033 CALL igamx2d( context,
'All',
' ', 1, 1, info, 1, -1, -1, -1, -1,
1036 IF( info.EQ.1 )
THEN
1038 WRITE( nout, fmt = 9994 )
'C '
1039 WRITE( nout, fmt = 9993 )iseedin( 1 )
1040 WRITE( nout, fmt = 9992 )iseedin( 2 )
1041 WRITE( nout, fmt = 9991 )iseedin( 3 )
1042 WRITE( nout, fmt = 9990 )iseedin( 4 )
1043 IF( lsame( uplo,
'L' ) )
THEN
1044 WRITE( nout, fmt = 9994 )
' UPLO= ''L'' '
1046 WRITE( nout, fmt = 9994 )
' UPLO= ''U'' '
1048 IF( lsame( subtests,
'Y' ) )
THEN
1049 WRITE( nout, fmt = 9994 )
' SUBTESTS= ''Y'' '
1051 WRITE( nout, fmt = 9994 )
' SUBTESTS= ''N'' '
1053 WRITE( nout, fmt = 9989 )n
1054 WRITE( nout, fmt = 9988 )nprow
1055 WRITE( nout, fmt = 9987 )npcol
1056 WRITE( nout, fmt = 9986 )nb
1057 WRITE( nout, fmt = 9985 )mattype
1058 WRITE( nout, fmt = 9984 )ibtype
1059 WRITE( nout, fmt = 9982 )abstol
1060 WRITE( nout, fmt = 9981 )thresh
1061 WRITE( nout, fmt = 9994 )
'C '
1065 CALL slcombine( context,
'All',
'>',
'W', 6, 1, wtime )
1066 CALL slcombine( context,
'All',
'>',
'C', 6, 1, ctime )
1068 IF( info.EQ.0 .OR. info.EQ.1 )
THEN
1069 IF( wtime( 1 ).GE.0.0 )
THEN
1070 WRITE( nout, fmt = 9999 )n, nb, nprow, npcol, mattype,
1071 $ ibtype, subtests, wtime( 1 ), ctime( 1 ), maxtstnrm,
1074 WRITE( nout, fmt = 9998 )n, nb, nprow, npcol, mattype,
1075 $ ibtype, subtests, ctime( 1 ), maxtstnrm, passed
1077 ELSE IF( info.EQ.2 )
THEN
1078 IF( wtime( 1 ).GE.0.0 )
THEN
1079 WRITE( nout, fmt = 9997 )n, nb, nprow, npcol, mattype,
1080 $ ibtype, subtests, wtime( 1 ), ctime( 1 )
1082 WRITE( nout, fmt = 9996 )n, nb, nprow, npcol, mattype,
1083 $ ibtype, subtests, ctime( 1 )
1085 ELSE IF( info.EQ.3 )
THEN
1086 WRITE( nout, fmt = 9995 )n, nb, nprow, npcol, mattype,
1094 9999
FORMAT( 1x, i5, 1x, i3, 1x, i3, 1x, i3, 1x, i3, 3x, i3, 4x, a1,
1095 $ 1x, f8.2, 1x, f8.2, 1x, g9.2, 1x, a14 )
1096 9998
FORMAT( 1x, i5, 1x, i3, 1x, i3, 1x, i3, 1x, i3, 3x, i3, 4x, a1,
1097 $ 1x, 8x, 1x, f8.2, 1x, g9.2, a14 )
1098 9997
FORMAT( 1x, i5, 1x, i3, 1x, i3, 1x, i3, 1x, i3, 3x, i3, 4x, a1,
1099 $ 1x, f8.2, 1x, f8.2, 11x,
'Bypassed' )
1100 9996
FORMAT( 1x, i5, 1x, i3, 1x, i3, 1x, i3, 1x, i3, 3x, i3, 4x, a1,
1101 $ 1x, 8x, 1x, f8.2, 11x,
'Bypassed' )
1102 9995
FORMAT( 1x, i5, 1x, i3, 1x, i3, 1x, i3, 1x, i3, 3x, i3, 4x, a1,
1103 $ 22x,
'Bad MEMORY parameters' )
1105 9993
FORMAT(
' ISEED( 1 ) =', i8 )
1106 9992
FORMAT(
' ISEED( 2 ) =', i8 )
1107 9991
FORMAT(
' ISEED( 3 ) =', i8 )
1108 9990
FORMAT(
' ISEED( 4 ) =', i8 )
1109 9989
FORMAT(
' N=', i8 )
1110 9988
FORMAT(
' NPROW=', i8 )
1111 9987
FORMAT(
' NPCOL=', i8 )
1112 9986
FORMAT(
' NB=', i8 )
1113 9985
FORMAT(
' MATTYPE=', i8 )
1114 9984
FORMAT(
' IBTYPE=', i8 )
1115 9983
FORMAT(
' SUBTESTS=', a1 )
1116 9982
FORMAT(
' ABSTOL=', d16.6 )
1117 9981
FORMAT(
' THRESH=', d16.6 )
1118 9980
FORMAT(
' Increase TOTMEM in PZGSEPDRIVER' )