1 SUBROUTINE pclltinfo( SUMMRY, NOUT, UPLO, NMAT, NVAL, LDNVAL, NNB,
2 $ NBVAL, LDNBVAL, NNR, NRVAL, LDNRVAL, NNBR,
3 $ NBRVAL, LDNBRVAL, NGRIDS, PVAL, LDPVAL,
4 $ QVAL, LDQVAL, THRESH, EST, WORK, IAM,
16 INTEGER IAM, LDNBRVAL, LDNBVAL, LDNRVAL, LDNVAL,
17 $ ldpval, ldqval, ngrids, nmat, nnb, nnbr,
22 INTEGER NBRVAL( LDNBRVAL ), NBVAL( LDNBVAL ),
23 $ nrval( ldnrval ), nval( ldnval ),
24 $ pval( ldpval ), qval(ldqval), work( * )
141 INTEGER BLOCK_CYCLIC_2D, CSRC_, CTXT_, DLEN_, DTYPE_,
142 $ LLD_, MB_, M_, NB_, N_, RSRC_
143 PARAMETER ( BLOCK_CYCLIC_2D = 1, dlen_ = 9, dtype_ = 1,
144 $ ctxt_ = 2, m_ = 3, n_ = 4, mb_ = 5, nb_ = 6,
145 $ rsrc_ = 7, csrc_ = 8, lld_ = 9 )
147 parameter( nin = 11 )
155 EXTERNAL blacs_abort, blacs_get, blacs_gridexit,
156 $ blacs_gridinit, blacs_setup,
icopy, igebr2d,
157 $ igebs2d, sgebr2d, sgebs2d
162 EXTERNAL LSAME, PSLAMCH
176 OPEN( nin, file =
'LLT.dat', status =
'OLD' )
177 READ( nin, fmt = * ) summry
182 READ( nin, fmt = 9999 ) usrinfo
186 READ( nin, fmt = * ) summry
187 READ( nin, fmt = * ) nout
188 IF( nout.NE.0 .AND. nout.NE.6 )
189 $
OPEN( nout, file = summry, status =
'UNKNOWN' )
195 READ( nin, fmt = * ) uplo
199 READ( nin, fmt = * ) nmat
200 IF( nmat.LT.1 .OR. nmat.GT.ldnval )
THEN
201 WRITE( nout, fmt = 9994 )
'N', ldnval
204 READ( nin, fmt = * ) ( nval( i ), i = 1, nmat )
208 READ( nin, fmt = * ) nnb
209 IF( nnb.LT.1 .OR. nnb.GT.ldnbval )
THEN
210 WRITE( nout, fmt = 9994 )
'NB', ldnbval
213 READ( nin, fmt = * ) ( nbval( i ), i = 1, nnb )
217 READ( nin, fmt = * ) nnr
218 IF( nnr.LT.1 .OR. nnr.GT.ldnrval )
THEN
219 WRITE( nout, fmt = 9994 )
'NRHS', ldnrval
222 READ( nin, fmt = * ) ( nrval( i ), i = 1, nnr )
226 READ( nin, fmt = * ) nnbr
227 IF( nnbr.LT.1 .OR. nnbr.GT.ldnbrval )
THEN
228 WRITE( nout, fmt = 9994 )
'NBRHS', ldnbrval
231 READ( nin, fmt = * ) ( nbrval( i ), i = 1, nnbr )
235 READ( nin, fmt = * ) ngrids
236 IF( ngrids.LT.1 .OR. ngrids.GT.ldpval )
THEN
237 WRITE( nout, fmt = 9994 )
'Grids', ldpval
239 ELSE IF( ngrids.GT.ldqval )
THEN
240 WRITE( nout, fmt = 9994 )
'Grids', ldqval
246 READ( nin, fmt = * ) ( pval( i ), i = 1, ngrids )
247 READ( nin, fmt = * ) ( qval( i ), i = 1, ngrids )
251 READ( nin, fmt = * ) thresh
256 READ( nin, fmt = * ) est
265 IF( nprocs.LT.1 )
THEN
268 nprocs =
max( nprocs, pval( i )*qval( i ) )
270 CALL blacs_setup( iam, nprocs )
276 CALL blacs_get( -1, 0, ictxt )
277 CALL blacs_gridinit( ictxt,
'Row-major', 1, nprocs )
281 eps = pslamch( ictxt,
'eps' )
285 CALL sgebs2d( ictxt,
'All',
' ', 1, 1, thresh, 1 )
291 IF( lsame( uplo,
'L' ) )
THEN
301 CALL igebs2d( ictxt,
'All',
' ', 7, 1, work, 7 )
304 CALL icopy( nmat, nval, 1, work( i ), 1 )
306 CALL icopy( nnb, nbval, 1, work( i ), 1 )
308 CALL icopy( nnr, nrval, 1, work( i ), 1 )
310 CALL icopy( nnbr, nbrval, 1, work( i ), 1 )
312 CALL icopy( ngrids, pval, 1, work( i ), 1 )
314 CALL icopy( ngrids, qval, 1, work( i ), 1 )
316 CALL igebs2d( ictxt,
'All',
' ', i, 1, work, i )
320 WRITE( nout, fmt = 9999 )
321 $
'SCALAPACK Ax=b by LLt factorization.'
322 WRITE( nout, fmt = 9999 ) usrinfo
323 WRITE( nout, fmt = * )
324 WRITE( nout, fmt = 9999 )
325 $
'Tests of the parallel '//
326 $
'complex single precision LLt factorization '//
328 WRITE( nout, fmt = 9999 )
329 $
'The following scaled residual '//
330 $
'checks will be computed:'
331 WRITE( nout, fmt = 9999 )
332 $
' Solve residual = ||Ax - b|| / '//
333 $
'(||x|| * ||A|| * eps * N)'
334 IF( lsame( uplo,
'L' ) )
THEN
335 WRITE( nout, fmt = 9999 )
336 $
' Factorization residual = ||A - LL''|| /'//
337 $
' (||A|| * eps * N)'
339 WRITE( nout, fmt = 9999 )
340 $
' Factorization residual = ||A - U''U|| /'//
341 $
' (||A|| * eps * N)'
343 WRITE( nout, fmt = 9999 )
344 $
'The matrix A is randomly '//
345 $
'generated for each test.'
346 WRITE( nout, fmt = * )
347 WRITE( nout, fmt = 9999 )
348 $
'An explanation of the input/output '//
349 $
'parameters follows:'
350 WRITE( nout, fmt = 9999 )
351 $
'TIME : Indicates whether WALL or '//
352 $
'CPU time was used.'
354 WRITE( nout, fmt = 9999 )
355 $
'UPLO : Whether data is stored in ''Upper'//
356 $
''' or ''Lower'' portion of array A.'
357 WRITE( nout, fmt = 9999 )
358 $
'N : The number of rows and columns '//
360 WRITE( nout, fmt = 9999 )
361 $
'NB : The size of the square blocks the'//
362 $
' matrix A is split into.'
363 WRITE( nout, fmt = 9999 )
364 $
'NRHS : The total number of RHS to solve'//
366 WRITE( nout, fmt = 9999 )
367 $
'NBRHS : The number of RHS to be put on '//
368 $
'a column of processes before going'
369 WRITE( nout, fmt = 9999 )
370 $
' on to the next column of processes.'
371 WRITE( nout, fmt = 9999 )
372 $
'P : The number of process rows.'
373 WRITE( nout, fmt = 9999 )
374 $
'Q : The number of process columns.'
375 WRITE( nout, fmt = 9999 )
376 $
'THRESH : If a residual value is less than'//
377 $
' THRESH, CHECK is flagged as PASSED'
378 WRITE( nout, fmt = 9999 )
379 $
'LLt time: Time in seconds to factor the'//
381 WRITE( nout, fmt = 9999 )
382 $
'Sol Time: Time in seconds to solve the'//
384 WRITE( nout, fmt = 9999 )
385 $
'MFLOPS : Rate of execution for factor '//
387 WRITE( nout, fmt = * )
388 WRITE( nout, fmt = 9999 )
389 $
'The following parameter values will be used:'
390 WRITE( nout, fmt = 9999 )
392 WRITE( nout, fmt = 9996 )
393 $
'N ', ( nval(i), i = 1,
min(nmat, 10) )
395 $
WRITE( nout, fmt = 9997 ) ( nval(i), i = 11, nmat )
396 WRITE( nout, fmt = 9996 )
397 $
'NB ', ( nbval(i), i = 1,
min(nnb, 10) )
399 $
WRITE( nout, fmt = 9997 ) ( nbval(i), i = 11, nnb )
400 WRITE( nout, fmt = 9996 )
401 $
'NRHS ', ( nrval(i), i = 1,
min(nnr, 10) )
403 $
WRITE( nout, fmt = 9997 ) ( nrval(i), i = 11, nnr )
404 WRITE( nout, fmt = 9996 )
405 $
'NBRHS', ( nbrval(i), i = 1,
min(nnbr, 10) )
407 $
WRITE( nout, fmt = 9997 ) ( nbrval(i), i = 11, nnbr )
408 WRITE( nout, fmt = 9996 )
409 $
'P ', ( pval(i), i = 1,
min(ngrids, 10) )
411 $
WRITE( nout, fmt = 9997) ( pval(i), i = 11, ngrids )
412 WRITE( nout, fmt = 9996 )
413 $
'Q ', ( qval(i), i = 1,
min(ngrids, 10) )
415 $
WRITE( nout, fmt = 9997 ) ( qval(i), i = 11, ngrids )
416 WRITE( nout, fmt = * )
417 WRITE( nout, fmt = 9995 ) eps
418 WRITE( nout, fmt = 9998 ) thresh
425 $
CALL blacs_setup( iam, nprocs )
430 CALL blacs_get( -1, 0, ictxt )
431 CALL blacs_gridinit( ictxt,
'Row-major', 1, nprocs )
435 eps = pslamch( ictxt,
'eps' )
437 CALL sgebr2d( ictxt,
'All',
' ', 1, 1, thresh, 1, 0, 0 )
438 CALL igebr2d( ictxt,
'All',
' ', 7, 1, work, 7, 0, 0 )
444 IF( work( 6 ).EQ.1 )
THEN
449 IF( work( 7 ).EQ.1 )
THEN
455 i = nmat + nnb + nnr + nnbr + 2*ngrids
456 CALL igebr2d( ictxt,
'All',
' ', 1, i, work, 1, 0, 0 )
458 CALL icopy( nmat, work( i ), 1, nval, 1 )
460 CALL icopy( nnb, work( i ), 1, nbval, 1 )
462 CALL icopy( nnr, work( i ), 1, nrval, 1 )
464 CALL icopy( nnbr, work( i ), 1, nbrval, 1 )
466 CALL icopy( ngrids, work( i ), 1, pval, 1 )
468 CALL icopy( ngrids, work( i ), 1, qval, 1 )
472 CALL blacs_gridexit( ictxt )
476 20
WRITE( nout, fmt = 9993 )
478 IF( nout.NE.6 .AND. nout.NE.0 )
480 CALL blacs_abort( ictxt, 1 )
484 9998
FORMAT(
'Routines pass computational tests if scaled residual ',
485 $
'is less than ', g12.5 )
486 9997
FORMAT(
' ', 10i6 )
487 9996
FORMAT( 2x, a5,
': ', 10i6 )
488 9995
FORMAT(
'Relative machine precision (eps) is taken to be ',
490 9994
FORMAT(
' Number of values of ',5a,
' is less than 1 or greater ',
492 9993
FORMAT(
' Illegal input in file ',40a,
'. Aborting run.' )