1 SUBROUTINE pcinvinfo( SUMMRY, NOUT, NMTYP, MATTYP, LDMTYP, NMAT,
2 $ NVAL, LDNVAL, NNB, NBVAL, LDNBVAL, NGRIDS,
3 $ PVAL, LDPVAL, QVAL, LDQVAL, THRESH, WORK,
12 INTEGER IAM, LDMTYP, LDNBVAL, LDNVAL, LDPVAL, LDQVAL,
13 $ NGRIDS, NMAT, NMTYP, NNB, NOUT, NPROCS
17 CHARACTER*3 MATTYP( LDMTYP )
18 CHARACTER*( * ) SUMMRY
19 INTEGER NBVAL( LDNBVAL ), NVAL( LDNVAL ),
20 $ pval( ldpval ), qval( ldqval ), work( * )
119 INTEGER BLOCK_CYCLIC_2D, CSRC_, CTXT_, DLEN_, DTYPE_,
120 $ LLD_, MB_, M_, NB_, N_, RSRC_
121 PARAMETER ( BLOCK_CYCLIC_2D = 1, dlen_ = 9, dtype_ = 1,
122 $ ctxt_ = 2, m_ = 3, n_ = 4, mb_ = 5, nb_ = 6,
123 $ rsrc_ = 7, csrc_ = 8, lld_ = 9 )
125 PARAMETER ( NIN = 11 )
133 EXTERNAL blacs_abort, blacs_get, blacs_gridexit,
134 $ blacs_gridinit, blacs_setup,
icopy, igebr2d,
135 $ igebs2d, sgebr2d, sgebs2d
140 EXTERNAL LSAMEN, PSLAMCH
154 OPEN( nin, file=
'INV.dat', status=
'OLD' )
155 READ( nin, fmt = * ) summry
160 READ( nin, fmt = 9999 ) usrinfo
164 READ( nin, fmt = * ) summry
165 READ( nin, fmt = * ) nout
166 IF( nout.NE.0 .AND. nout.NE.6 )
167 $
OPEN( nout, file = summry, status =
'UNKNOWN' )
173 READ( nin, fmt = * ) nmtyp
174 IF( nmtyp.LT.1 .OR. nmtyp.GT.ldmtyp )
THEN
175 WRITE( nout, fmt = 9994 )
'nb of matrix types', ldmtyp
178 READ( nin, fmt = * ) ( mattyp( i ), i = 1, nmtyp )
182 READ( nin, fmt = * ) nmat
183 IF( nmat.LT.1 .OR. nmat.GT.ldnval )
THEN
184 WRITE( nout, fmt = 9994 )
'N', ldnval
187 READ( nin, fmt = * ) ( nval( i ), i = 1, nmat )
191 READ( nin, fmt = * ) nnb
192 IF( nnb.LT.1 .OR. nnb.GT.ldnbval )
THEN
193 WRITE( nout, fmt = 9994 )
'NB', ldnbval
196 READ( nin, fmt = * ) ( nbval( i ), i = 1, nnb )
200 READ( nin, fmt = * ) ngrids
201 IF( ngrids.LT.1 .OR. ngrids.GT.ldpval )
THEN
202 WRITE( nout, fmt = 9994 )
'Grids', ldpval
204 ELSE IF( ngrids.GT.ldqval )
THEN
205 WRITE( nout, fmt = 9994 )
'Grids', ldqval
211 READ( nin, fmt = * ) ( pval( i ), i = 1, ngrids )
212 READ( nin, fmt = * ) ( qval( i ), i = 1, ngrids )
216 READ( nin, fmt = * ) thresh
225 IF( nprocs.LT.1 )
THEN
228 nprocs =
max( nprocs, pval( i ) * qval( i ) )
230 CALL blacs_setup( iam, nprocs )
236 CALL blacs_get( -1, 0, ictxt )
237 CALL blacs_gridinit( ictxt,
'Row-major', 1, nprocs )
241 eps = pslamch( ictxt,
'eps' )
245 CALL sgebs2d( ictxt,
'All',
' ', 1, 1, thresh, 1 )
250 CALL igebs2d( ictxt,
'All',
' ', 4, 1, work, 4 )
254 IF( lsamen( 3, mattyp( k ),
'GEN' ) )
THEN
257 ELSE IF( lsamen( 3, mattyp( k ),
'UTR' ) )
THEN
260 ELSE IF( lsamen( 3, mattyp( k ),
'LTR' ) )
THEN
263 ELSE IF( lsamen( 3, mattyp( k ),
'UPD' ) )
THEN
266 ELSE IF( lsamen( 3, mattyp( k ),
'LPD' ) )
THEN
272 CALL icopy( nmat, nval, 1, work( i ), 1 )
274 CALL icopy( nnb, nbval, 1, work( i ), 1 )
276 CALL icopy( ngrids, pval, 1, work( i ), 1 )
278 CALL icopy( ngrids, qval, 1, work( i ), 1 )
280 CALL igebs2d( ictxt,
'All',
' ', i, 1, work, i )
284 WRITE( nout, fmt = 9999 )
285 $
'SCALAPACK Matrix Inversion routines.'
286 WRITE( nout, fmt = 9999 ) usrinfo
287 WRITE( nout, fmt = * )
288 WRITE( nout, fmt = 9999 )
289 $
'Tests of the parallel '//
290 $
'complex single precision Matrix Inversion '//
292 WRITE( nout, fmt = 9999 )
293 $
'The following scaled residual '//
294 $
'checks will be computed:'
295 WRITE( nout, fmt = 9999 )
296 $
' Inverse residual = ||inv(A)*A - I|| '//
297 $
'/ (||A|| * eps * N)'
298 WRITE( nout, fmt = 9999 )
299 $
'The matrix A is randomly '//
300 $
'generated for each test.'
301 WRITE( nout, fmt = * )
302 WRITE( nout, fmt = 9999 )
303 $
'An explanation of the input/output '//
304 $
'parameters follows:'
305 WRITE( nout, fmt = 9999 )
306 $
'TIME : Indicates whether WALL or '//
307 $
'CPU time was used.'
309 WRITE( nout, fmt = 9999 )
310 $
'N : The number of rows and columns '//
312 WRITE( nout, fmt = 9999 )
313 $
'NB : The size of the square blocks'//
314 $
' the matrix A is split into.'
315 WRITE( nout, fmt = 9999 )
316 $
'P : The number of process rows.'
317 WRITE( nout, fmt = 9999 )
318 $
'Q : The number of process columns.'
319 WRITE( nout, fmt = 9999 )
320 $
'THRESH : If a residual value is less '//
321 $
'than THRESH, CHECK is flagged as PASSED.'
322 WRITE( nout, fmt = 9999 )
323 $
'Fct time : Time in seconds to factor the'//
324 $
' matrix, if needed.'
325 WRITE( nout, fmt = 9999 )
326 $
'Inv Time : Time in seconds to inverse the'//
328 WRITE( nout, fmt = 9999 )
329 $
'MFLOPS : Rate of execution for factor '//
331 WRITE( nout, fmt = * )
332 WRITE( nout, fmt = 9999 )
333 $
'The following parameter values will be used:'
334 WRITE( nout, fmt = 9996 )
335 $
'N ', ( nval( i ), i = 1,
min( nmat, 10 ) )
337 $
WRITE( nout, fmt = 9997 ) ( nval( i ), i = 11, nmat )
338 WRITE( nout, fmt = 9996 )
339 $
'NB ', ( nbval( i ), i = 1,
min( nnb, 10 ) )
341 $
WRITE( nout, fmt = 9997 ) ( nbval( i ), i = 11, nnb )
342 WRITE( nout, fmt = 9996 )
343 $
'P ', ( pval( i ), i = 1,
min( ngrids, 10 ) )
345 $
WRITE( nout, fmt = 9997) ( pval( i ), i = 11, ngrids )
346 WRITE( nout, fmt = 9996 )
347 $
'Q ', ( qval( i ), i = 1,
min( ngrids, 10 ) )
349 $
WRITE( nout, fmt = 9997 ) ( qval( i ), i = 11, ngrids )
350 WRITE( nout, fmt = 9995 ) eps
351 WRITE( nout, fmt = 9998 ) thresh
358 $
CALL blacs_setup( iam, nprocs )
363 CALL blacs_get( -1, 0, ictxt )
364 CALL blacs_gridinit( ictxt,
'Row-major', 1, nprocs )
368 eps = pslamch( ictxt,
'eps' )
370 CALL sgebr2d( ictxt,
'All',
' ', 1, 1, thresh, 1, 0, 0 )
371 CALL igebr2d( ictxt,
'All',
' ', 4, 1, work, 4, 0, 0 )
377 i = nmtyp+nmat+nnb+2*ngrids
378 CALL igebr2d( ictxt,
'All',
' ', i, 1, work, i, 0, 0 )
381 IF( work( k ).EQ.1 )
THEN
383 ELSE IF( work( k ).EQ.2 )
THEN
385 ELSE IF( work( k ).EQ.3 )
THEN
387 ELSE IF( work( k ).EQ.4 )
THEN
389 ELSE IF( work( k ).EQ.5 )
THEN
395 CALL icopy( nmat, work( i ), 1, nval, 1 )
397 CALL icopy( nnb, work( i ), 1, nbval, 1 )
399 CALL icopy( ngrids, work( i ), 1, pval, 1 )
401 CALL icopy( ngrids, work( i ), 1, qval, 1 )
405 CALL blacs_gridexit( ictxt )
409 40
WRITE( nout, fmt = 9993 )
411 IF( nout.NE.6 .AND. nout.NE.0 )
413 CALL blacs_abort( ictxt, 1 )
418 9998
FORMAT(
'Routines pass computational tests if scaled residual ',
419 $
'is less than ', g12.5 )
420 9997
FORMAT(
' ', 10i6 )
421 9996
FORMAT( 2x, a5,
' : ', 10i6 )
422 9995
FORMAT(
'Relative machine precision (eps) is taken to be ',
424 9994
FORMAT(
' Number of values of ',5a,
' is less than 1 or greater ',
426 9993
FORMAT(
' Illegal input in file ',40a,
'. Aborting run.' )