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