1 SUBROUTINE pcqrinfo( SUMMRY, NOUT, NFACT, FACTOR, LDFACT, NMAT,
2 $ MVAL, LDMVAL, NVAL, LDNVAL, NNB, MBVAL,
3 $ LDMBVAL, NBVAL, LDNBVAL, NGRIDS, PVAL,
4 $ LDPVAL, QVAL, LDQVAL, THRESH, WORK, IAM,
13 INTEGER IAM, LDFACT, LDMBVAL, LDMVAL, LDNBVAL, LDNVAL,
14 $ LDPVAL, LDQVAL, NFACT, NGRIDS, NMAT, NNB,
19 CHARACTER*2 FACTOR( LDFACT )
21 INTEGER MBVAL( LDMBVAL ), MVAL( LDMVAL ),
22 $ NBVAL( LDNBVAL ), NVAL( LDNVAL ),
23 $ 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 LSAMEN, PSLAMCH
176 OPEN( nin, file=
'QR.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 = * ) nfact
196 IF( nfact.LT.1 .OR. nfact.GT.ldfact )
THEN
197 WRITE( nout, fmt = 9994 )
'nb of factorization', ldfact
200 READ( nin, fmt = * ) ( factor( i ), i = 1, nfact )
204 READ( nin, fmt = * ) nmat
205 IF( nmat.LT.1 .OR. nmat.GT.ldnval )
THEN
206 WRITE( nout, fmt = 9994 )
'N', ldnval
208 ELSE IF( nmat.GT.ldmval )
THEN
209 WRITE( nout, fmt = 9994 )
'M', ldmval
212 READ( nin, fmt = * ) ( mval( i ), i = 1, nmat )
213 READ( nin, fmt = * ) ( nval( i ), i = 1, nmat )
217 READ( nin, fmt = * ) nnb
218 IF( nnb.LT.1 .OR. nnb.GT.ldmbval )
THEN
219 WRITE( nout, fmt = 9994 )
'MB', ldmbval
221 ELSE IF( nnb.GT.ldnbval )
THEN
222 WRITE( nout, fmt = 9994 )
'NB', ldnbval
225 READ( nin, fmt = * ) ( mbval( i ), i = 1, nnb )
226 READ( nin, fmt = * ) ( nbval( i ), i = 1, nnb )
230 READ( nin, fmt = * ) ngrids
231 IF( ngrids.LT.1 .OR. ngrids.GT.ldpval )
THEN
232 WRITE( nout, fmt = 9994 )
'Grids', ldpval
234 ELSE IF( ngrids.GT.ldqval )
THEN
235 WRITE( nout, fmt = 9994 )
'Grids', ldqval
241 READ( nin, fmt = * ) ( pval( i ), i = 1, ngrids )
242 READ( nin, fmt = * ) ( qval( i ), i = 1, ngrids )
246 READ( nin, fmt = * ) thresh
255 IF( nprocs.LT.1 )
THEN
258 nprocs =
max( nprocs, pval( i ) * qval( i ) )
260 CALL blacs_setup( iam, nprocs )
266 CALL blacs_get( -1, 0, ictxt )
267 CALL blacs_gridinit( ictxt,
'Row-major', 1, nprocs )
271 eps = pslamch( ictxt,
'eps' )
275 CALL sgebs2d( ictxt,
'All',
' ', 1, 1, thresh, 1 )
280 CALL igebs2d( ictxt,
'All',
' ', 4, 1, work, 4 )
284 IF( lsamen( 2, factor( k ),
'QR' ) )
THEN
287 ELSE IF( lsamen( 2, factor( k ),
'QL' ) )
THEN
290 ELSE IF( lsamen( 2, factor( k ),
'LQ' ) )
THEN
293 ELSE IF( lsamen( 2, factor( k ),
'RQ' ) )
THEN
296 ELSE IF( lsamen( 2, factor( k ),
'QP' ) )
THEN
299 ELSE IF( lsamen( 2, factor( k ),
'TZ' ) )
THEN
305 CALL icopy( nmat, mval, 1, work( i ), 1 )
307 CALL icopy( nmat, nval, 1, work( i ), 1 )
309 CALL icopy( nnb, mbval, 1, work( i ), 1 )
311 CALL icopy( nnb, nbval, 1, work( i ), 1 )
313 CALL icopy( ngrids, pval, 1, work( i ), 1 )
315 CALL icopy( ngrids, qval, 1, work( i ), 1 )
317 CALL igebs2d( ictxt,
'All',
' ', i, 1, work, i )
321 WRITE( nout, fmt = 9999 )
322 $
'ScaLAPACK QR factorizations routines.'
323 WRITE( nout, fmt = 9999 ) usrinfo
324 WRITE( nout, fmt = * )
325 WRITE( nout, fmt = 9999 )
326 $
'Tests of the parallel '//
327 $
'complex single precision QR factorizations '//
329 WRITE( nout, fmt = 9999 )
330 $
'The following scaled residual '//
331 $
'checks will be computed:'
332 WRITE( nout, fmt = 9999 )
333 $
' || A - QR || / (|| A || * eps * N) and/or'
334 WRITE( nout, fmt = 9999 )
335 $
' || A - QL || / (|| A || * eps * N) and/or'
336 WRITE( nout, fmt = 9999 )
337 $
' || A - LQ || / (|| A || * eps * N) and/or'
338 WRITE( nout, fmt = 9999 )
339 $
' || A - RQ || / (|| A || * eps * N) and/or'
340 WRITE( nout, fmt = 9999 )
341 $
' || A - QRP || / (|| A || * eps * N) and/or'
342 WRITE( nout, fmt = 9999 )
343 $
' || A - TZ || / (|| A || * eps * N)'
344 WRITE( nout, fmt = 9999 )
345 $
'The matrix A is randomly '//
346 $
'generated for each test.'
347 WRITE( nout, fmt = * )
348 WRITE( nout, fmt = 9999 )
349 $
'An explanation of the input/output '//
350 $
'parameters follows:'
351 WRITE( nout, fmt = 9999 )
352 $
'TIME : Indicates whether WALL or '//
353 $
'CPU time was used.'
355 WRITE( nout, fmt = 9999 )
356 $
'M : The number of rows in the '//
358 WRITE( nout, fmt = 9999 )
359 $
'N : The number of columns in the '//
361 WRITE( nout, fmt = 9999 )
362 $
'MB : The row blocksize of the blocks'//
363 $
' the matrix A is split into.'
364 WRITE( nout, fmt = 9999 )
365 $
'NB : The column blocksize of the blocks'//
366 $
' the matrix A is split into.'
367 WRITE( nout, fmt = 9999 )
368 $
'P : The number of process rows.'
369 WRITE( nout, fmt = 9999 )
370 $
'Q : The number of process columns.'
371 WRITE( nout, fmt = 9999 )
372 $
'THRESH : If a residual value is less than'//
373 $
' THRESH, CHECK is flagged as PASSED'
374 WRITE( nout, fmt = 9999 )
375 WRITE( nout, fmt = 9999 )
376 $
'Fact Time: Time in seconds to factor the'//
378 WRITE( nout, fmt = 9999 )
379 $
'MFLOPS : Execution rate of the '//
381 WRITE( nout, fmt = * )
382 WRITE( nout, fmt = 9999 )
383 $
'The following parameter values will be used:'
384 WRITE( nout, fmt = 9996 )
385 $
'M ', ( mval( i ), i = 1,
min( nmat, 10 ) )
387 $
WRITE( nout, fmt = 9997 ) ( mval( i ), i = 11, nmat )
388 WRITE( nout, fmt = 9996 )
389 $
'N ', ( nval( i ), i = 1,
min( nmat, 10 ) )
391 $
WRITE( nout, fmt = 9997 ) ( nval( i ), i = 11, nmat )
392 WRITE( nout, fmt = 9996 )
393 $
'MB ', ( mbval( i ), i = 1,
min( nnb, 10 ) )
395 $
WRITE( nout, fmt = 9997 ) ( mbval( i ), i = 11, nnb )
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 $
'P ', ( pval( i ), i = 1,
min( ngrids, 10 ) )
403 $
WRITE( nout, fmt = 9997) ( pval( i ), i = 11, ngrids )
404 WRITE( nout, fmt = 9996 )
405 $
'Q ', ( qval( i ), i = 1,
min( ngrids, 10 ) )
407 $
WRITE( nout, fmt = 9997 ) ( qval( i ), i = 11, ngrids )
408 WRITE( nout, fmt = * )
409 WRITE( nout, fmt = 9995 ) eps
410 WRITE( nout, fmt = 9998 ) thresh
417 $
CALL blacs_setup( iam, nprocs )
422 CALL blacs_get( -1, 0, ictxt )
423 CALL blacs_gridinit( ictxt,
'Row-major', 1, nprocs )
427 eps = pslamch( ictxt,
'eps' )
429 CALL sgebr2d( ictxt,
'All',
' ', 1, 1, thresh, 1, 0, 0 )
430 CALL igebr2d( ictxt,
'All',
' ', 4, 1, work, 4, 0, 0 )
436 i = nfact + 2*nmat + 2*nnb + 2*ngrids
437 CALL igebr2d( ictxt,
'All',
' ', i, 1, work, i, 0, 0 )
440 IF( work( k ).EQ.1 )
THEN
442 ELSE IF( work( k ).EQ.2 )
THEN
444 ELSE IF( work( k ).EQ.3 )
THEN
446 ELSE IF( work( k ).EQ.4 )
THEN
448 ELSE IF( work( k ).EQ.5 )
THEN
450 ELSE IF( work( k ).EQ.6 )
THEN
456 CALL icopy( nmat, work( i ), 1, mval, 1 )
458 CALL icopy( nmat, work( i ), 1, nval, 1 )
460 CALL icopy( nnb, work( i ), 1, mbval, 1 )
462 CALL icopy( nnb, work( i ), 1, nbval, 1 )
464 CALL icopy( ngrids, work( i ), 1, pval, 1 )
466 CALL icopy( ngrids, work( i ), 1, qval, 1 )
470 CALL blacs_gridexit( ictxt )
474 40
WRITE( nout, fmt = 9993 )
476 IF( nout.NE.6 .AND. nout.NE.0 )
478 CALL blacs_abort( ictxt, 1 )
483 9998
FORMAT(
'Routines pass computational tests if scaled residual ',
484 $
'is less than ', g12.5 )
485 9997
FORMAT(
' ', 10i6 )
486 9996
FORMAT( 2x, a5,
' : ', 10i6 )
487 9995
FORMAT(
'Relative machine precision (eps) is taken to be ',
489 9994
FORMAT(
' Number of values of ',5a,
' is less than 1 or greater ',
491 9993
FORMAT(
' Illegal input in file ',40a,
'. Aborting run.' )