3 SUBROUTINE pcseptst( DESCA, UPLO, N, MATTYPE, SUBTESTS, THRESH,
4 $ ORDER, ABSTOL, ISEED, A, COPYA, Z, LDA, WIN,
5 $ WNEW, IFAIL, ICLUSTR, GAP, IPREPAD, IPOSTPAD,
6 $ WORK, LWORK, RWORK, LRWORK, IWORK, LIWORK,
15 CHARACTER SUBTESTS, UPLO
16 INTEGER INFO, IPOSTPAD, IPREPAD, LDA, LIWORK, LRWORK,
17 $ LWORK, MATTYPE, N, NOUT, ORDER
21 INTEGER DESCA( * ), ICLUSTR( * ), IFAIL( * ),
22 $ iseed( 4 ), iwork( * )
23 REAL GAP( * ), RWORK( * ), WIN( * ), WNEW( * )
24 COMPLEX A( LDA, * ), COPYA( LDA, * ), WORK( * ),
205 INTEGER BLOCK_CYCLIC_2D, DLEN_, DTYPE_, CTXT_, M_, N_,
206 $ MB_, NB_, RSRC_, CSRC_, LLD_
207 PARAMETER ( BLOCK_CYCLIC_2D = 1, dlen_ = 9, dtype_ = 1,
208 $ ctxt_ = 2, m_ = 3, n_ = 4, mb_ = 5, nb_ = 6,
209 $ rsrc_ = 7, csrc_ = 8, lld_ = 9 )
210 REAL ZERO, ONE, TEN, HALF
211 parameter( zero = 0.0e+0, one = 1.0e+0, ten = 10.0e+0,
214 parameter( padval = ( 19.25e+0, 1.1e+1 ) )
216 PARAMETER ( CZERO = ( 0.0e+0, 0.0e+0 ) )
218 parameter( cone = ( 1.0e+0, 0.0e+0 ) )
220 parameter( maxtyp = 22 )
225 CHARACTER JOBZ, RANGE
227 INTEGER CONTEXT, I, IAM, IINFO, IL, IMODE, IN, INDD,
228 $ indrwork, indwork, isizeheevd, isizeheevx,
229 $ isizesubtst, isizetst, itype, iu, j,
230 $ lheevdsize, lheevxsize, llrwork, llwork,
231 $ maxsize, mycol, myrow, nb, ngen, nloc, nnodes,
232 $ np, np0, npcol, nprow, nq, nq0, res, rsizechk,
233 $ rsizeheevd, rsizeheevx, rsizeqtq, rsizesubtst,
234 $ rsizetst, sizeheevd, sizeheevx, sizemqrleft,
235 $ sizemqrright, sizeqrf, sizesubtst, sizetms,
236 $ 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,
clatms, igamx2d,
260 INTRINSIC abs, int,
max,
min, 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_*
276 passed =
'PASSED EEVX'
277 context = desca( ctxt_ )
280 CALL blacs_pinfo( iam, nnodes )
281 CALL blacs_gridinfo( context, nprow, npcol, myrow, mycol )
287 CALL pclasizesep( desca, iprepad, ipostpad, sizemqrleft,
288 $ sizemqrright, sizeqrf, sizetms, rsizeqtq,
289 $ rsizechk, sizeheevx, rsizeheevx, isizeheevx,
290 $ sizeheevd, rsizeheevd, isizeheevd, sizesubtst,
291 $ rsizesubtst, isizesubtst, sizetst, rsizetst,
294 IF( lrwork.LT.rsizetst )
THEN
298 CALL igamx2d( context,
'a',
' ', 1, 1, info, 1, 1, 1, -1, -1, 0 )
305 llwork = lwork - indwork + 1
306 llrwork = lrwork - indrwork + 1
308 ulp = pslamch( context,
'P' )
310 unfl = pslamch( context,
'Safe min' )
312 CALL slabad( unfl, ovfl )
313 rtunfl = sqrt( unfl )
314 rtovfl = sqrt( ovfl )
315 aninv = one / real(
max( 1, n ) )
319 IF( myrow.EQ.0 .AND. mycol.EQ.0 )
THEN
320 CALL igebs2d( context,
'a',
' ', 4, 1, iseed, 4 )
322 CALL igebr2d( context,
'a',
' ', 4, 1, iseed, 4, 0, 0 )
324 iseedin( 1 ) = iseed( 1 )
325 iseedin( 2 ) = iseed( 2 )
326 iseedin( 3 ) = iseed( 3 )
327 iseedin( 4 ) = iseed( 4 )
346 itype = ktype( mattype )
347 imode = kmode( mattype )
351 GO TO ( 10, 20, 30 )kmagn( mattype )
358 anorm = ( rtovfl*ulp )*aninv
362 anorm = rtunfl*n*ulpinv
366 IF( mattype.LE.15 )
THEN
369 cond = ulpinv*aninv / ten
377 IF( itype.EQ.1 )
THEN
382 rwork( indd+i-1 ) = zero
384 CALL pclaset(
'All', n, n, czero, czero, copya, 1, 1,
388 ELSE IF( itype.EQ.2 )
THEN
393 rwork( indd+i-1 ) = one
395 CALL pclaset(
'All', n, n, czero, cone, copya, 1, 1, desca )
398 ELSE IF( itype.EQ.4 )
THEN
402 CALL pcfillpad( desca( ctxt_ ), sizetms, 1, work( indwork ),
403 $ sizetms, iprepad, ipostpad, padval+1.0e+0 )
405 CALL pclatms( n, n,
'S', iseed,
'S', rwork( indd ), imode,
406 $ cond, anorm, 0, 0,
'N', copya, 1, 1, desca,
407 $ order, work( indwork+iprepad ), sizetms,
411 CALL pcchekpad( desca( ctxt_ ),
'PCLATMS1-WORK', sizetms, 1,
412 $ work( indwork ), sizetms, iprepad, ipostpad,
415 ELSE IF( itype.EQ.5 )
THEN
419 CALL pcfillpad( desca( ctxt_ ), sizetms, 1, work( indwork ),
420 $ sizetms, iprepad, ipostpad, padval+2.0e+0 )
422 CALL pclatms( n, n,
'S', iseed,
'S', rwork( indd ), imode,
423 $ cond, anorm, n, n,
'N', copya, 1, 1, desca,
424 $ order, work( indwork+iprepad ), sizetms,
427 CALL pcchekpad( desca( ctxt_ ),
'PCLATMS2-WORK', sizetms, 1,
428 $ work( indwork ), sizetms, iprepad, ipostpad,
433 ELSE IF( itype.EQ.8 )
THEN
437 np = numroc( n, desca( mb_ ), myrow, 0, nprow )
438 nq = numroc( n, desca( nb_ ), mycol, 0, npcol )
439 CALL pcmatgen( desca( ctxt_ ),
'H',
'N', n, n, desca( mb_ ),
440 $ desca( nb_ ), copya, desca( lld_ ),
441 $ desca( rsrc_ ), desca( csrc_ ), iseed( 1 ),
442 $ 0, np, 0, nq, myrow, mycol, nprow, npcol )
446 ELSE IF( itype.EQ.9 )
THEN
451 CALL pcfillpad( desca( ctxt_ ), sizetms, 1, work( indwork ),
452 $ sizetms, iprepad, ipostpad, padval+3.0e+0 )
454 CALL pclatms( n, n,
'S', iseed,
'S', rwork( indd ), imode,
455 $ cond, anorm, n, n,
'N', copya, 1, 1, desca,
456 $ order, work( indwork+iprepad ), sizetms,
461 CALL pcchekpad( desca( ctxt_ ),
'PCLATMS3-WORK', sizetms, 1,
462 $ work( indwork ), sizetms, iprepad, ipostpad,
465 ELSE IF( itype.EQ.10 )
THEN
470 CALL pclaset(
'All', n, n, czero, czero, copya, 1, 1,
472 np = numroc( n, desca( mb_ ), 0, 0, nprow )
473 nq = numroc( n, desca( nb_ ), 0, 0, npcol )
479 in =
min( 1+int( slaran( iseed )*real( nloc ) ), n-ngen )
481 CALL clatms( in, in,
'S', iseed,
'P', rwork( indd ),
482 $ imode, cond, anorm, 1, 1,
'N', a, lda,
483 $ work( indwork ), iinfo )
486 temp1 = abs( a( i-1, i ) ) /
487 $ sqrt( abs( a( i-1, i-1 )*a( i, i ) ) )
488 IF( temp1.GT.half )
THEN
489 a( i-1, i ) = half*sqrt( abs( a( i-1, i-1 )*a( i,
491 a( i, i-1 ) = a( i-1, i )
494 CALL pcelset( copya, ngen+1, ngen+1, desca, a( 1, 1 ) )
496 CALL pcelset( copya, ngen+i, ngen+i, desca,
498 CALL pcelset( copya, ngen+i-1, ngen+i, desca,
500 CALL pcelset( copya, ngen+i, ngen+i-1, desca,
508 ELSE IF( itype.EQ.11 )
THEN
517 in =
min( j, n-ngen )
519 rwork( indd+ngen+i ) = temp1
528 CALL pcfillpad( desca( ctxt_ ), sizetms, 1, work( indwork ),
529 $ sizetms, iprepad, ipostpad, padval+4.0e+0 )
531 CALL pclatms( n, n,
'S', iseed,
'S', rwork( indd ), imode,
532 $ cond, anorm, 0, 0,
'N', copya, 1, 1, desca,
533 $ order, work( indwork+iprepad ), sizetms,
536 CALL pcchekpad( desca( ctxt_ ),
'PCLATMS4-WORK', sizetms, 1,
537 $ work( indwork ), sizetms, iprepad, ipostpad,
549 $
CALL slasrt(
'I', n, rwork( indd ), iinfo )
560 $ iseed, rwork( indd ), maxsize, vecsize,
563 lheevxsize =
min( maxsize, llrwork )
565 CALL pcsepsubtst( wknown,
'v',
'a', uplo, n, vl, vu, il, iu,
566 $ thresh, abstol, a, copya, z, 1, 1, desca,
567 $ rwork( indd ), win, ifail, iclustr, gap,
568 $ iprepad, ipostpad, work( indwork ), llwork,
569 $ rwork( indrwork ), llrwork, lheevxsize,
570 $ iwork, isizeheevx, res, tstnrm, qtqnrm,
578 IF( thresh.LE.zero )
THEN
581 ELSE IF( res.NE.0 )
THEN
587 IF( thresh.GT.zero .AND. lsame( subtests,
'Y' ) )
THEN
596 $ iseed, win( 1+iprepad ), maxsize,
601 CALL pcsepsubtst( .true., jobz, range, uplo, n, vl, vu, il,
602 $ iu, thresh, abstol, a, copya, z, 1, 1,
603 $ desca, win( 1+iprepad ), wnew, ifail,
604 $ iclustr, gap, iprepad, ipostpad,
605 $ work( indwork ), llwork, rwork, lrwork,
606 $ lheevxsize, iwork, isizeheevx, res,
607 $ tstnrm, qtqnrm, nout )
610 passed =
'FAILED stest 1'
611 maxtstnrm =
max( tstnrm, maxtstnrm )
612 maxqtqnrm =
max( qtqnrm, maxqtqnrm )
623 $ iseed, win( 1+iprepad ), maxsize,
626 lheevxsize = vecsize + int( slaran( iseed )*
627 $ real( maxsize-vecsize ) )
629 CALL pcsepsubtst( .true., jobz, range, uplo, n, vl, vu, il,
630 $ iu, thresh, abstol, a, copya, z, 1, 1,
631 $ desca, win( 1+iprepad ), wnew, ifail,
632 $ iclustr, gap, iprepad, ipostpad,
633 $ work( indwork ), llwork, rwork, lrwork,
634 $ lheevxsize, iwork, isizeheevx, res,
635 $ tstnrm, qtqnrm, nout )
638 passed =
'FAILED stest 2'
639 maxtstnrm =
max( tstnrm, maxtstnrm )
640 maxqtqnrm =
max( qtqnrm, maxqtqnrm )
652 $ iseed, win( 1+iprepad ), maxsize,
656 CALL pcsepsubtst( .true., jobz, range, uplo, n, vl, vu, il,
657 $ iu, thresh, abstol, a, copya, z, 1, 1,
658 $ desca, win( 1+iprepad ), wnew, ifail,
659 $ iclustr, gap, iprepad, ipostpad,
660 $ work( indwork ), llwork, rwork, lrwork,
661 $ lheevxsize, iwork, isizeheevx, res,
662 $ tstnrm, qtqnrm, nout )
665 maxtstnrm =
max( tstnrm, maxtstnrm )
666 maxqtqnrm =
max( qtqnrm, maxqtqnrm )
667 passed =
'FAILED stest 3'
684 $ iseed, win( 1+iprepad ), maxsize,
689 CALL pcsepsubtst( .true., jobz, range, uplo, n, vl, vu, il,
690 $ iu, thresh, abstol, a, copya, z, 1, 1,
691 $ desca, win( 1+iprepad ), wnew, ifail,
692 $ iclustr, gap, iprepad, ipostpad,
693 $ work( indwork ), llwork, rwork, lrwork,
694 $ lheevxsize, iwork, isizeheevx, res,
695 $ tstnrm, qtqnrm, nout )
698 maxtstnrm =
max( tstnrm, maxtstnrm )
699 maxqtqnrm =
max( qtqnrm, maxqtqnrm )
700 passed =
'FAILED stest 4'
717 $ iseed, win( 1+iprepad ), maxsize,
722 CALL pcsepsubtst( .true., jobz, range, uplo, n, vl, vu, il,
723 $ iu, thresh, abstol, a, copya, z, 1, 1,
724 $ desca, win( 1+iprepad ), wnew, ifail,
725 $ iclustr, gap, iprepad, ipostpad,
726 $ work( indwork ), llwork, rwork, lrwork,
727 $ lheevxsize, iwork, isizeheevx, res,
728 $ tstnrm, qtqnrm, nout )
731 maxtstnrm =
max( tstnrm, maxtstnrm )
732 maxqtqnrm =
max( qtqnrm, maxqtqnrm )
733 passed =
'FAILED stest 5'
749 $ iseed, win( 1+iprepad ), maxsize,
754 CALL pcsepsubtst( .true., jobz, range, uplo, n, vl, vu, il,
755 $ iu, thresh, abstol, a, copya, z, 1, 1,
756 $ desca, win( 1+iprepad ), wnew, ifail,
757 $ iclustr, gap, iprepad, ipostpad,
758 $ work( indwork ), llwork, rwork, lrwork,
759 $ lheevxsize, iwork, isizeheevx, res,
760 $ tstnrm, qtqnrm, nout )
763 maxtstnrm =
max( tstnrm, maxtstnrm )
764 maxqtqnrm =
max( qtqnrm, maxqtqnrm )
765 passed =
'FAILED stest 6'
781 $ iseed, win( 1+iprepad ), maxsize,
783 lheevxsize = vecsize + int( slaran( iseed )*
784 $ real( maxsize-vecsize ) )
786 CALL pcsepsubtst( .true., jobz, range, uplo, n, vl, vu, il,
787 $ iu, thresh, abstol, a, copya, z, 1, 1,
788 $ desca, win( 1+iprepad ), wnew, ifail,
789 $ iclustr, gap, iprepad, ipostpad,
790 $ work( indwork ), llwork, rwork, lrwork,
791 $ lheevxsize, iwork, isizeheevx, res,
792 $ tstnrm, qtqnrm, nout )
795 maxtstnrm =
max( tstnrm, maxtstnrm )
796 maxqtqnrm =
max( qtqnrm, maxqtqnrm )
797 passed =
'FAILED stest 7'
813 $ iseed, win( 1+iprepad ), maxsize,
818 CALL pcsepsubtst( .true., jobz, range, uplo, n, vl, vu, il,
819 $ iu, thresh, abstol, a, copya, z, 1, 1,
820 $ desca, win( 1+iprepad ), wnew, ifail,
821 $ iclustr, gap, iprepad, ipostpad,
822 $ work( indwork ), llwork, rwork, lrwork,
823 $ lheevxsize, iwork, isizeheevx, res,
824 $ tstnrm, qtqnrm, nout )
827 maxtstnrm =
max( tstnrm, maxtstnrm )
828 maxqtqnrm =
max( qtqnrm, maxqtqnrm )
829 passed =
'FAILED stest 8'
845 $ iseed, win( 1+iprepad ), maxsize,
850 CALL pcsepsubtst( .true., jobz, range, uplo, n, vl, vu, il,
851 $ iu, thresh, abstol, a, copya, z, 1, 1,
852 $ desca, win( 1+iprepad ), wnew, ifail,
853 $ iclustr, gap, iprepad, ipostpad,
854 $ work( indwork ), llwork, rwork, lrwork,
855 $ lheevxsize, iwork, isizeheevx, res,
856 $ tstnrm, qtqnrm, nout )
859 maxtstnrm =
max( tstnrm, maxtstnrm )
860 maxqtqnrm =
max( qtqnrm, maxqtqnrm )
861 passed =
'FAILED stest 9'
878 $ iseed, win( 1+iprepad ), maxsize,
883 CALL pcsepsubtst( .true., jobz, range, uplo, n, vl, vu, il,
884 $ iu, thresh, abstol, a, copya, z, 1, 1,
885 $ desca, win( 1+iprepad ), wnew, ifail,
886 $ iclustr, gap, iprepad, ipostpad,
887 $ work( indwork ), llwork, rwork, lrwork,
888 $ lheevxsize, iwork, isizeheevx, res,
889 $ tstnrm, qtqnrm, nout )
892 maxtstnrm =
max( tstnrm, maxtstnrm )
893 maxqtqnrm =
max( qtqnrm, maxqtqnrm )
894 passed =
'FAILED stest10'
912 $ iseed, win( 1+iprepad ), maxsize,
916 CALL pcsepsubtst( .true., jobz, range, uplo, n, vl, vu, il,
917 $ iu, thresh, abstol, a, copya, z, 1, 1,
918 $ desca, win( 1+iprepad ), wnew, ifail,
919 $ iclustr, gap, iprepad, ipostpad,
920 $ work( indwork ), llwork, rwork, lrwork,
921 $ lheevxsize, iwork, isizeheevx, res,
922 $ tstnrm, qtqnrm, nout )
925 maxtstnrm =
max( tstnrm, maxtstnrm )
926 maxqtqnrm =
max( qtqnrm, maxqtqnrm )
927 passed =
'FAILED stest11'
944 $ iseed, win( 1+iprepad ), maxsize,
949 CALL pcsepsubtst( .true., jobz, range, uplo, n, vl, vu, il,
950 $ iu, thresh, abstol, a, copya, z, 1, 1,
951 $ desca, win( 1+iprepad ), wnew, ifail,
952 $ iclustr, gap, iprepad, ipostpad,
953 $ work( indwork ), llwork, rwork, lrwork,
954 $ lheevxsize, iwork, isizeheevx, res,
955 $ tstnrm, qtqnrm, nout )
958 maxtstnrm =
max( tstnrm, maxtstnrm )
959 maxqtqnrm =
max( qtqnrm, maxqtqnrm )
960 passed =
'FAILED stest12'
978 $ iseed, win( 1+iprepad ), maxsize,
982 CALL pcsepsubtst( .true., jobz, range, uplo, n, vl, vu, il,
983 $ iu, thresh, abstol, a, copya, z, 1, 1,
984 $ desca, win( 1+iprepad ), wnew, ifail,
985 $ iclustr, gap, iprepad, ipostpad,
986 $ work( indwork ), llwork, rwork, lrwork,
987 $ lheevxsize, iwork, isizeheevx, res,
988 $ tstnrm, qtqnrm, nout )
991 maxtstnrm =
max( tstnrm, maxtstnrm )
992 maxqtqnrm =
max( qtqnrm, maxqtqnrm )
993 passed =
'FAILED stest13'
1001 CALL igamx2d( context,
'All',
' ', 1, 1, info, 1, -1, -1, -1, -1,
1004 IF( info.EQ.1 )
THEN
1006 WRITE( nout, fmt = 9994 )
'C '
1007 WRITE( nout, fmt = 9993 )iseedin( 1 )
1008 WRITE( nout, fmt = 9992 )iseedin( 2 )
1009 WRITE( nout, fmt = 9991 )iseedin( 3 )
1010 WRITE( nout, fmt = 9990 )iseedin( 4 )
1011 IF( lsame( uplo,
'L' ) )
THEN
1012 WRITE( nout, fmt = 9994 )
' UPLO= ''L'' '
1014 WRITE( nout, fmt = 9994 )
' UPLO= ''U'' '
1016 IF( lsame( subtests,
'Y' ) )
THEN
1017 WRITE( nout, fmt = 9994 )
' SUBTESTS= ''Y'' '
1019 WRITE( nout, fmt = 9994 )
' SUBTESTS= ''N'' '
1021 WRITE( nout, fmt = 9989 )n
1022 WRITE( nout, fmt = 9988 )nprow
1023 WRITE( nout, fmt = 9987 )npcol
1024 WRITE( nout, fmt = 9986 )nb
1025 WRITE( nout, fmt = 9985 )mattype
1026 WRITE( nout, fmt = 9982 )abstol
1027 WRITE( nout, fmt = 9981 )thresh
1028 WRITE( nout, fmt = 9994 )
'C '
1032 CALL slcombine( context,
'All',
'>',
'W', 6, 1, wtime )
1033 CALL slcombine( context,
'All',
'>',
'C', 6, 1, ctime )
1035 IF( info.EQ.0 .OR. info.EQ.1 )
THEN
1036 IF( wtime( 1 ).GE.0.0 )
THEN
1037 WRITE( nout, fmt = 9999 )n, nb, nprow, npcol, mattype,
1038 $ subtests, wtime( 1 ), ctime( 1 ), maxtstnrm,
1041 WRITE( nout, fmt = 9998 )n, nb, nprow, npcol, mattype,
1042 $ subtests, ctime( 1 ), maxtstnrm, maxqtqnrm, passed
1044 ELSE IF( info.EQ.2 )
THEN
1045 IF( wtime( 1 ).GE.0.0 )
THEN
1046 WRITE( nout, fmt = 9997 )n, nb, nprow, npcol, mattype,
1047 $ subtests, wtime( 1 ), ctime( 1 )
1049 WRITE( nout, fmt = 9996 )n, nb, nprow, npcol, mattype,
1050 $ subtests, ctime( 1 )
1052 ELSE IF( info.EQ.3 )
THEN
1053 WRITE( nout, fmt = 9995 )n, nb, nprow, npcol, mattype,
1060 passed =
'PASSED EEVD'
1064 IF( info.EQ.0 )
THEN
1066 np0 = numroc( n, nb, 0, 0, nprow )
1067 nq0 = numroc(
max( n, 1 ), nb, 0, 0, npcol )
1068 lheevdsize = 1 + 9*n + 3*np0*nq0
1069 isizeheevd =
max( 1, 2+7*n+8*npcol )
1071 CALL pcsdpsubtst( wknown, uplo, n, thresh, abstol, a, copya, z,
1072 $ 1, 1, desca, win, wnew, iprepad, ipostpad,
1073 $ work( indwork ), llwork, rwork, lrwork,
1074 $ lheevdsize, iwork, isizeheevd, res, tstnrm,
1081 passed =
'FAILED EEVD'
1088 CALL igamx2d( context,
'All',
' ', 1, 1, info, 1, -1, -1, -1, -1,
1091 IF( info.EQ.1 )
THEN
1093 WRITE( nout, fmt = 9994 )
'C '
1094 WRITE( nout, fmt = 9993 )iseedin( 1 )
1095 WRITE( nout, fmt = 9992 )iseedin( 2 )
1096 WRITE( nout, fmt = 9991 )iseedin( 3 )
1097 WRITE( nout, fmt = 9990 )iseedin( 4 )
1098 IF( lsame( uplo,
'L' ) )
THEN
1099 WRITE( nout, fmt = 9994 )
' UPLO= ''L'' '
1101 WRITE( nout, fmt = 9994 )
' UPLO= ''U'' '
1103 IF( lsame( subtests,
'Y' ) )
THEN
1104 WRITE( nout, fmt = 9994 )
' SUBTESTS= ''Y'' '
1106 WRITE( nout, fmt = 9994 )
' SUBTESTS= ''N'' '
1108 WRITE( nout, fmt = 9989 )n
1109 WRITE( nout, fmt = 9988 )nprow
1110 WRITE( nout, fmt = 9987 )npcol
1111 WRITE( nout, fmt = 9986 )nb
1112 WRITE( nout, fmt = 9985 )mattype
1113 WRITE( nout, fmt = 9982 )abstol
1114 WRITE( nout, fmt = 9981 )thresh
1115 WRITE( nout, fmt = 9994 )
'C '
1119 CALL slcombine( context,
'All',
'>',
'W', 6, 1, wtime )
1120 CALL slcombine( context,
'All',
'>',
'C', 6, 1, ctime )
1122 IF( info.EQ.0 .OR. info.EQ.1 )
THEN
1123 IF( wtime( 1 ).GE.0.0 )
THEN
1124 WRITE( nout, fmt = 9999 )n, nb, nprow, npcol, mattype,
1125 $ subtests, wtime( 1 ), ctime( 1 ), maxtstnrm,
1128 WRITE( nout, fmt = 9998 )n, nb, nprow, npcol, mattype,
1129 $ subtests, ctime( 1 ), maxtstnrm, maxqtqnrm, passed
1131 ELSE IF( info.EQ.2 )
THEN
1132 IF( wtime( 1 ).GE.0.0 )
THEN
1133 WRITE( nout, fmt = 9997 )n, nb, nprow, npcol, mattype,
1134 $ subtests, wtime( 1 ), ctime( 1 )
1136 WRITE( nout, fmt = 9996 )n, nb, nprow, npcol, mattype,
1137 $ subtests, ctime( 1 )
1139 ELSE IF( info.EQ.3 )
THEN
1140 WRITE( nout, fmt = 9995 )n, nb, nprow, npcol, mattype,
1147 9999
FORMAT( 1x, i5, 1x, i3, 1x, i3, 1x, i3, 1x, i3, 3x, a1, 1x, f8.2,
1148 $ 1x, f8.2, 1x, g9.2, 1x, g9.2, 1x, a14 )
1149 9998
FORMAT( 1x, i5, 1x, i3, 1x, i3, 1x, i3, 1x, i3, 3x, a1, 1x, 8x,
1150 $ 1x, f8.2, 1x, g9.2, 1x, g9.2, a14 )
1151 9997
FORMAT( 1x, i5, 1x, i3, 1x, i3, 1x, i3, 1x, i3, 3x, a1, 1x, f8.2,
1152 $ 1x, f8.2, 21x,
'Bypassed' )
1153 9996
FORMAT( 1x, i5, 1x, i3, 1x, i3, 1x, i3, 1x, i3, 3x, a1, 1x, 8x,
1154 $ 1x, f8.2, 21x,
'Bypassed' )
1155 9995
FORMAT( 1x, i5, 1x, i3, 1x, i3, 1x, i3, 1x, i3, 3x, a1, 32x,
1156 $
'Bad MEMORY parameters' )
1158 9993
FORMAT(
' ISEED( 1 ) =', i8 )
1159 9992
FORMAT(
' ISEED( 2 ) =', i8 )
1160 9991
FORMAT(
' ISEED( 3 ) =', i8 )
1161 9990
FORMAT(
' ISEED( 4 ) =', i8 )
1162 9989
FORMAT(
' N=', i8 )
1163 9988
FORMAT(
' NPROW=', i8 )
1164 9987
FORMAT(
' NPCOL=', i8 )
1165 9986
FORMAT(
' NB=', i8 )
1166 9985
FORMAT(
' MATTYPE=', i8 )
1167 9984
FORMAT(
' IBTYPE=', i8 )
1168 9983
FORMAT(
' SUBTESTS=', a1 )
1169 9982
FORMAT(
' ABSTOL=', d16.6 )
1170 9981
FORMAT(
' THRESH=', d16.6 )
1171 9980
FORMAT(
' Increase TOTMEM in PCSEPDRIVER' )