1 SUBROUTINE pctrdinfo( SUMMRY, NOUT, UPLO, NMAT, NVAL, LDNVAL, NNB,
2 $ NBVAL, LDNBVAL, NGRIDS, PVAL, LDPVAL, QVAL,
3 $ LDQVAL, THRESH, WORK, IAM, NPROCS )
12 INTEGER IAM, LDNBVAL, LDNVAL, LDPVAL, ,
13 $ ngrids, nmat, nnb, nprocs, nout
17 CHARACTER*( * ) SUMMRY*(*)
18 INTEGER NBVAL( LDNBVAL ), NVAL( LDNVAL ),
19 $ pval( ldpval ), qval( ldqval ), work( * )
109 INTEGER BLOCK_CYCLIC_2D, CSRC_, CTXT_, DLEN_, DTYPE_,
110 $ LLD_, MB_, M_, NB_, N_, RSRC_
111 parameter( block_cyclic_2d = 1, dlen_ = 9, dtype_ = 1,
112 $ ctxt_ = 2, m_ = 3, n_ = 4, mb_ = 5, nb_ = 6,
113 $ rsrc_ = 7, csrc_ = 8, lld_ = 9 )
115 PARAMETER ( NIN = 11 )
130 EXTERNAL pslamch, lsame
144 OPEN( nin, file=
'TRD.dat', status=
'OLD' )
145 READ( nin, fmt = * ) summry
150 READ( nin, fmt = 9999 ) usrinfo
154 READ( nin, fmt = * ) summry
155 READ( nin, fmt = * ) nout
156 IF( nout.NE.0 .AND. nout.NE.6 )
157 $
OPEN( nout, file = summry, status =
'UNKNOWN' )
163 READ( nin, fmt = * ) uplo
167 READ( nin, fmt = * ) nmat
168 IF( nmat.LT.1 .OR. nmat.GT.ldnval )
THEN
169 WRITE( nout, fmt = 9994 )
'N', ldnval
172 READ( nin, fmt = * ) ( nval( i ), i = 1, nmat )
176 READ( nin, fmt = * ) nnb
177 IF( nnb.LT.1 .OR. nnb.GT.ldnbval )
THEN
178 WRITE( nout, fmt = 9994 )
'NB', ldnbval
181 READ( nin, fmt = * ) ( nbval( i ), i = 1, nnb )
185 READ( nin, fmt = * ) ngrids
186 IF( ngrids.LT.1 .OR. ngrids.GT.ldpval )
THEN
187 WRITE( nout, fmt = 9994 )
'Grids', ldpval
189 ELSE IF( ngrids.GT.ldqval )
THEN
190 WRITE( nout, fmt = 9994 )
'Grids', ldqval
196 READ( nin, fmt = * ) ( pval( i ), i = 1, ngrids )
197 READ( nin, fmt = * ) ( qval( i ), i = 1, ngrids )
201 READ( nin, fmt = * ) thresh
210 IF( nprocs.LT.1 )
THEN
213 nprocs =
max( nprocs, pval( i )*qval( i ) )
215 CALL blacs_setup( iam, nprocs )
221 CALL blacs_get( -1, 0, ictxt )
226 eps = pslamch( ictxt,
'eps' )
230 CALL sgebs2d( ictxt,
'All',
' ', 1, 1, thresh, 1 )
235 IF( lsame( uplo,
'L' ) )
THEN
240 CALL igebs2d( ictxt,
'All',
' ', 4, 1, work, 4 )
243 CALL icopy( nmat, nval, 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
', ' ', I, 1, WORK, I )
255 WRITE( NOUT, FMT = 9999 )
256 $ 'scalapack reduction routine to hermitian
'//
257 $ 'tridiagonal form.
'
258 WRITE( NOUT, FMT = 9999 ) USRINFO
259 WRITE( NOUT, FMT = * )
260 WRITE( NOUT, FMT = 9999 )
261 $ 'tests of
the parallel
'//
262 $ 'complex single precision Hermitian
'//
264 WRITE( NOUT, FMT = 9999 ) 'reduction routines.
'
265 WRITE( NOUT, FMT = 9999 )
266 $ 'The scaled residual
'//
267 $ 'checks will be computed:
'
268 WRITE( NOUT, FMT = 9999 )
269 $ ' ||A - QTQ
''|| / (||A|| * eps * N)
'
270 WRITE( NOUT, FMT = 9999 )
271 $ 'The matrix A is randomly
'//
272 $ 'generated for each test.
'
273 WRITE( NOUT, FMT = * )
274 WRITE( NOUT, FMT = 9999 )
275 $ 'An explanation of the input/output
'//
276 $ 'parameters follows:
'
277 WRITE( NOUT, FMT = 9999 )
278 $ ' : the
''Upper
'' or
''Low
'//
279 $ 'er
'' part of A is to be referenced.
'
280 WRITE( NOUT, FMT = 9999 )
281 $ 'TIME : Indicates whether WALL or
'//
283 WRITE( NOUT, FMT = 9999 )
284 $ 'N : The number of rows and columns
'//
286 WRITE( NOUT, FMT = 9999 )
287 $ 'NB : The size of the square blocks
'//
288 $ ' the matrix A is split into.
'
289 WRITE( NOUT, FMT = 9999 )
290 $ 'P : The number of rows.
'
291 WRITE( NOUT, FMT = 9999 )
292 $ 'Q : The number of process columns.
'
293 WRITE( NOUT, FMT = 9999 )
294 $ 'THRESH : a residual
value is less
'//
295 $ 'than THRESH, CHECK is flagged as PASSED.
'
296 WRITE( NOUT, FMT = 9999 )
297 $ 'TRD time : Time in seconds to reduce the
'//
298 $ ' matrix to tridiagonal form.
'
299 WRITE( NOUT, FMT = 9999 )
300 $ 'MFLOPS : Rate of execution for
'//
301 $ 'Hermitian tridiagonal reduction.
'
302 WRITE( NOUT, FMT = * )
303 WRITE( NOUT, FMT = 9999 )
304 $ 'The following
parameter values will be used:'
305 WRITE( nout, fmt = 9999 )
307 WRITE( nout, fmt = 9996 )
308 $
'N ', ( nval( i ), i = 1,
min( nmat, 10 ) )
310 $
WRITE( nout, fmt = 9997 ) ( nval( i ), i = 11, nmat )
311 WRITE( nout, fmt = 9996 )
312 $
'NB ', ( nbval( i ), i = 1,
min( nnb, 10 ) )
314 $
WRITE( nout, fmt = 9997 ) ( nbval( i ), i = 11, nnb )
315 WRITE( nout, fmt = 9996 )
316 $
'P ', ( pval( i ), i = 1,
min( ngrids, 10 ) )
318 $
WRITE( nout, fmt = 9997 ) ( pval( i ), i = 11, ngrids )
319 WRITE( nout, fmt = 9996 )
320 $
'Q ', ( qval( i ), i = 1,
min( ngrids, 10 ) )
322 $
WRITE( nout, fmt = 9997 ) ( qval( i ), i = 11, ngrids )
323 WRITE( nout, fmt = * )
324 WRITE( nout, fmt = 9995 ) eps
325 WRITE( nout, fmt = 9998 ) thresh
332 $
CALL blacs_setup( iam, nprocs )
337 CALL blacs_get( -1, 0, ictxt )
342 EPS = PSLAMCH( ICTXT, 'eps
' )
344 CALL SGEBR2D( ICTXT, 'all
', ' ', 1, 1, THRESH, 1, 0, 0 )
345 CALL IGEBR2D( ICTXT, 'all
', ' ', 4, 1, WORK, 4, 0, 0 )
349.EQ.
IF( WORK( 4 )1 ) THEN
355 I = NMAT + NNB + 2*NGRIDS
356 CALL IGEBR2D( ICTXT, 'all
', ' ', I, 1, WORK, I, 0, 0 )
358 CALL ICOPY( NMAT, WORK( I ), 1, NVAL, 1 )
360 CALL ICOPY( NNB, WORK( I ), 1, NBVAL, 1 )
362 CALL ICOPY( NGRIDS, WORK( I ), 1, PVAL, 1 )
364 CALL ICOPY( NGRIDS, WORK( I ), 1, QVAL, 1 )
368 CALL BLACS_GRIDEXIT( ICTXT )
372 20 WRITE( NOUT, FMT = 9993 )
374.NE..AND..NE.
IF( NOUT6 NOUT0 )
376 CALL BLACS_ABORT( ICTXT, 1 )
381 9998 FORMAT( 'routines pass computational tests
if scaled residual
',
382 $ 'is less than
', G12.5 )
383 9997 FORMAT( ' ', 10I6 )
384 9996 FORMAT( 2X, A5, ' :
', 10I6 )
385 9995 FORMAT( 'relative machine precision(eps) is taken to be
',
387 9994 FORMAT( ' number of values of
',5A, ' is less than 1 or greater
',
389 9993 FORMAT( ' illegal input in file
',40A,'. aborting run.
' )