1 SUBROUTINE pcpblaschk( SYMM, UPLO, N, BWL, BWU, NRHS, X, IX, JX,
2 $ DESCX, IASEED, A, IA, JA, DESCA, IBSEED,
3 $ ANORM, RESID, WORK, WORKSIZ )
13 INTEGER BWL, BWU, IA, IASEED, IBSEED,
14 $ ix, ja, jx, n, nrhs, worksiz
18 INTEGER DESCA( * ), DESCX( * )
19 COMPLEX A( * ), WORK( * ), X( * )
162 PARAMETER ( ONE = ( 1.0e+0, 0.0e+0 ),
163 $ zero = ( 0.0e+0, 0.0e+0 ) )
164 INTEGER BLOCK_CYCLIC_2D, CSRC_, CTXT_, DLEN_, DTYPE_,
165 $ LLD_, MB_, M_, NB_, N_, RSRC_
166 parameter( block_cyclic_2d = 1, dlen_ = 9, dtype_ = 1,
167 $ ctxt_ = 2, m_ = 3, n_ = 4, mb_ = 5, nb_ = 6,
168 $ rsrc_ = 7, csrc_ = 8, lld_ = 9 )
170 PARAMETER ( INT_ONE = 1 )
173 INTEGER IACOL, IAROW, ICTXT,
174 $ IIA, IIX, IPB, IPW,
175 $ ixcol, ixrow, j, jja, jjx, lda,
176 $ mycol, myrow, nb, np, npcol, nprow, nq
177 INTEGER BW, INFO, IPPRODUCT, WORK_MIN
178 REAL DIVISOR, EPS, RESID1, NORMX
183 EXTERNAL blacs_gridinfo, cgamx2d, cgemm, cgsum2d,
185 $ sgebs2d, sgerv2d, sgesd2d
188 INTEGER ICAMAX, NUMROC
190 EXTERNAL icamax, numroc, pslamch
193 INTRINSIC abs,
max,
min, mod, real
199 ictxt = desca( ctxt_ )
202 IF( lsame( symm,
'H' ) )
THEN
204 work_min =
max(5,
max(bw*(bw+2),nb))+2*nb
207 work_min =
max(5,
max(bw*(bw+2),nb))+2*nb
210 IF ( worksiz .LT. work_min )
THEN
211 CALL pxerbla( ictxt,
'PCBLASCHK', -18 )
215 CALL blacs_gridinfo( ictxt, nprow, npcol, myrow, mycol )
217 eps = pslamch( ictxt,
'eps' )
219 divisor = anorm * eps * real( n )
221 CALL infog2l( ia, ja, desca, nprow, npcol, myrow, mycol, iia, jja,
223 CALL infog2l( ix, jx, descx, nprow, npcol, myrow, mycol, iix, jjx,
225 np = numroc( (bw+1), desca( mb_ ), myrow, 0, nprow )
226 nq = numroc( n, desca( nb_ ), mycol, 0, npcol )
229 ipproduct = 1 + desca( nb_ )
230 ipw = 1 + 2*desca( nb_ )
236 IF( lsame( symm,
'H' ))
THEN
237 CALL pcbmatgen( ictxt, uplo,
'D', bw, bw, n, bw+1,
238 $ desca( nb_ ), a, desca( lld_ ), 0, 0,
239 $ iaseed, myrow, mycol, nprow, npcol )
242 CALL pcbmatgen( ictxt,
'N', uplo, bwl, bwu, n,
243 $ desca( mb_ ), desca( nb_ ), a,
244 $ desca( lld_ ), 0, 0, iaseed, myrow,
245 $ mycol, nprow, npcol )
257 CALL pcpbdcmv( bw+1, bw, uplo, n, a, 1, desca,
258 $ 1, x( 1 + (j-1)*descx( lld_ )), 1, descx,
259 $ work( ipproduct ), work( ipw ), (bw+2)*bw, info )
264 CALL pcmatgen( descx( ctxt_ ),
'No',
'No', descx( m_ ),
265 $ descx( n_ ), descx( mb_ ), descx( nb_ ),
266 $ work( ipb ), descx( lld_ ), descx( rsrc_ ),
267 $ descx( csrc_ ), ibseed, 0, nq, j-1, 1, mycol,
268 $ myrow, npcol, nprow )
272 CALL pcaxpy( n, -one, work( ipproduct ), 1, 1, descx, 1,
273 $ work( ipb ), 1, 1, descx, 1 )
275 CALL pscnrm2( n, normx,
276 $ x, 1, j, descx, 1 )
278 CALL pscnrm2( n, resid1,
279 $ work( ipb ), 1, 1, descx, 1 )
284 resid1 = resid1 / ( normx*divisor )
286 resid =
max( resid, resid1 )