1 SUBROUTINE pdseprreq( HETERO, NIN, MEM, MEMSIZE, NOUT, ISEED,
2 $ NTESTS, NSKIPPED, NNOCHECK, NPASSED, INFO )
13 INTEGER INFO, MEMSIZE, NIN, NNOCHECK, NOUT, NPASSED,
18 DOUBLE PRECISION MEM( MEMSIZE )
73 parameter( dlen_ = 9 )
74 INTEGER DBLESZ, INTGSZ
75 parameter( dblesz = 8, intgsz = 4 )
77 parameter( maxsetsize = 50 )
81 INTEGER CONTEXT, IAM, IMIDPAD, INITCON, IPOSTPAD,
82 $ iprepad, isizesubtst, isizeevr, isizetst,
83 $ lda, llwork, matsize, mattype, mycol, myrow, n,
84 $ nb, nmatsizes, nmattypes, nnodes, np, npcol,
85 $ npconfigs, nprow, nq, nuplos, order, pconfig,
86 $ ptra, ptrcopya, ptrgap, ptriclus, ptrifail,
87 $ ptriwrk, ptrw, ptrw2, ptrwork, ptrz, res,
88 $ sizechk, sizemqrleft, sizemqrright, sizeqrf,
89 $ sizeqtq, sizesubtst, sizeevr,
90 $ sizetms, sizetst, uplo
92 DOUBLE PRECISION ABSTOL, THRESH
96 INTEGER DESCA( DLEN_ ), MATSIZES( MAXSETSIZE ),
97 $ mattypes( maxsetsize ), nbs( maxsetsize ),
98 $ npcols( maxsetsize ), nprows( maxsetsize )
101 INTEGER ICEIL, NUMROC
102 EXTERNAL iceil, numroc
105 EXTERNAL blacs_abort, blacs_get, blacs_gridexit,
106 $ blacs_gridinfo, blacs_gridinit, blacs_pinfo,
114 CALL blacs_pinfo( iam, nnodes )
115 CALL blacs_get( -1, 0, initcon )
116 CALL blacs_gridinit( initcon,
'R', 1, nnodes )
118 CALL pdsepinfo( initcon, iam, nin, nout, maxsetsize, nmatsizes,
119 $ matsizes, nuplos, uplos, npconfigs, nprows,
120 $ npcols, nbs, nmattypes, mattypes, 22, subtests,
121 $ thresh, order, abstol, info )
123 CALL blacs_gridexit( initcon )
127 DO 40 matsize = 1, nmatsizes
129 DO 30 pconfig = 1, npconfigs
131 DO 20 mattype = 1, nmattypes
133 DO 10 uplo = 1, nuplos
135 n = matsizes( matsize )
138 nprow = nprows( pconfig )
139 npcol = npcols( pconfig )
142 np = numroc( n, nb, 0, 0, nprow )
143 nq = numroc( n, nb, 0, 0, npcol )
144 iprepad =
max( nb, np )
146 ipostpad =
max( nb, nq )
148 lda =
max( np, 1 ) + imidpad
150 CALL blacs_get( -1, 0, context )
151 CALL blacs_gridinit( context,
'R', nprow, npcol )
152 CALL blacs_gridinfo( context, nprow, npcol, myrow,
155 IF( myrow.GE.0 )
THEN
156 CALL descinit( desca, n, n, nb, nb, 0, 0,
157 $ context, lda, info )
159 $ sizemqrleft, sizemqrright,
160 $ sizeqrf, sizetms, sizeqtq,
161 $ sizechk, sizeevr, isizeevr,
162 $ sizesubtst, isizesubtst,
163 $ sizetst, isizetst )
166 ptrz = ptra + lda*nq + iprepad + ipostpad
167 ptrcopya = ptrz + lda*nq + iprepad + ipostpad
168 ptrw = ptrcopya + lda*nq + iprepad + ipostpad
169 ptrw2 = ptrw +
max( n, 1 ) + iprepad + ipostpad
170 ptrgap = ptrw2 +
max( n, 1 ) + iprepad +
172 ptrifail = ptrgap + nprow*npcol + iprepad +
174 ptriclus = ptrifail + iceil( n+iprepad+ipostpad,
176 ptriwrk = ptriclus + iceil( 2*nprow*npcol+
177 $ iprepad+ipostpad, dblesz / intgsz )
178 ptrwork = ptriwrk + iceil( isizetst+iprepad+
179 $ ipostpad, dblesz / intgsz )
180 llwork = memsize - ptrwork + 1
183 IF( llwork.LT.sizetst )
THEN
184 nskipped = nskipped + 1
187 $ mattypes( mattype ), subtests,
188 $ thresh, n, abstol, iseed,
189 $ mem( ptra ), mem( ptrcopya ),
190 $ mem( ptrz ), lda, mem( ptrw ),
191 $ mem( ptrw2 ), mem( ptrifail ),
193 $ mem( ptrgap ), iprepad,
194 $ ipostpad, mem( ptrwork ),
195 $ llwork, mem( ptriwrk ),
196 $ isizetst, hetero, nout, res )
199 npassed = npassed + 1
200 ELSE IF( res.EQ.2 )
THEN
201 nnocheck = nnocheck + 1
202 ELSE IF( res.EQ.3 )
THEN
203 nskipped = nskipped + 1
204 WRITE( nout, fmt = * )
' PDSEPRREQ failed'
205 CALL blacs_abort( context, -1 )
208 CALL blacs_gridexit( context )