1 SUBROUTINE psbrdinfo( SUMMRY, NOUT, NMAT, MVAL, LDMVAL, NVAL,
2 $ LDNVAL, NNB, NBVAL, LDNBVAL, NGRIDS, PVAL,
3 $ LDPVAL, QVAL, LDQVAL, THRESH, WORK, IAM,
12 CHARACTER*( * ) SUMMRY
13 INTEGER IAM, LDMVAL, LDNBVAL, LDNVAL, LDPVAL,
14 $ LDQVAL, NGRIDS, NMAT, NNB, NPROCS, NOUT
18 INTEGER MVAL( LDMVAL ), NBVAL( LDNBVAL ),
19 $ NVAL( LDNVAL ), PVAL( LDPVAL ),
20 $ QVAL( LDQVAL ), WORK( * )
112 INTEGER BLOCK_CYCLIC_2D, CSRC_, CTXT_, DLEN_, DTYPE_,
113 $ LLD_, MB_, M_, NB_, N_, RSRC_
114 PARAMETER ( BLOCK_CYCLIC_2D = 1, dlen_ = 9, dtype_ = 1,
115 $ ctxt_ = 2, m_ = 3, n_ = 4, mb_ = 5, nb_ = 6,
116 $ rsrc_ = 7, csrc_ = 8, lld_ = 9 )
118 PARAMETER ( NIN = 11 )
126 EXTERNAL blacs_abort, blacs_get, blacs_gridexit,
127 $ blacs_gridinit, blacs_setup, igebr2d, igebs2d,
146 OPEN( unit = nin, file =
'BRD.dat', status =
'OLD' )
147 READ( nin, fmt = * ) summry
152 READ( nin, fmt = 9999 ) usrinfo
156 READ( nin, fmt = * ) summry
157 READ( nin, fmt = * ) nout
158 IF( nout.NE.0 .AND. nout.NE.6 )
159 $
OPEN( unit = nout, file = summry, status =
'UNKNOWN' )
165 READ( nin, fmt = * ) nmat
166 IF( nmat.LT.1. .OR. nmat.GT.ldmval )
THEN
167 WRITE( nout, fmt = 9997 )
'M', ldmval
170 READ( nin, fmt = * ) ( mval( i ), i = 1, nmat )
171 READ( nin, fmt = * ) ( nval( i ), i = 1, nmat )
175 READ( nin, fmt = * ) nnb
176 IF( nnb.LT.1 .OR. nnb.GT.ldnbval )
THEN
177 WRITE( nout, fmt = 9997 )
'NB', ldnbval
180 READ( nin, fmt = * ) ( nbval( i ), i = 1, nnb )
184 READ( nin, fmt = * ) ngrids
185 IF( ngrids.LT.1 .OR. ngrids.GT.ldpval )
THEN
186 WRITE( nout, fmt = 9997 )
'Grids', ldpval
188 ELSE IF( ngrids.GT.ldqval )
THEN
189 WRITE( nout, fmt = 9997 )
'Grids', ldqval
195 READ( nin, fmt = * ) ( pval( i ), i = 1, ngrids )
196 READ( nin, fmt = * ) ( qval( i ), i = 1, ngrids )
200 READ( nin, fmt = * ) thresh
209 IF( nprocs.LT.1 )
THEN
212 nprocs =
max( nprocs, pval( i )*qval( i ) )
214 CALL blacs_setup( iam, nprocs )
220 CALL blacs_get( -1, 0, ictxt )
221 CALL blacs_gridinit( ictxt,
'Row-major', 1, nprocs )
225 eps = pslamch( ictxt,
'eps' )
229 CALL sgebs2d( ictxt,
'All',
' ', 1, 1, thresh, 1 )
234 CALL igebs2d( ictxt,
'All',
' ', 1, 3, work, 1 )
237 CALL icopy( nmat, mval, 1, work( i ), 1 )
239 CALL icopy( nmat, nval, 1, work( i ), 1 )
241 CALL icopy( nnb, nbval, 1, work( i ), 1 )
243 CALL icopy( ngrids, pval, 1, work( i ), 1 )
245 CALL icopy( ngrids, qval, 1, work( i ), 1 )
247 CALL igebs2d( ictxt,
'All',
' ', i, 1, work, i )
251 WRITE( nout, fmt = 9999 )
252 $
'SCALAPACK Bidiagonal reduction'
253 WRITE( nout, fmt = 9999 ) usrinfo
254 WRITE( nout, fmt = * )
255 WRITE( nout, fmt = 9999 )
256 $
'Tests of the parallel '//
257 $
'real single precision bidiagonal '
258 WRITE( nout, fmt = 9999 )
'reduction routines.'
259 WRITE( nout, fmt = 9999 )
260 $
'The following scaled residual '//
261 $
'checks will be computed:'
262 WRITE( nout, fmt = 9999 )
263 $
' ||A - Q B P''|| / (||A|| * eps * N)'
264 WRITE( nout, fmt = 9999 )
265 $
'The matrix A is randomly '//
266 $
'generated for each test.'
267 WRITE( nout, fmt = * )
268 WRITE( nout, fmt = 9999 )
269 $
'An explanation of the input/output '//
270 $
'parameters follows:'
271 WRITE( nout, fmt = 9999 )
272 $
'TIME : Indicates whether WALL or '//
273 $
'CPU time was used.'
274 WRITE( nout, fmt = 9999 )
275 $
'M : The number of rows '//
277 WRITE( nout, fmt = 9999 )
278 $
'N : The number of columns '//
280 WRITE( nout, fmt = 9999 )
281 $
'NB : The size of the square blocks'//
282 $
' the matrix A is split into.'
283 WRITE( nout, fmt = 9999 )
284 $
'P : The number of process rows.'
285 WRITE( nout, fmt = 9999 )
286 $
'Q : The number of process columns.'
287 WRITE( nout, fmt = 9999 )
288 $
'THRESH : If a residual value is less'//
289 $
' than THRESH, CHECK is flagged as PASSED'
290 WRITE( nout, fmt = 9999 )
291 $
'BRD time : Time in seconds to reduce the'//
293 WRITE( nout, fmt = 9999 )
294 $
'MFLOPS : Rate of execution for '//
295 $
'the bidiagonal reduction.'
296 WRITE( nout, fmt = * )
297 WRITE( nout, fmt = 9999 )
298 $
'The following parameter values will be used:'
299 WRITE( nout, fmt = 9995 )
300 $
'M ', ( mval( i ), i = 1,
min( nmat, 10 ) )
302 $
WRITE( nout, fmt = 9994 ) ( mval( i ), i = 11, nmat )
303 WRITE( nout, fmt = 9995 )
304 $
'N ', ( nval( i ), i = 1,
min( nmat, 10 ) )
306 $
WRITE( nout, fmt = 9994 ) ( nval( i ), i = 11, nmat )
307 WRITE( nout, fmt = 9995 )
308 $
'NB ', ( nbval( i ), i = 1,
min( nnb, 10 ) )
310 $
WRITE( nout, fmt = 9994 )( nbval( i ), i = 11, nnb )
311 WRITE( nout, fmt = 9995 )
312 $
'P ', ( pval( i ), i = 1,
min( ngrids, 10 ) )
314 $
WRITE( nout, fmt = 9994 )( pval( i ), i = 11, ngrids )
315 WRITE( nout, fmt = 9995 )
316 $
'Q ', ( qval( i ), i = 1,
min( ngrids, 10 ) )
318 $
WRITE( nout, fmt = 9994 )( qval( i ), i = 11, ngrids )
319 WRITE( nout, fmt = 9999 )
' '
320 WRITE( nout, fmt = 9996 ) eps
321 WRITE( nout, fmt = 9993 ) thresh
328 $
CALL blacs_setup( iam, nprocs )
333 CALL blacs_get( -1, 0, ictxt )
334 CALL blacs_gridinit( ictxt,
'Row-major', 1, nprocs )
338 eps = pslamch( ictxt,
'eps' )
340 CALL sgebr2d( ictxt,
'All',
' ', 1, 1, thresh, 1, 0, 0 )
341 CALL igebr2d( ictxt,
'All',
' ', 1, 3, work, 1, 0, 0 )
346 i = 2*nmat + nnb + 2*ngrids
347 CALL igebr2d( ictxt,
'All',
' ', i, 1, work, i, 0, 0 )
349 CALL icopy( nmat, work( i ), 1, mval, 1 )
351 CALL icopy( nmat, work( i ), 1, nval, 1 )
353 CALL icopy( nnb, work( i ), 1, nbval, 1 )
355 CALL icopy( ngrids, work( i ), 1, pval, 1 )
357 CALL icopy( ngrids, work( i ), 1, qval, 1 )
361 CALL blacs_gridexit( ictxt )
366 WRITE( nout, fmt = 9998 )
368 IF( nout.NE.6 .AND. nout.NE.0 )
370 CALL blacs_abort( ictxt, 1 )
375 9998
FORMAT(
' Illegal input in file ', 40a,
'. Aborting run.' )
376 9997
FORMAT(
' Number of values of ', 5a,
377 $
' is less than 1 or greater ',
'than ', i2 )
378 9996
FORMAT(
'Relative machine precision (eps) is taken to be ',
380 9995
FORMAT( 2x, a5,
': ', 10i6 )
381 9994
FORMAT(
' ', 10i6 )
382 9993
FORMAT(
'Routines pass computational tests if scaled residual is',
383 $
' less than ', g12.5 )