1 SUBROUTINE pcdblaschk( SYMM, UPLO, TRANS, N, BWL, BWU, NRHS, X,
2 $ IX, JX, DESCX, IASEED, A, IA, JA, DESCA,
3 $ IBSEED, ANORM, RESID, WORK, WORKSIZ )
12 CHARACTER SYMM, TRANS, UPLO
13 INTEGER BWL, BWU, IA, IASEED, IBSEED,
14 $ ix, ja, jx, n, nrhs, worksiz
18 INTEGER DESCA( * ), DESCX( * )
19 COMPLEX A( * ), WORK( * ), X( * )
165 PARAMETER ( ONE = ( 1.0e+0, 0.0e+0 ),
166 $ zero = ( 0.0e+0, 0.0e+0 ) )
167 INTEGER BLOCK_CYCLIC_2D, CSRC_, CTXT_, DLEN_, DTYPE_,
168 $ LLD_, MB_, M_, NB_, N_, RSRC_
169 parameter( block_cyclic_2d = 1, dlen_ = 9, dtype_ = 1,
170 $ ctxt_ = 2, m_ = 3, n_ = 4, mb_ = 5, nb_ = 6,
171 $ rsrc_ = 7, csrc_ = 8, lld_ = 9 )
173 PARAMETER ( INT_ONE = 1 )
176 INTEGER IACOL, IAROW, ICTXT,
177 $ IIA, IIX, IPB, IPW,
178 $ ixcol, ixrow, j, jja, jjx, lda,
179 $ mycol, myrow, nb, np, npcol, nprow, nq
180 INTEGER BW, INFO, IPPRODUCT, WORK_MIN
181 REAL DIVISOR, EPS, RESID1, NORMX
186 EXTERNAL blacs_gridinfo, cgamx2d, cgemm, cgsum2d,
188 $ sgebs2d, sgerv2d, sgesd2d
191 INTEGER ICAMAX, NUMROC
193 EXTERNAL icamax, numroc, pslamch
196 INTRINSIC abs,
max,
min, mod, real
202 ictxt = desca( ctxt_ )
205 IF( lsame( symm,
'H' ) )
THEN
207 work_min =
max(5,
max(
max(bwl,bwu)*(
max(bwl,bwu)+2),nb))+2*nb
210 work_min =
max(5,
max(
max(bwl,bwu)*(
max(bwl,bwu)+2),nb))+2*nb
213 IF ( worksiz .LT. work_min )
THEN
214 CALL pxerbla( ictxt,
'PCBLASCHK', -18 )
218 CALL blacs_gridinfo( ictxt, nprow, npcol, myrow, mycol )
220 eps = pslamch( ictxt,
'eps' )
222 divisor = anorm * eps * real( n )
224 CALL infog2l( ia, ja, desca, nprow, npcol, myrow, mycol, iia, jja,
226 CALL infog2l( ix, jx, descx, nprow, npcol, myrow, mycol, iix, jjx,
228 np = numroc( (bwl+bwu+1), desca( mb_ ), myrow, 0, nprow )
229 nq = numroc( n, desca( nb_ ), mycol, 0, npcol )
232 ipproduct = 1 + desca( nb_ )
233 ipw = 1 + 2*desca( nb_ )
239 IF( lsame( symm,
'H' ))
THEN
240 CALL pcbmatgen( ictxt, uplo,
'D', bw, bw, n, bw+1,
241 $ desca( nb_ ), a, desca( lld_ ), 0, 0,
242 $ iaseed, myrow, mycol, nprow, npcol )
245 CALL pcbmatgen( ictxt,
'N', uplo, bwl, bwu, n,
246 $ desca( mb_ ), desca( nb_ ), a,
247 $ desca( lld_ ), 0, 0, iaseed, myrow,
248 $ mycol, nprow, npcol )
260 CALL pcgbdcmv( bwl+bwu+1, bwl, bwu, trans, n, a, 1, desca,
261 $ 1, x( 1 + (j-1)*descx( lld_ )), 1, descx,
262 $ work( ipproduct ), work( ipw ),
263 $ (
max(bwl,bwu)+2)*
max(bwl,bwu), info )
268 CALL pcmatgen( descx( ctxt_ ),
'No',
'No', descx( m_ ),
269 $ descx( n_ ), descx( mb_ ), descx( nb_ ),
270 $ work( ipb ), descx( lld_ ), descx( rsrc_ ),
271 $ descx( csrc_ ), ibseed, 0, nq, j-1, 1, mycol,
272 $ myrow, npcol, nprow )
276 CALL pcaxpy( n, -one, work( ipproduct ), 1, 1, descx, 1,
277 $ work( ipb ), 1, 1, descx, 1 )
279 CALL pscnrm2( n, normx,
280 $ x, 1, j, descx, 1 )
282 CALL pscnrm2( n, resid1,
283 $ work( ipb ), 1, 1, descx, 1 )
288 resid1 = resid1 / ( normx*divisor )
290 resid =
max( resid, resid1 )