OpenRadioss 2025.1.11
OpenRadioss project
Loading...
Searching...
No Matches
pdtrddriver.f
Go to the documentation of this file.
1 PROGRAM pdtrddriver
2*
3* -- ScaLAPACK testing driver (version 1.7) --
4* University of Tennessee, Knoxville, Oak Ridge National Laboratory,
5* and University of California, Berkeley.
6* October 15, 1999
7*
8* Purpose
9* ========
10*
11* PDTRDDRIVER is the main test program for the DOUBLE PRECISION
12* SCALAPACK TRD (symmetric tridiagonal reduction) routines.
13*
14* The program must be driven by a short data file. An annotated
15* example of a data file can be obtained by deleting the first 3
16* characters from the following 13 lines:
17* 'ScaLAPACK TRD computation input file'
18* 'PVM machine'
19* 'TRD.out' output file name
20* 6 device out
21* 'L' define Lower or Upper
22* 3 number of problems sizes
23* 5 31 201 values of N
24* 3 number of NB's
25* 2 3 5 values of NB
26* 7 number of process grids (ordered pairs of P & Q)
27* 1 2 1 4 2 3 8 values of P
28* 1 2 4 1 3 2 1 values of Q
29* 1.0 threshold
30*
31* Internal Parameters
32* ===================
33*
34* TOTMEM INTEGER, default = 2000000
35* TOTMEM is a machine-specific parameter indicating the
36* maximum amount of available memory in bytes.
37* The user should customize TOTMEM to his platform. Remember
38* to leave room in memory for the operating system, the BLACS
39* buffer, etc. For example, on a system with 8 MB of memory
40* per process (e.g., one processor on an Intel iPSC/860), the
41* parameters we use are TOTMEM=6200000 (leaving 1.8 MB for OS,
42* code, BLACS buffer, etc). However, for PVM, we usually set
43* TOTMEM = 2000000. Some experimenting with the maximum value
44* of TOTMEM may be required.
45*
46* INTGSZ INTEGER, default = 4 bytes.
47* DBLESZ INTEGER, default = 8 bytes.
48* INTGSZ and DBLESZ indicate the length in bytes on the
49* given platform for an integer and a double precision real.
50* MEM DOUBLE PRECISION array, dimension ( TOTMEM / DBLESZ )
51*
52* All arrays used by SCALAPACK routines are allocated from
53* this array and referenced by pointers. The integer IPA,
54* for example, is a pointer to the starting element of MEM for
55* the matrix A.
56*
57* =====================================================================
58*
59* .. Parameters ..
60 INTEGER block_cyclic_2d, csrc_, ctxt_, dlen_, dtype_,
61 $ lld_, mb_, m_, nb_, n_, rsrc_
62 parameter( block_cyclic_2d = 1, dlen_ = 9, dtype_ = 1,
63 $ ctxt_ = 2, m_ = 3, n_ = 4, mb_ = 5, nb_ = 6,
64 $ rsrc_ = 7, csrc_ = 8, lld_ = 9 )
65 INTEGER dblesz, totmem, memsiz, ntests
66 DOUBLE PRECISION padval
67 parameter( dblesz = 8, totmem = 2000000,
68 $ memsiz = totmem / dblesz, ntests = 20,
69 $ padval = -9923.0d+0 )
70* ..
71* .. Local Scalars ..
72 LOGICAL check
73 CHARACTER uplo
74 CHARACTER*6 passed
75 CHARACTER*80 OUTFILE
76 INTEGER i, iam, iaseed, ictxt, imidpad, info, ipa, ipd,
77 $ IPE, ipostpad, iprepad, ipt, IPW, itemp, j, k,
78 $ kfail, kpass, kskip, ktests, lcm, lwork, mycol,
79 $ myrow, n, nb, ndiag, ngrids, nmat, nnb, noffd,
80 $ nout, np, npcol, nprocs, nprow, nq, worksiz,
81 $ worktrd
82 REAL thresh
83 DOUBLE PRECISION anorm, fresid, nops, tmflops
84* ..
85* .. Local Arrays ..
86 INTEGER desca( dlen_ ), ierr( 1 ), nbval( ntests ),
87 $ nval( ntests ), pval( ntests ), qval( ntests )
88 DOUBLE PRECISION ctime( 1 ), mem( memsiz ), wtime( 1 )
89* ..
90* .. External Subroutines ..
91 EXTERNAL blacs_barrier, blacs_exit, blacs_get,
93 $ blacs_pinfo, descinit, igsum2d, pdchekpad,
97* ..
98* .. External Functions ..
99 LOGICAL lsame
100 INTEGER iceil, ilcm, numroc
101 DOUBLE PRECISION pdlansy
102 EXTERNAL lsame, iceil, ilcm, numroc, pdlansy
103* ..
104* .. Intrinsic Functions ..
105 INTRINSIC dble, max
106* ..
107* .. Data statements ..
108 DATA ktests, kpass, kfail, kskip / 4*0 /
109* ..
110* .. Executable Statements ..
111*
112 IF( block_cyclic_2d*csrc_*ctxt_*dlen_*dtype_*lld_*mb_*m_*nb_*n_*
113 $ rsrc_.LT.0 )stop
114* Get starting information
115*
116 CALL blacs_pinfo( iam, nprocs )
117 iaseed = 100
118 CALL pdtrdinfo( outfile, nout, uplo, nmat, nval, ntests, nnb,
119 $ nbval, ntests, ngrids, pval, ntests, qval, ntests,
120 $ thresh, mem, iam, nprocs )
121 check = ( thresh.GE.0.0e+0 )
122*
123* Print headings
124*
125 IF( iam.EQ.0 ) THEN
126 WRITE( nout, fmt = * )
127 WRITE( nout, fmt = 9995 )
128 WRITE( nout, fmt = 9994 )
129 WRITE( nout, fmt = * )
130 END IF
131*
132* Loop over different process grids
133*
134 DO 30 i = 1, ngrids
135*
136 nprow = pval( i )
137 npcol = qval( i )
138*
139* Make sure grid information is correct
140*
141 ierr( 1 ) = 0
142 IF( nprow.LT.1 ) THEN
143 IF( iam.EQ.0 )
144 $ WRITE( nout, fmt = 9999 )'GRID', 'nprow', nprow
145 ierr( 1 ) = 1
146 ELSE IF( npcol.LT.1 ) THEN
147 IF( iam.EQ.0 )
148 $ WRITE( nout, fmt = 9999 )'GRID', 'npcol', npcol
149 ierr( 1 ) = 1
150 ELSE IF( nprow*npcol.GT.nprocs ) THEN
151 IF( iam.EQ.0 )
152 $ WRITE( nout, fmt = 9998 )nprow*npcol, nprocs
153 ierr( 1 ) = 1
154 END IF
155*
156 IF( ierr( 1 ).GT.0 ) THEN
157 IF( iam.EQ.0 )
158 $ WRITE( nout, fmt = 9997 )'grid'
159 kskip = kskip + 1
160 GO TO 30
161 END IF
162*
163* Define process grid
164*
165 CALL blacs_get( -1, 0, ictxt )
166 CALL blacs_gridinit( ictxt, 'Row-major', nprow, npcol )
167 CALL blacs_gridinfo( ictxt, nprow, npcol, myrow, mycol )
168*
169* Go to bottom of loop if this case doesn't use my process
170*
171 IF( myrow.GE.nprow .OR. mycol.GE.npcol )
172 $ GO TO 30
173*
174 DO 20 j = 1, nmat
175*
176 n = nval( j )
177*
178* Make sure matrix information is correct
179*
180 ierr( 1 ) = 0
181 IF( n.LT.1 ) THEN
182 IF( iam.EQ.0 )
183 $ WRITE( nout, fmt = 9999 )'MATRIX', 'N', n
184 ierr( 1 ) = 1
185 END IF
186*
187* Make sure no one had error
188*
189 CALL igsum2d( ictxt, 'All', ' ', 1, 1, ierr, 1, -1, 0 )
190*
191 IF( ierr( 1 ).GT.0 ) THEN
192 IF( iam.EQ.0 )
193 $ WRITE( nout, fmt = 9997 )'matrix'
194 kskip = kskip + 1
195 GO TO 20
196 END IF
197*
198* Loop over different blocking sizes
199*
200 DO 10 k = 1, nnb
201*
202 nb = nbval( k )
203*
204* Make sure nb is legal
205*
206 ierr( 1 ) = 0
207 IF( nb.LT.1 ) THEN
208 ierr( 1 ) = 1
209 IF( iam.EQ.0 )
210 $ WRITE( nout, fmt = 9999 )'NB', 'NB', nb
211 END IF
212*
213* Check all processes for an error
214*
215 CALL igsum2d( ictxt, 'All', ' ', 1, 1, ierr, 1, -1, 0 )
216*
217 IF( ierr( 1 ).GT.0 ) THEN
218 IF( iam.EQ.0 )
219 $ WRITE( nout, fmt = 9997 )'NB'
220 kskip = kskip + 1
221 GO TO 10
222 END IF
223*
224* Padding constants
225*
226 np = numroc( n, nb, myrow, 0, nprow )
227 nq = numroc( n, nb, mycol, 0, npcol )
228 IF( check ) THEN
229 iprepad = max( nb, np )
230 imidpad = nb
231 ipostpad = max( nb, nq )
232 ELSE
233 iprepad = 0
234 imidpad = 0
235 ipostpad = 0
236 END IF
237*
238* Initialize the array descriptor for the matrix A
239*
240 CALL descinit( desca, n, n, nb, nb, 0, 0, ictxt,
241 $ max( 1, np )+imidpad, ierr( 1 ) )
242*
243* Check all processes for an error
244*
245 CALL igsum2d( ictxt, 'All', ' ', 1, 1, IERR, 1, -1, 0 )
246*
247.LT. IF( IERR( 1 )0 ) THEN
248.EQ. IF( IAM0 )
249 $ WRITE( NOUT, FMT = 9997 )'descriptor'
250 KSKIP = KSKIP + 1
251 GO TO 10
252 END IF
253*
254* Assign pointers into MEM for SCALAPACK arrays, A is
255* allocated starting at position MEM( IPREPAD+1 )
256*
257 NDIAG = NQ
258 IF( LSAME( UPLO, 'u' ) ) THEN
259 NOFFD = NQ
260 ELSE
261 NOFFD = NUMROC( N-1, NB, MYCOL, 0, NPCOL )
262 END IF
263*
264 IPA = IPREPAD + 1
265 IPD = IPA + DESCA( LLD_ )*NQ + IPOSTPAD + IPREPAD
266 IPE = IPD + NDIAG + IPOSTPAD + IPREPAD
267 IPT = IPE + NOFFD + IPOSTPAD + IPREPAD
268 IPW = IPT + NQ + IPOSTPAD + IPREPAD
269*
270* Calculate the amount of workspace required for the
271* reduction
272*
273 LWORK = MAX( NB*( NP+1 ), 3*NB )
274 WORKTRD = LWORK + IPOSTPAD
275 WORKSIZ = WORKTRD
276*
277* Figure the amount of workspace required by the check
278*
279 IF( CHECK ) THEN
280 ITEMP = 2*NQ + NP
281.NE. IF( NPROWNPCOL ) THEN
282 LCM = ILCM( NPROW, NPCOL )
283 ITEMP = NB*ICEIL( ICEIL( NP, NB ), LCM / NPROW ) +
284 $ ITEMP
285 END IF
286 ITEMP = MAX( ITEMP, 2*( NB+NP )*NB )
287 WORKSIZ = MAX( LWORK, ITEMP ) + IPOSTPAD
288 END IF
289*
290* Check for adequate memory for problem size
291*
292 IERR( 1 ) = 0
293.GT. IF( IPW+WORKSIZMEMSIZ ) THEN
294.EQ. IF( IAM0 )
295 $ WRITE( NOUT, FMT = 9996 )'tridiagonal reduction',
296 $ ( IPW+WORKSIZ )*DBLESZ
297 IERR( 1 ) = 1
298 END IF
299*
300* Check all processes for an error
301*
302 CALL IGSUM2D( ICTXT, 'all', ' ', 1, 1, IERR, 1, -1, 0 )
303*
304.GT. IF( IERR( 1 )0 ) THEN
305.EQ. IF( IAM0 )
306 $ WRITE( NOUT, FMT = 9997 )'memory'
307 KSKIP = KSKIP + 1
308 GO TO 10
309 END IF
310*
311* Generate the matrix A
312*
313 CALL PDMATGEN( ICTXT, 'symm', 'n', DESCA( M_ ),
314 $ DESCA( N_ ), DESCA( MB_ ), DESCA( NB_ ),
315 $ MEM( IPA ), DESCA( LLD_ ), DESCA( RSRC_ ),
316 $ DESCA( CSRC_ ), IASEED, 0, NP, 0, NQ,
317 $ MYROW, MYCOL, NPROW, NPCOL )
318*
319* Need Infinity-norm of A for checking
320*
321 IF( CHECK ) THEN
322 CALL PDFILLPAD( ICTXT, NP, NQ, MEM( IPA-IPREPAD ),
323 $ DESCA( LLD_ ), IPREPAD, IPOSTPAD,
324 $ PADVAL )
325 CALL PDFILLPAD( ICTXT, NDIAG, 1, MEM( IPD-IPREPAD ),
326 $ NDIAG, IPREPAD, IPOSTPAD, PADVAL )
327 CALL PDFILLPAD( ICTXT, NOFFD, 1, MEM( IPE-IPREPAD ),
328 $ NOFFD, IPREPAD, IPOSTPAD, PADVAL )
329 CALL PDFILLPAD( ICTXT, NQ, 1, MEM( IPT-IPREPAD ), NQ,
330 $ IPREPAD, IPOSTPAD, PADVAL )
331 CALL PDFILLPAD( ICTXT, WORKSIZ-IPOSTPAD, 1,
332 $ MEM( IPW-IPREPAD ), WORKSIZ-IPOSTPAD,
333 $ IPREPAD, IPOSTPAD, PADVAL )
334 ANORM = PDLANSY( 'i', UPLO, N, MEM( IPA ), 1, 1,
335 $ DESCA, MEM( IPW ) )
336 CALL PDCHEKPAD( ICTXT, 'pdlansy', NP, NQ,
337 $ MEM( IPA-IPREPAD ), DESCA( LLD_ ),
338 $ IPREPAD, IPOSTPAD, PADVAL )
339 CALL PDCHEKPAD( ICTXT, 'pdlansy', WORKSIZ-IPOSTPAD, 1,
340 $ MEM( IPW-IPREPAD ), WORKSIZ-IPOSTPAD,
341 $ IPREPAD, IPOSTPAD, PADVAL )
342 CALL PDFILLPAD( ICTXT, WORKTRD-IPOSTPAD, 1,
343 $ MEM( IPW-IPREPAD ), WORKTRD-IPOSTPAD,
344 $ IPREPAD, IPOSTPAD, PADVAL )
345 END IF
346*
347 CALL SLBOOT
348 CALL BLACS_BARRIER( ICTXT, 'all' )
349 CALL SLTIMER( 1 )
350*
351* Reduce to symmetric tridiagonal form
352*
353 CALL PDSYTRD( UPLO, N, MEM( IPA ), 1, 1, DESCA,
354 $ MEM( IPD ), MEM( IPE ), MEM( IPT ),
355 $ MEM( IPW ), LWORK, INFO )
356*
357 CALL SLTIMER( 1 )
358*
359 IF( CHECK ) THEN
360*
361* Check for memory overwrite
362*
363 CALL PDCHEKPAD( ICTXT, 'pdsytrd', NP, NQ,
364 $ MEM( IPA-IPREPAD ), DESCA( LLD_ ),
365 $ IPREPAD, IPOSTPAD, PADVAL )
366 CALL PDCHEKPAD( ICTXT, 'pdsytrd', NDIAG, 1,
367 $ MEM( IPD-IPREPAD ), NDIAG, IPREPAD,
368 $ IPOSTPAD, PADVAL )
369 CALL PDCHEKPAD( ICTXT, 'pdsytrd', NOFFD, 1,
370 $ MEM( IPE-IPREPAD ), NOFFD, IPREPAD,
371 $ IPOSTPAD, PADVAL )
372 CALL PDCHEKPAD( ICTXT, 'pdsytrd', NQ, 1,
373 $ MEM( IPT-IPREPAD ), NQ, IPREPAD,
374 $ IPOSTPAD, PADVAL )
375 CALL PDCHEKPAD( ICTXT, 'pdsytrd', WORKTRD-IPOSTPAD, 1,
376 $ MEM( IPW-IPREPAD ), WORKTRD-IPOSTPAD,
377 $ IPREPAD, IPOSTPAD, PADVAL )
378 CALL PDFILLPAD( ICTXT, WORKSIZ-IPOSTPAD, 1,
379 $ MEM( IPW-IPREPAD ), WORKSIZ-IPOSTPAD,
380 $ IPREPAD, IPOSTPAD, PADVAL )
381*
382* Compute fctres = ||A - QTQ'|| / (||A|| * N * eps)
383*
384 CALL PDSYTDRV( UPLO, N, MEM( IPA ), 1, 1, DESCA,
385 $ MEM( IPD ), MEM( IPE ), MEM( IPT ),
386 $ MEM( IPW ), IERR( 1 ) )
387 CALL PDLAFCHK( 'symm', 'no', N, N, MEM( IPA ), 1, 1,
388 $ DESCA, IASEED, ANORM, FRESID,
389 $ MEM( IPW ) )
390*
391* Check for memory overwrite
392*
393 CALL PDCHEKPAD( ICTXT, 'pdsytdrv', NP, NQ,
394 $ MEM( IPA-IPREPAD ), DESCA( LLD_ ),
395 $ IPREPAD, IPOSTPAD, PADVAL )
396 CALL PDCHEKPAD( ICTXT, 'pdsytdrv', NDIAG, 1,
397 $ MEM( IPD-IPREPAD ), NDIAG, IPREPAD,
398 $ IPOSTPAD, PADVAL )
399 CALL PDCHEKPAD( ICTXT, 'pdsytdrv', NOFFD, 1,
400 $ MEM( IPE-IPREPAD ), NOFFD, IPREPAD,
401 $ IPOSTPAD, PADVAL )
402 CALL PDCHEKPAD( ICTXT, 'pdsytdrv', WORKSIZ-IPOSTPAD,
403 $ 1, MEM( IPW-IPREPAD ),
404 $ WORKSIZ-IPOSTPAD, IPREPAD, IPOSTPAD,
405 $ PADVAL )
406*
407* Test residual and detect NaN result
408*
409.LE..AND..EQ. IF( FRESIDTHRESH FRESID-FRESID
410.AND..EQ. $ 0.0D+0 IERR( 1 )0 ) THEN
411 KPASS = KPASS + 1
412 PASSED = 'passed'
413 ELSE
414.EQ..AND..EQ. IF( MYROW0 MYCOL0 )
415 $ WRITE( NOUT, FMT = 9986 )FRESID
416 KFAIL = KFAIL + 1
417 PASSED = 'failed'
418 END IF
419*
420.EQ..AND..EQ..AND..NE. IF( MYROW0 MYCOL0 IERR( 1 )0 )
421 $ WRITE( NOUT, FMT = * )'d or e copies incorrect ...'
422 ELSE
423*
424* Don't perform the checking, only the timing operation
425*
426 KPASS = KPASS + 1
427 FRESID = FRESID - FRESID
428 PASSED = 'bypass'
429 END IF
430*
431* Gather maximum of all CPU and WALL clock timings
432*
433 CALL SLCOMBINE( ICTXT, 'all', '>', 'w', 1, 1, WTIME )
434 CALL SLCOMBINE( ICTXT, 'all', '>', 'c', 1, 1, CTIME )
435*
436* Print results
437*
438.EQ..AND..EQ. IF( MYROW0 MYCOL0 ) THEN
439*
440* TRD requires 4/3 N^3 floating point operations
441*
442 NOPS = DBLE( N )
443*
444 NOPS = ( 4.0D+0 / 3.0D+0 )*NOPS**3
445 NOPS = NOPS / 1.0D+6
446*
447* Print WALL time
448*
449.GT. IF( WTIME( 1 )0.0D+0 ) THEN
450 TMFLOPS = NOPS / WTIME( 1 )
451 ELSE
452 TMFLOPS = 0.0D+0
453 END IF
454.GE. IF( WTIME( 1 )0.0D+0 )
455 $ WRITE( NOUT, FMT = 9993 )'wall', UPLO, N, NB,
456 $ NPROW, NPCOL, WTIME( 1 ), TMFLOPS, FRESID, PASSED
457*
458* Print CPU time
459*
460.GT. IF( CTIME( 1 )0.0D+0 ) THEN
461 TMFLOPS = NOPS / CTIME( 1 )
462 ELSE
463 TMFLOPS = 0.0D+0
464 END IF
465.GE. IF( CTIME( 1 )0.0D+0 )
466 $ WRITE( NOUT, FMT = 9993 )'cpu ', UPLO, N, NB,
467 $ NPROW, NPCOL, CTIME( 1 ), TMFLOPS, FRESID, PASSED
468 END IF
469 10 CONTINUE
470 20 CONTINUE
471*
472 CALL BLACS_GRIDEXIT( ICTXT )
473 30 CONTINUE
474*
475 CALL PDTTRDTESTER( IAM, NPROCS, CHECK, NOUT, THRESH, NVAL, NMAT,
476 $ MEM, TOTMEM, KPASS, KFAIL, KSKIP )
477*
478* Print ending messages and close output file
479*
480.EQ. IF( IAM0 ) THEN
481 KTESTS = KPASS + KFAIL + KSKIP
482 WRITE( NOUT, FMT = * )
483 WRITE( NOUT, FMT = 9992 )KTESTS
484 IF( CHECK ) THEN
485 WRITE( NOUT, FMT = 9991 )KPASS
486 WRITE( NOUT, FMT = 9989 )KFAIL
487 ELSE
488 WRITE( NOUT, FMT = 9990 )KPASS
489 END IF
490 WRITE( NOUT, FMT = 9988 )KSKIP
491 WRITE( NOUT, FMT = * )
492 WRITE( NOUT, FMT = * )
493 WRITE( NOUT, FMT = 9987 )
494.NE..AND..NE. IF( NOUT6 NOUT0 )
495 $ CLOSE ( NOUT )
496 END IF
497*
498 CALL BLACS_EXIT( 0 )
499*
500 9999 FORMAT( 'illegal ', A6, ': ', A5, ' = ', I3,
501 $ '; it should be at least 1' )
502 9998 FORMAT( 'illegal grid: nprow*npcol = ', I4, '. it can be at most',
503 $ I4 )
504 9997 FORMAT( 'bad ', A6, ' parameters: going on to next test case.' )
505 9996 FORMAT( 'unable to perform ', A, ': need totmem of at least',
506 $ I11 )
507 9995 FORMAT( 'time uplo n nb p q trd time ',
508 $ ' mflops residual check' )
509 9994 FORMAT( '---- ---- ------ --- ----- ----- --------- ',
510 $ '----------- -------- ------' )
511 9993 FORMAT( A4, 1X, A4, 1X, I6, 1X, I3, 1X, I5, 1X, I5, 1X, F9.2, 1X,
512 $ F11.2, 1X, F8.2, 1X, A6 )
513 9992 FORMAT( 'finished', I4, ' tests, with the following results:' )
514 9991 FORMAT( I5, ' tests completed and passed residual checks.' )
515 9990 FORMAT( I5, ' tests completed without checking.' )
516 9989 FORMAT( I5, ' tests completed and failed residual checks.' )
517 9988 FORMAT( I5, ' tests skipped because of illegal input values.' )
518 9987 FORMAT( 'END OF TESTS.' )
519 9986 FORMAT( '||A - Q*T*Q''|| / (||A|| * N * eps) = ', g25.7 )
520*
521 stop
522*
523* End of PDTRDDRIVER
524*
525 END
subroutine pdlafchk(aform, diag, m, n, a, ia, ja, desca, iaseed, anorm, fresid, work)
Definition pdlafchk.f:3
subroutine pdmatgen(ictxt, aform, diag, m, n, mb, nb, a, lda, iarow, iacol, iseed, iroff, irnum, icoff, icnum, myrow, mycol, nprow, npcol)
Definition pdmatgen.f:4
end diagonal values have been computed in the(sparse) matrix id.SOL
logical function lsame(ca, cb)
LSAME
Definition lsame.f:53
integer function iceil(inum, idenom)
Definition iceil.f:2
integer function ilcm(m, n)
Definition ilcm.f:2
#define max(a, b)
Definition macros.h:21
subroutine blacs_gridinit(cntxt, c, nprow, npcol)
Definition mpi.f:745
subroutine descinit(desc, m, n, mb, nb, irsrc, icsrc, ictxt, lld, info)
Definition mpi.f:777
subroutine blacs_gridexit(cntxt)
Definition mpi.f:762
subroutine blacs_gridinfo(cntxt, nprow, npcol, myrow, mycol)
Definition mpi.f:754
integer function numroc(n, nb, iproc, isrcproc, nprocs)
Definition mpi.f:786
subroutine pdchekpad(ictxt, mess, m, n, a, lda, ipre, ipost, chkval)
Definition pdchekpad.f:3
subroutine pdfillpad(ictxt, m, n, a, lda, ipre, ipost, chkval)
Definition pdfillpad.f:2
double precision function pdlansy(norm, uplo, n, a, ia, ja, desca, work)
Definition pdlansy.f:3
subroutine pdsytdrv(uplo, n, a, ia, ja, desca, d, e, tau, work, info)
Definition pdsytdrv.f:3
subroutine pdsytrd(uplo, n, a, ia, ja, desca, d, e, tau, work, lwork, info)
Definition pdsytrd.f:3
program pdtrddriver
Definition pdtrddriver.f:1
subroutine pdtrdinfo(summry, nout, uplo, nmat, nval, ldnval, nnb, nbval, ldnbval, ngrids, pval, ldpval, qval, ldqval, thresh, work, iam, nprocs)
Definition pdtrdinfo.f:4
subroutine pdttrdtester(iam, nprocs, check, nout, thresh, nval, nmat, mem, totmem, kpass, kfail, kskip)
Definition pdttrdtester.f:3
subroutine slboot()
Definition sltimer.f:2
subroutine sltimer(i)
Definition sltimer.f:47
subroutine slcombine(ictxt, scope, op, timetype, n, ibeg, times)
Definition sltimer.f:267