1 SUBROUTINE pzpbinfo( SUMMRY, NOUT, UPLO, NMAT, NVAL, LDNVAL, NBW,
2 $ BWVAL, LDBWVAL, NNB, NBVAL, LDNBVAL, NNR,
3 $ NRVAL, LDNRVAL, NNBR, NBRVAL, LDNBRVAL,
4 $ NGRIDS, PVAL, LDPVAL, QVAL, LDQVAL, THRESH,
18 $ LDBWVAL, LDNBRVAL, LDNBVAL, LDNRVAL, LDNVAL,
19 $ ldpval, ldqval, ngrids, nmat, nnb, nnbr, nbw,
24 INTEGER NBRVAL( LDNBRVAL ), NBVAL( LDNBVAL ),
25 $ nrval( ldnrval ), nval( ldnval ),
27 $ pval( ldpval ), qval(ldqval), work( * )
154 PARAMETER ( NIN = 11 )
162 EXTERNAL blacs_abort, blacs_get, blacs_gridexit,
163 $ blacs_gridinit, blacs_setup,
icopy, igebr2d,
164 $ igebs2d, sgebr2d, sgebs2d
168 DOUBLE PRECISION PDLAMCH
169 EXTERNAL LSAME, PDLAMCH
183 OPEN( nin, file =
'BLLT.dat', status =
'OLD' )
184 READ( nin, fmt = * ) summry
189 READ( nin, fmt = 9999 ) usrinfo
193 READ( nin, fmt = * ) summry
194 READ( nin, fmt = * ) nout
195 IF( nout.NE.0 .AND. nout.NE.6 )
196 $
OPEN( nout, file = summry, status =
'UNKNOWN' )
202 READ( nin, fmt = * ) uplo
207 READ( nin, fmt = * ) nmat
208 IF( nmat.LT.1 .OR. nmat.GT.ldnval )
THEN
209 WRITE( nout, fmt = 9994 )
'N', ldnval
212 READ( nin, fmt = * ) ( nval( i ), i = 1, nmat )
216 READ( nin, fmt = * ) nbw
217 IF( nbw.LT.1 .OR. nbw.GT.ldbwval )
THEN
218 WRITE( nout, fmt = 9994 )
'BW', ldbwval
221 READ( nin, fmt = * ) ( bwval( i ), i = 1, nbw )
225 READ( nin, fmt = * ) nnb
226 IF( nnb.LT.1 .OR. nnb.GT.ldnbval )
THEN
227 WRITE( nout, fmt = 9994 )
'NB', ldnbval
230 READ( nin, fmt = * ) ( nbval( i ), i = 1, nnb )
234 READ( nin, fmt = * ) nnr
235 IF( nnr.LT.1 .OR. nnr.GT.ldnrval )
THEN
236 WRITE( nout, fmt = 9994 )
'NRHS', ldnrval
239 READ( nin, fmt = * ) ( nrval( i ), i = 1, nnr )
243 READ( nin, fmt = * ) nnbr
244 IF( nnbr.LT.1 .OR. nnbr.GT.ldnbrval )
THEN
245 WRITE( nout, fmt = 9994 )
'NBRHS', ldnbrval
248 READ( nin, fmt = * ) ( nbrval( i ), i = 1, nnbr )
252 READ( nin, fmt = * ) ngrids
253 IF( ngrids.LT.1 .OR. ngrids.GT.ldpval )
THEN
254 WRITE( nout, fmt = 9994 )
'Grids', ldpval
256 ELSE IF( ngrids.GT.ldqval )
THEN
257 WRITE( nout, fmt = 9994 )
'Grids', ldqval
262 DO 8738 i = 1, ngrids
268 READ( nin, fmt = * ) ( qval( i ), i = 1, ngrids )
272 READ( nin, fmt = * ) thresh
281 IF( nprocs.LT.1 )
THEN
284 nprocs =
max( nprocs, pval( i )*qval( i ) )
286 CALL blacs_setup( iam, nprocs )
292 CALL blacs_get( -1, 0, ictxt )
293 CALL blacs_gridinit( ictxt,
'Row-major', 1, nprocs )
297 eps = pdlamch( ictxt,
'eps' )
301 CALL sgebs2d( ictxt,
'All',
' ', 1, 1, thresh, 1 )
315 IF( lsame( uplo,
'L' ) )
THEN
322 CALL igebs2d( ictxt,
'All',
' ', 1, 1, i-1, 1 )
324 CALL igebs2d( ictxt,
'All',
' ', i-1, 1, work, i-1 )
327 CALL icopy( nmat, nval, 1, work( i ), 1 )
329 CALL icopy( nbw, bwval, 1, work( i ), 1 )
331 CALL icopy( nnb, nbval, 1, work( i ), 1 )
333 CALL icopy( nnr, nrval, 1, work( i ), 1 )
335 CALL icopy( nnbr, nbrval, 1, work( i ), 1 )
337 CALL icopy( ngrids, pval, 1, work( i ), 1 )
339 CALL icopy( ngrids, qval, 1, work( i ), 1 )
341 CALL igebs2d( ictxt,
'All',
' ', i-1, 1, work, i-1 )
345 WRITE( nout, fmt = 9999 )
346 $
'SCALAPACK banded linear systems.'
347 WRITE( nout, fmt = 9999 ) usrinfo
348 WRITE( nout, fmt = * )
349 WRITE( nout, fmt = 9999 )
350 $
'Tests of the parallel '//
351 $
'complex single precision band matrix solve '
352 WRITE( nout, fmt = 9999 )
353 $
'The following scaled residual '//
354 $
'checks will be computed:'
355 WRITE( nout, fmt = 9999 )
356 $
' Solve residual = ||Ax - b|| / '//
357 $
'(||x|| * ||A|| * eps * N)'
358 IF( lsame( uplo,
'L' ) )
THEN
359 WRITE( nout, fmt = 9999 )
360 $
' Factorization residual = ||A - LL''|| /'//
361 $
' (||A|| * eps * N)'
363 WRITE( nout, fmt = 9999 )
364 $
' Factorization residual = ||A - U''U|| /'//
365 $
' (||A|| * eps * N)'
367 WRITE( nout, fmt = 9999 )
368 $
'The matrix A is randomly '//
369 $
'generated for each test.'
370 WRITE( nout, fmt = * )
371 WRITE( nout, fmt = 9999 )
372 $
'An explanation of the input/output '//
373 $
'parameters follows:'
374 WRITE( nout, fmt = 9999 )
375 $
'TIME : Indicates whether WALL or '//
376 $
'CPU time was used.'
378 WRITE( nout, fmt = 9999 )
379 $
'UPLO : Whether data represents ''Upper'//
380 $
''' or ''Lower'' triangular portion of array A.'
381 WRITE( nout, fmt = 9999 )
382 $
'TRANS : Whether solve is to be done with'//
383 $
' ''Transpose'' of matrix A (T,C) or not (N).'
384 WRITE( nout, fmt = 9999 )
385 $
'N : The number of rows and columns '//
387 WRITE( nout, fmt = 9999 )
388 $
'bw : The number of diagonals '//
390 WRITE( nout, fmt = 9999 )
391 $
'NB : The size of the column panels the'//
392 $
' matrix A is split into. [-1 for default]'
393 WRITE( nout, fmt = 9999 )
394 $
'NRHS : The total number of RHS to solve'//
396 WRITE( nout, fmt = 9999 )
397 $
'NBRHS : The number of RHS to be put on '//
398 $
'a column of processes before going'
399 WRITE( nout, fmt = 9999 )
400 $
' on to the next column of processes.'
401 WRITE( nout, fmt = 9999 )
402 $
'P : The number of process rows.'
403 WRITE( nout, fmt = 9999 )
404 $
'Q : The number of process columns.'
405 WRITE( nout, fmt = 9999 )
406 $
'THRESH : If a residual value is less than'//
407 $
' THRESH, CHECK is flagged as PASSED'
408 WRITE( nout, fmt = 9999 )
409 $
'Fact time: Time in seconds to factor the'//
411 WRITE( nout, fmt = 9999 )
412 $
'Sol Time: Time in seconds to solve the'//
414 WRITE( nout, fmt = 9999 )
415 $
'MFLOPS : Rate of execution for factor '//
416 $
'and solve using sequential operation count.'
417 WRITE( nout, fmt = 9999 )
418 $
'MFLOP2 : Rough estimate of speed '//
419 $
'using actual op count (accurate big P,N).'
420 WRITE( nout, fmt = * )
421 WRITE( nout, fmt = 9999 )
422 $
'The following parameter values will be used:'
423 WRITE( nout, fmt = 9999 )
425 WRITE( nout, fmt = 9996 )
426 $
'N ', ( nval(i), i = 1,
min(nmat, 10) )
428 $
WRITE( nout, fmt = 9997 ) ( nval(i), i = 11, nmat )
429 WRITE( nout, fmt = 9996 )
430 $
'bw ', ( bwval(i), i = 1,
min(nbw, 10) )
432 $
WRITE( nout, fmt = 9997 ) ( bwval(i), i = 11, nbw )
433 WRITE( nout, fmt = 9996 )
434 $
'NB ', ( nbval(i), i = 1,
min(nnb, 10) )
436 $
WRITE( nout, fmt = 9997 ) ( nbval(i), i = 11, nnb )
437 WRITE( nout, fmt = 9996 )
438 $
'NRHS ', ( nrval(i), i = 1,
min(nnr, 10) )
440 $
WRITE( nout, fmt = 9997 ) ( nrval(i), i = 11, nnr )
441 WRITE( nout, fmt = 9996 )
442 $
'NBRHS', ( nbrval(i), i = 1,
min(nnbr, 10) )
444 $
WRITE( nout, fmt = 9997 ) ( nbrval(i), i = 11, nnbr )
445 WRITE( nout, fmt = 9996 )
446 $
'P ', ( pval(i), i = 1,
min(ngrids, 10) )
448 $
WRITE( nout, fmt = 9997) ( pval(i), i = 11, ngrids )
449 WRITE( nout, fmt = 9996 )
450 $
'Q ', ( qval(i), i = 1,
min(ngrids, 10) )
452 $
WRITE( nout, fmt = 9997 ) ( qval(i), i = 11, ngrids )
453 WRITE( nout, fmt = * )
454 WRITE( nout, fmt = 9995 ) eps
455 WRITE( nout, fmt = 9998 ) thresh
462 $
CALL blacs_setup( iam, nprocs )
467 CALL blacs_get( -1, 0, ictxt )
468 CALL blacs_gridinit( ictxt,
'Row-major', 1, nprocs )
472 eps = pdlamch( ictxt,
'eps' )
474 CALL sgebr2d( ictxt,
'All',
' ', 1, 1, thresh, 1, 0, 0 )
475 CALL igebr2d( ictxt,
'All',
' ', 1, 1, i, 1, 0, 0 )
476 CALL igebr2d( ictxt,
'All',
' ', i, 1, work, i, 0, 0 )
490 IF( work( i ) .EQ. 1 )
THEN
497 i = nmat + nbw + nnb + nnr + nnbr + 2*ngrids
499 CALL igebr2d( ictxt,
'All',
' ', 1, i, work, 1, 0, 0 )
501 CALL icopy( nmat, work( i ), 1, nval, 1 )
503 CALL icopy( nbw, work( i ), 1, bwval, 1 )
505 CALL icopy( nnb, work( i ), 1, nbval, 1 )
507 CALL icopy( nnr, work( i ), 1, nrval, 1 )
509 CALL icopy( nnbr, work( i ), 1, nbrval, 1 )
511 CALL icopy( ngrids, work( i ), 1, pval, 1 )
513 CALL icopy( ngrids, work( i ), 1, qval, 1 )
517 CALL blacs_gridexit( ictxt )
521 20
WRITE( nout, fmt = 9993 )
523 IF( nout.NE.6 .AND. nout.NE.0 )
526 CALL blacs_abort( ictxt, 1 )
530 9998
FORMAT(
'Routines pass computational tests if scaled residual ',
531 $
'is less than ', g12.5 )
532 9997
FORMAT(
' ', 10i6 )
533 9996
FORMAT( 2x, a5,
': ', 10i6 )
534 9995
FORMAT(
'Relative machine precision (eps) is taken to be ',
536 9994
FORMAT(
' Number of values of ',5a,
' is less than 1 or greater ',
538 9993
FORMAT(
' Illegal input in file ',40a,
'. Aborting run.' )