1 SUBROUTINE pshrdinfo( SUMMRY, NOUT, NMAT, NVAL, NVLO, NVHI,
2 $ LDNVAL, NNB, NBVAL, LDNBVAL, NGRIDS, PVAL,
3 $ LDPVAL, QVAL, LDQVAL, THRESH, WORK, IAM,
12 INTEGER IAM, LDNBVAL, LDNVAL, LDPVAL, LDQVAL,
13 $ NGRIDS, NMAT, NNB, NOUT, NPROCS
17 CHARACTER*( * ) SUMMRY
18 INTEGER NBVAL( LDNBVAL ), NVAL( LDNVAL ),
19 $ NVHI( LDNVAL ), NVLO( LDNVAL ),
20 $ pval( ldpval ), qval( ldqval ), work( * )
110 INTEGER BLOCK_CYCLIC_2D, CSRC_, CTXT_, DLEN_, DTYPE_,
111 $ LLD_, MB_, M_, NB_, N_, RSRC_
112 PARAMETER ( BLOCK_CYCLIC_2D = 1, dlen_ = 9, dtype_ = 1,
113 $ ctxt_ = 2, m_ = 3, n_ = 4, mb_ = 5, nb_ = 6,
114 $ rsrc_ = 7, csrc_ = 8, lld_ = 9 )
116 PARAMETER ( NIN = 11 )
124 EXTERNAL blacs_abort, blacs_get, blacs_gridexit,
125 $ blacs_gridinit, blacs_setup,
icopy, igebr2d,
126 $ igebs2d, sgebr2d, sgebs2d
144 OPEN( unit = nin, file =
'HRD.dat', status =
'OLD' )
145 READ( nin, fmt = * )summry
150 READ( nin, fmt = * ) usrinfo
154 READ( nin, fmt = * ) summry
155 READ( nin, fmt = * ) nout
156 IF( nout.NE.0 .AND. nout.NE.6 )
157 $
OPEN( unit = nout, file = summry, status =
'UNKNOWN' )
163 READ( nin, fmt = * ) nmat
164 IF( nmat.LT.1. .OR. nmat.GT.ldnval )
THEN
165 WRITE( nout, fmt = 9997 )
'N', ldnval
171 READ( nin, fmt = * ) ( nval( i ), i = 1, nmat )
172 READ( nin, fmt = * ) ( nvlo( i ), i = 1, nmat )
173 READ( nin, fmt = * ) ( nvhi( i ), i = 1, nmat )
177 READ( nin, fmt = * ) nnb
178 IF( nnb.LT.1 .OR. nnb.GT.ldnbval )
THEN
179 WRITE( nout, fmt = 9997 )
'NB', ldnbval
182 READ( nin, fmt = * ) ( nbval( i ), i = 1, nnb )
186 READ( nin, fmt = * ) ngrids
187 IF( ngrids.LT.1 .OR. ngrids.GT.ldpval )
THEN
188 WRITE( nout, fmt = 9997 )
'Grids', ldpval
190 ELSE IF( ngrids.GT.ldqval )
THEN
191 WRITE( nout, fmt = 9997 )
'Grids', ldqval
197 READ( nin, fmt = * ) ( pval( i ), i = 1, ngrids )
198 READ( nin, fmt = * ) ( qval( i ), i = 1, ngrids )
202 READ( nin, fmt = * ) thresh
211 IF( nprocs.LT.1 )
THEN
214 nprocs =
max( nprocs, pval( i )*qval( i ) )
216 CALL blacs_setup( iam, nprocs )
222 CALL blacs_get( -1, 0, ictxt )
223 CALL blacs_gridinit( ictxt,
'Row-major', 1, nprocs )
227 eps = pslamch( ictxt,
'eps' )
231 CALL sgebs2d( ictxt,
'All',
' ', 1, 1, thresh, 1 )
236 CALL igebs2d( ictxt,
'All',
' ', 1, 3, work, 1 )
239 CALL icopy( nmat, nval, 1, work( i ), 1 )
241 CALL icopy( nmat, nvlo, 1, work( i ), 1 )
243 CALL icopy( nmat, nvhi, 1, work( i ), 1 )
245 CALL icopy( nnb, nbval, 1, work( i ), 1 )
247 CALL icopy( ngrids, pval, 1, work( i ), 1 )
249 CALL icopy( ngrids, qval, 1, work( i ), 1 )
251 CALL igebs2d( ictxt,
'All',
' ', 1, i, work, 1 )
255 WRITE( nout, fmt = 9999 )
256 $
'ScaLAPACK Reduction routine to Hessenberg form.'
257 WRITE( nout, fmt = 9999 ) usrinfo
258 WRITE( nout, fmt = * )
259 WRITE( nout, fmt = 9999 )
260 $
'Tests of the parallel '//
261 $
'real single precision Hessenberg '
262 WRITE( nout, fmt = 9999 )
'reduction routines.'
263 WRITE( nout, fmt = 9999 )
264 $
'The following scaled residual '//
265 $
'checks will be computed:'
266 WRITE( nout, fmt = 9999 )
267 $
' ||A - Q H Q''|| / (||A|| * eps * N)'
268 WRITE( nout, fmt = 9999 )
269 $
'The matrix A is randomly '//
270 $
'generated for each test.'
271 WRITE( nout, fmt = * )
272 WRITE( nout, fmt = 9999 )
273 $
'An explanation of the input/output '//
274 $
'parameters follows:'
275 WRITE( nout, fmt = 9999 )
276 $
'TIME : Indicates whether WALL or '//
277 $
'CPU time was used.'
278 WRITE( nout, fmt = 9999 )
279 $
'N : The number of rows and columns '//
281 WRITE( nout, fmt = 9999 )
282 $
'NB : The size of the square blocks'//
283 $
' the matrix A is split into.'
284 WRITE( nout, fmt = 9999 )
285 $
' on to the next column of processes.'
286 WRITE( nout, fmt = 9999 )
287 $
'P : The number of process rows.'
288 WRITE( nout, fmt = 9999 )
289 $
'Q : The number of process columns.'
290 WRITE( nout, fmt = 9999 )
291 $
'HRD time : Time in seconds to compute HRD '
292 WRITE( nout, fmt = 9999 )
293 $
'MFLOPS : Rate of execution for HRD ' //
295 WRITE( nout, fmt = * )
296 WRITE( nout, fmt = 9999 )
297 $
'The following parameter values will be used:'
298 WRITE( nout, fmt = 9995 )
299 $
'N ', ( nval( i ), i = 1,
min( nmat, 10 ) )
301 $
WRITE( nout, fmt = 9994 ) ( nval( i ), i = 11, nmat )
302 WRITE( nout, fmt = 9995 )
303 $
'ILO ', ( nvlo( i ), i = 1,
min( nmat, 10 ) )
305 $
WRITE( nout, fmt = 9994 ) ( nvlo( i ), i = 11, nmat )
306 WRITE( nout, fmt = 9995 )
307 $
'IHI ', ( nvhi( i ), i = 1,
min( nmat, 10 ) )
309 $
WRITE( nout, fmt = 9994 ) ( nvhi( i ), i = 11, nmat )
310 WRITE( nout, fmt = 9995 )
311 $
'NB ', ( nbval( i ), i = 1,
min( nnb, 10 ) )
313 $
WRITE( nout, fmt = 9994 ) ( nbval( i ), i = 11, nnb )
314 WRITE( nout, fmt = 9995 )
315 $
'P ', ( pval( i ), i = 1,
min( ngrids, 10 ) )
317 $
WRITE( nout, fmt = 9994 ) ( pval( i ), i = 11, ngrids )
318 WRITE( nout, fmt = 9995 )
319 $
'Q ', ( qval( i ), i = 1,
min( ngrids, 10 ) )
321 $
WRITE( nout, fmt = 9994 ) ( qval( i ), i = 11, ngrids )
322 WRITE( nout, fmt = * )
323 WRITE( nout, fmt = 9996 ) eps
324 WRITE( nout, fmt = 9993 ) thresh
331 $
CALL blacs_setup( iam, nprocs )
336 CALL blacs_get( -1, 0, ictxt )
337 CALL blacs_gridinit( ictxt,
'Row-major', 1, nprocs )
341 eps = pslamch( ictxt,
'eps' )
343 CALL sgebr2d( ictxt,
'All',
' ', 1, 1, thresh, 1, 0, 0 )
344 CALL igebr2d( ictxt,
'All',
' ', 1, 3, work, 1, 0, 0 )
349 i = 3*nmat + nnb + 2*ngrids
350 CALL igebr2d( ictxt,
'All',
' ', 1, i, work, 1, 0, 0 )
353 CALL icopy( nmat, work( i ), 1, nval, 1 )
355 CALL icopy( nmat, work( i ), 1, nvlo, 1 )
357 CALL icopy( nmat, work( i ), 1, nvhi, 1 )
359 CALL icopy( nnb, work( i ), 1, nbval, 1 )
361 CALL icopy( ngrids, work( i ), 1, pval, 1 )
363 CALL icopy( ngrids, work( i ), 1, qval, 1 )
367 CALL blacs_gridexit( ictxt )
372 WRITE( nout, fmt = 9998 )
374 IF( nout.NE.6 .AND. nout.NE.0 )
376 CALL blacs_abort( ictxt, 1 )
381 9998
FORMAT(
' ILLEGAL INPUT IN FILE ', 40a,
'. ABORTING RUN.' )
382 9997
FORMAT(
' NUMBER OF VALUES OF ', 5a,
383 $
' IS LESS THAN 1 OR GREATER ',
'THAN ', i2 )
384 9996
FORMAT(
'Relative machine precision (eps) is taken to be ',
386 9995
FORMAT( 2x, a5,
': ', 10i6 )
387 9994
FORMAT(
' ', 10i6 )
388 9993
FORMAT(
'Routines pass computational tests if scaled residual is',
389 $
' less than ', g14.7 )