1 SUBROUTINE psseprtst(DESCA, UPLO, N, MATTYPE, SUBTESTS, THRESH,
2 $ ORDER, ABSTOL, ISEED, A, COPYA, Z, LDA, WIN,
3 $ WNEW, IFAIL, ICLUSTR, GAP, IPREPAD, IPOSTPAD,
5 $ IWORK, LIWORK, HETERO, NOUT, INFO )
15 CHARACTER HETERO, SUBTESTS, UPLO
16 INTEGER INFO, IPOSTPAD, IPREPAD, LDA, LIWORK, LWORK,
17 $ MATTYPE, N, NOUT, ORDER
21 INTEGER DESCA( * ), ICLUSTR( * ), IFAIL( * ),
22 $ iseed( 4 ), iwork( * )
23 REAL A( LDA, * ), COPYA( LDA, * ), GAP( * ),
24 $ WIN( * ), WNEW( * ), WORK( * ), Z( LDA, * )
190 INTEGER CTXT_, MB_, NB_, RSRC_, CSRC_, LLD_
191 PARAMETER ( CTXT_ = 2, mb_ = 5, nb_ = 6,
192 $ rsrc_ = 7, csrc_ = 8, lld_ = 9 )
193 REAL HALF, ONE, TEN, ZERO
194 parameter( zero = 0.0e0, one = 1.0e0,
195 $ ten = 10.0e0, half = 0.5e0 )
197 parameter( padval = 19.25e0 )
199 PARAMETER ( MAXTYP = 22 )
204 CHARACTER JOBZ, RANGE
206 INTEGER CONTEXT, I, IAM, IHETERO, IINFO, IL, IMODE, IN,
207 $ indd, indwork, isizesubtst, isizeevr,
208 $ isizetst, itype, iu, j, llwork, levrsize,
209 $ maxsize, mycol, myrow, nb, ngen, nloc,
210 $ nnodes, np, npcol, nprow, nq, res, sizechk,
211 $ sizemqrleft, sizemqrright, sizeqrf, sizeqtq,
212 $ sizesubtst, sizeevr, sizetms,
213 $ sizetst, valsize, vecsize
214 REAL ANINV, ANORM, COND, MAXQTQNRM, MAXTSTNRM, OVFL,
219 INTEGER ISEEDIN( 4 ), KMAGN( MAXTYP ), KMODE( MAXTYP ),
221 DOUBLE PRECISION CTIME( 10 ), WTIME( 10 )
227 EXTERNAL SLARAN, LSAME, NUMROC, PSLAMCH
230 EXTERNAL blacs_gridinfo, blacs_pinfo, igamx2d, igebr2d,
237 INTRINSIC abs, real, int,
max,
min, sqrt
240 DATA ktype / 1, 2, 4, 4, 4, 4, 4, 5, 5, 5, 5, 5, 8,
241 $ 8, 8, 9, 9, 9, 9, 9, 10, 11 /
242 DATA kmagn / 1, 1, 1, 1, 1, 2, 3, 1, 1, 1, 2, 3, 1,
243 $ 2, 3, 1, 1, 1, 2, 3, 1, 1 /
244 DATA kmode / 0, 0, 4, 3, 1, 4, 4, 4, 3, 1, 4, 4, 0,
245 $ 0, 0, 4, 3, 1, 4, 4, 3, 0 /
250 passed =
'PASSED EVR'
251 context = desca( ctxt_ )
254 CALL blacs_pinfo( iam, nnodes )
255 CALL blacs_gridinfo( context, nprow, npcol, myrow, mycol )
260 IF( lsame( hetero,
'Y' ) )
THEN
265 CALL igebs2d( context,
'All',
' ', 1, 1, ihetero, 1 )
267 CALL igebr2d( context,
'All',
' ', 1, 1, ihetero, 1, 0, 0 )
269 IF( ihetero.EQ.2 )
THEN
277 CALL pslasizesepr( desca, iprepad, ipostpad, sizemqrleft,
278 $ sizemqrright, sizeqrf, sizetms, sizeqtq,
279 $ sizechk, sizeevr, isizeevr,
281 $ isizesubtst, sizetst, isizetst )
282 IF( lwork.LT.sizetst )
THEN
286 CALL igamx2d( context,
'a',
' ', 1, 1, info, 1, 1, 1, -1, -1, 0 )
292 llwork = lwork - indwork + 1
294 ulp = pslamch( context,
'P' )
296 unfl = pslamch( context,
'Safe min' )
298 CALL slabad( unfl, ovfl )
299 rtunfl = sqrt( unfl )
300 rtovfl = sqrt( ovfl )
301 aninv = one / real(
max( 1, n ) )
305 IF( myrow.EQ.0 .AND. mycol.EQ.0 )
THEN
306 CALL igebs2d( context,
'a',
' ', 4, 1, iseed, 4 )
308 CALL igebr2d( context,
'a',
' ', 4, 1, iseed, 4, 0, 0 )
310 iseedin( 1 ) = iseed( 1 )
311 iseedin( 2 ) = iseed( 2 )
312 iseedin( 3 ) = iseed( 3 )
313 iseedin( 4 ) = iseed( 4 )
332 itype = ktype( mattype )
333 imode = kmode( mattype )
337 GO TO ( 10, 20, 30 )kmagn( mattype )
344 anorm = ( rtovfl*ulp )*aninv
348 anorm = rtunfl*n*ulpinv
352 IF( mattype.LE.15 )
THEN
355 cond = ulpinv*aninv / ten
360 IF( itype.EQ.1 )
THEN
365 work( indd+i-1 ) = zero
367 CALL pslaset(
'All', n, n, zero, zero, copya, 1, 1, desca )
370 ELSE IF( itype.EQ.2 )
THEN
375 work( indd+i-1 ) = one
377 CALL pslaset(
'All', n, n, zero, one, copya, 1, 1, desca )
380 ELSE IF( itype.EQ.4 )
THEN
384 CALL psfillpad( desca( ctxt_ ), sizetms, 1, work( indwork ),
385 $ sizetms, iprepad, ipostpad, padval+1.0e0 )
387 CALL pslatms( n, n,
'S', iseed,
'S', work( indd ), imode,
388 $ cond, anorm, 0, 0,
'N', copya, 1, 1, desca,
389 $ order, work( indwork+iprepad ), sizetms,
393 CALL pschekpad( desca( ctxt_ ),
'PSLATMS1-WORK', sizetms, 1,
394 $ work( indwork ), sizetms, iprepad, ipostpad,
397 ELSE IF( itype.EQ.5 )
THEN
401 CALL psfillpad( desca( ctxt_ ), sizetms, 1, work( indwork ),
402 $ sizetms, iprepad, ipostpad, padval+2.0e0 )
404 CALL pslatms( n, n,
'S', iseed,
'S', work( indd ), imode,
405 $ cond, anorm, n, n,
'N', copya, 1, 1, desca,
406 $ order, work( indwork+iprepad ), sizetms,
409 CALL pschekpad( desca( ctxt_ ),
'PSLATMS2-WORK', sizetms, 1,
410 $ work( indwork ), sizetms, iprepad, ipostpad,
415 ELSE IF( itype.EQ.8 )
THEN
419 np = numroc( n, desca( mb_ ), myrow, 0, nprow )
420 nq = numroc( n, desca( nb_ ), mycol, 0, npcol )
421 CALL psmatgen( desca( ctxt_ ),
'S',
'N', n, n, desca( mb_ ),
422 $ desca( nb_ ), copya, desca( lld_ ),
423 $ desca( rsrc_ ), desca( csrc_ ), iseed( 1 ),
424 $ 0, np, 0, nq, myrow, mycol, nprow, npcol )
428 ELSE IF( itype.EQ.9 )
THEN
432 CALL psfillpad( desca( ctxt_ ), sizetms, 1, work( indwork ),
433 $ sizetms, iprepad, ipostpad, padval+3.0e0 )
435 CALL pslatms( n, n,
'S', iseed,
'S', work( indd ), imode,
436 $ cond, anorm, n, n,
'N', copya, 1, 1, desca,
437 $ order, work( indwork+iprepad ), sizetms,
442 CALL pschekpad( desca( ctxt_ ),
'PSLATMS3-WORK', sizetms, 1,
443 $ work( indwork ), sizetms, iprepad, ipostpad,
446 ELSE IF( itype.EQ.10 )
THEN
451 CALL pslaset(
'All', n, n, zero, zero, copya, 1, 1, desca )
452 np = numroc( n, desca( mb_ ), 0, 0, nprow )
453 nq = numroc( n, desca( nb_ ), 0, 0, npcol )
459 in =
min( 1+int( slaran( iseed )*real( nloc ) ), n-ngen )
461 CALL slatms( in, in,
'S', iseed,
'P', work( indd ),
462 $ imode, cond, anorm, 1, 1,
'N', a, lda,
463 $ work( indwork ), iinfo )
466 temp1 = abs( a( i-1, i ) ) /
467 $ sqrt( abs( a( i-1, i-1 )*a( i, i ) ) )
468 IF( temp1.GT.half )
THEN
469 a( i-1, i ) = half*sqrt( abs( a( i-1, i-1 )*a( i,
471 a( i, i-1 ) = a( i-1, i )
474 CALL pselset( copya, ngen+1, ngen+1, desca, a( 1, 1 ) )
476 CALL pselset( copya, ngen+i, ngen+i, desca,
478 CALL pselset( copya, ngen+i-1, ngen+i, desca,
480 CALL pselset( copya, ngen+i, ngen+i-1, desca,
488 ELSE IF( itype.EQ.11 )
THEN
497 in =
min( j, n-ngen )
499 work( indd+ngen+i ) = temp1
507 CALL psfillpad( desca( ctxt_ ), sizetms, 1, work( indwork ),
508 $ sizetms, iprepad, ipostpad, padval+4.0e0 )
510 CALL pslatms( n, n,
'S', iseed,
'S', work( indd ), imode,
511 $ cond, anorm, 0, 0,
'N', copya, 1, 1, desca,
512 $ order, work( indwork+iprepad ), sizetms,
515 CALL pschekpad( desca( ctxt_ ),
'PSLATMS4-WORK', sizetms, 1,
516 $ work( indwork ), sizetms, iprepad, ipostpad,
524 $
CALL slasrt(
'I', n, work( indd ), iinfo )
527 $ iseed, work( indd ), maxsize, vecsize,
529 levrsize =
min( maxsize, llwork )
531 CALL psseprsubtst( wknown,
'v',
'a', uplo, n, vl, vu, il, iu,
532 $ thresh, abstol, a, copya, z, 1, 1, desca,
533 $ work( indd ), win, ifail, iclustr, gap,
534 $ iprepad, ipostpad, work( indwork ), llwork,
535 $ levrsize, iwork, isizeevr, res, tstnrm,
541 IF( thresh.LE.zero )
THEN
544 ELSE IF( res.NE.0 )
THEN
550 IF( thresh.GT.zero .AND. lsame( subtests,
'Y' ) )
THEN
559 $ iseed, win( 1+iprepad ), maxsize,
564 CALL psseprsubtst( .true., jobz, range, uplo, n, vl, vu, il,
565 $ iu, thresh, abstol, a, copya, z, 1, 1,
566 $ desca, win( 1+iprepad ), wnew, ifail,
567 $ iclustr, gap, iprepad, ipostpad,
568 $ work( indwork ), llwork, levrsize,
569 $ iwork, isizeevr, res, tstnrm, qtqnrm,
573 maxtstnrm =
max( tstnrm, maxtstnrm )
574 maxqtqnrm =
max( qtqnrm, maxqtqnrm )
575 passed =
'FAILED stest 1'
592 $ iseed, win( 1+iprepad ), maxsize,
597 CALL psseprsubtst( .true., jobz, range, uplo, n, vl, vu, il,
598 $ iu, thresh, abstol, a, copya, z, 1, 1,
599 $ desca, win( 1+iprepad ), wnew, ifail,
600 $ iclustr, gap, iprepad, ipostpad,
601 $ work( indwork ), llwork, levrsize,
602 $ iwork, isizeevr, res, tstnrm, qtqnrm,
606 maxtstnrm =
max( tstnrm, maxtstnrm )
607 maxqtqnrm =
max( qtqnrm, maxqtqnrm )
608 passed =
'FAILED stest 2'
624 $ iseed, win( 1+iprepad ), maxsize,
629 CALL psseprsubtst( .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, levrsize,
634 $ iwork, isizeevr, res, tstnrm, qtqnrm,
638 maxtstnrm =
max( tstnrm, maxtstnrm )
639 maxqtqnrm =
max( qtqnrm, maxqtqnrm )
640 passed =
'FAILED stest 3'
656 $ iseed, win( 1+iprepad ), maxsize,
661 CALL psseprsubtst( .true., jobz, range, uplo, n, vl, vu, il,
662 $ iu, thresh, abstol, a, copya, z, 1, 1,
663 $ desca, win( 1+iprepad ), wnew, ifail,
664 $ iclustr, gap, iprepad, ipostpad,
665 $ work( indwork ), llwork, levrsize,
666 $ iwork, isizeevr, res, tstnrm, qtqnrm,
670 maxtstnrm =
max( tstnrm, maxtstnrm )
671 maxqtqnrm =
max( qtqnrm, maxqtqnrm )
672 passed =
'FAILED stest 4'
688 $ iseed, win( 1+iprepad ), maxsize,
693 CALL psseprsubtst( .true., jobz, range, uplo, n, vl, vu, il,
694 $ iu, thresh, abstol, a, copya, z, 1, 1,
695 $ desca, win( 1+iprepad ), wnew, ifail,
696 $ iclustr, gap, iprepad, ipostpad,
697 $ work( indwork ), llwork, levrsize,
698 $ iwork, isizeevr, res, tstnrm, qtqnrm,
702 maxtstnrm =
max( tstnrm, maxtstnrm )
703 maxqtqnrm =
max( qtqnrm, maxqtqnrm )
704 passed =
'FAILED stest 5'
710 CALL igamx2d( context,
'All',
' ', 1, 1, info, 1, -1, -1, -1, -1,
713 IF( iam.EQ.0 .AND. .false. )
THEN
714 WRITE( nout, fmt = 9994 )
'C '
715 WRITE( nout, fmt = 9993 )iseedin( 1 )
716 WRITE( nout, fmt = 9992 )iseedin( 2 )
717 WRITE( nout, fmt = 9991 )iseedin( 3 )
718 WRITE( nout, fmt = 9990 )iseedin( 4 )
719 IF( lsame( uplo,
'L' ) )
THEN
720 WRITE( nout, fmt = 9994 )
' UPLO= ''L'' '
722 WRITE( nout, fmt = 9994 )
' UPLO= ''U'' '
724 IF( lsame( subtests,
'Y' ) )
THEN
725 WRITE( nout, fmt = 9994 )
' SUBTESTS= ''Y'' '
727 WRITE( nout, fmt = 9994 )
' SUBTESTS= ''N'' '
729 WRITE( nout, fmt = 9989 )n
730 WRITE( nout, fmt = 9988 )nprow
731 WRITE( nout, fmt = 9987 )npcol
732 WRITE( nout, fmt = 9986 )nb
733 WRITE( nout, fmt = 9985 )mattype
734 WRITE( nout, fmt = 9982 )abstol
735 WRITE( nout, fmt = 9981 )thresh
736 WRITE( nout, fmt = 9994 )
'C '
740 CALL slcombine( context,
'All',
'>',
'W', 6, 1, wtime )
741 CALL slcombine( context,
'All',
'>',
'C', 6, 1, ctime )
743 IF( info.EQ.0 .OR. info.EQ.1 )
THEN
744 IF( wtime( 1 ).GE.0.0 )
THEN
745 WRITE( nout, fmt = 9999 )n, nb, nprow, npcol, mattype,
746 $ subtests, wtime( 1 ), ctime( 1 ), maxtstnrm,
749 WRITE( nout, fmt = 9998 )n, nb, nprow, npcol, mattype,
750 $ subtests, ctime( 1 ), maxtstnrm, maxqtqnrm, passed
752 ELSE IF( info.EQ.2 )
THEN
753 IF( wtime( 1 ).GE.0.0 )
THEN
754 WRITE( nout, fmt = 9997 )n, nb, nprow, npcol, mattype,
755 $ subtests, wtime( 1 ), ctime( 1 )
757 WRITE( nout, fmt = 9996 )n, nb, nprow, npcol, mattype,
758 $ subtests, ctime( 1 )
760 ELSE IF( info.EQ.3 )
THEN
761 WRITE( nout, fmt = 9995 )n, nb, nprow, npcol, mattype,
769 9999
FORMAT( 1x, i5, 1x, i3, 1x, i3, 1x, i3, 1x, i3, 3x, a1, 1x,
770 $ f8.2, 1x, f8.2, 1x, g9.2, 1x, g9.2, 1x, a14 )
771 9998
FORMAT( 1x, i5, 1x, i3, 1x, i3, 1x, i3, 1x, i3, 3x, a1, 1x, 8x,
772 $ 1x, f8.2, 1x, g9.2, 1x, g9.2, a14 )
773 9997
FORMAT( 1x, i5, 1x, i3, 1x, i3, 1x, i3, 1x, i3, 3x, a1, 1x, f8.2,
774 $ 1x, f8.2, 21x,
'Bypassed' )
775 9996
FORMAT( 1x, i5, 1x, i3, 1x, i3, 1x, i3, 1x, i3, 3x, a1, 1x, 8x,
776 $ 1x, f8.2, 21x,
'Bypassed' )
777 9995
FORMAT( 1x, i5, 1x, i3, 1x, i3, 1x, i3, 1x, i3, 3x, a1, 32x,
778 $
'Bad MEMORY parameters' )
780 9993
FORMAT(
' ISEED( 1 ) =', i8 )
781 9992
FORMAT(
' ISEED( 2 ) =', i8 )
782 9991
FORMAT(
' ISEED( 3 ) =', i8 )
783 9990
FORMAT(
' ISEED( 4 ) =', i8 )
784 9989
FORMAT(
' N=', i8 )
785 9988
FORMAT(
' NPROW=', i8 )
786 9987
FORMAT(
' NPCOL=', i8 )
787 9986
FORMAT(
' NB=', i8 )
788 9985
FORMAT(
' MATTYPE=', i8 )
791 9982
FORMAT(
' ABSTOL=', d16.6 )
792 9981
FORMAT(
' THRESH=', d16.6 )