ScaLAPACK 2.1  2.1
ScaLAPACK: Scalable Linear Algebra PACKage
pcseptst.f
Go to the documentation of this file.
1 
2 *
3  SUBROUTINE pcseptst( DESCA, UPLO, N, MATTYPE, SUBTESTS, THRESH,
4  $ ORDER, ABSTOL, ISEED, A, COPYA, Z, LDA, WIN,
5  $ WNEW, IFAIL, ICLUSTR, GAP, IPREPAD, IPOSTPAD,
6  $ WORK, LWORK, RWORK, LRWORK, IWORK, LIWORK,
7  $ NOUT, INFO )
8 *
9 * -- ScaLAPACK routine (version 1.7) --
10 * University of Tennessee, Knoxville, Oak Ridge National Laboratory,
11 * and University of California, Berkeley.
12 * March 15, 2002
13 *
14 * .. Scalar Arguments ..
15  CHARACTER SUBTESTS, UPLO
16  INTEGER INFO, IPOSTPAD, IPREPAD, LDA, LIWORK, LRWORK,
17  $ LWORK, MATTYPE, N, NOUT, ORDER
18  REAL ABSTOL, THRESH
19 * ..
20 * .. Array Arguments ..
21  INTEGER DESCA( * ), ICLUSTR( * ), IFAIL( * ),
22  $ iseed( 4 ), iwork( * )
23  REAL GAP( * ), RWORK( * ), WIN( * ), WNEW( * )
24  COMPLEX A( LDA, * ), COPYA( LDA, * ), WORK( * ),
25  $ z( lda, * )
26 * ..
27 *
28 * Purpose
29 * =======
30 *
31 * PCSEPTST builds a random matrix, runs PCHEEVX() to
32 * compute the eigenvalues
33 * and eigenvectors and then performs two tests to
34 * determine if the result
35 * is good enough. The two tests are:
36 * |AQ -QL| / (abstol + ulp * norm(A) )
37 * and
38 * |QT * Q - I| / ulp * norm(A)
39 *
40 * The random matrix built depends upon the following parameters:
41 * N, NB, ISEED, ORDER
42 *
43 * Arguments
44 * =========
45 *
46 * NP = the number of rows local to a given process.
47 * NQ = the number of columns local to a given process.
48 *
49 * DESCA (global and local input) INTEGER array of dimension DLEN_
50 * The array descriptor for the distributed matrices
51 *
52 * UPLO (global input) CHARACTER*1
53 * Specifies whether the upper or lower triangular part of the
54 * Hermitian matrix A is stored:
55 * = 'U': Upper triangular
56 * = 'L': Lower triangular
57 *
58 * N (global input) INTEGER
59 * Size of the matrix to be tested. (global size)
60 *
61 * MATTYPE (global input) INTEGER
62 * Matrix type
63 * Currently, the list of possible types is:
64 *
65 * (1) The zero matrix.
66 * (2) The identity matrix.
67 *
68 * (3) A diagonal matrix with evenly spaced entries
69 * 1, ..., ULP and random signs.
70 * (ULP = (first number larger than 1) - 1 )
71 * (4) A diagonal matrix with geometrically spaced entries
72 * 1, ..., ULP and random signs.
73 * (5) A diagonal matrix with "clustered" entries 1, ULP, ..., ULP
74 * and random signs.
75 *
76 * (6) Same as (4), but multiplied by SQRT( overflow threshold )
77 * (7) Same as (4), but multiplied by SQRT( underflow threshold )
78 *
79 * (8) A matrix of the form U' D U, where U is orthogonal and
80 * D has evenly spaced entries 1, ..., ULP with random signs
81 * on the diagonal.
82 *
83 * (9) A matrix of the form U' D U, where U is orthogonal and
84 * D has geometrically spaced entries 1, ..., ULP with random
85 * signs on the diagonal.
86 *
87 * (10) A matrix of the form U' D U, where U is orthogonal and
88 * D has "clustered" entries 1, ULP,..., ULP with random
89 * signs on the diagonal.
90 *
91 * (11) Same as (8), but multiplied by SQRT( overflow threshold )
92 * (12) Same as (8), but multiplied by SQRT( underflow threshold )
93 *
94 * (13) Hermitian matrix with random entries chosen from (-1,1).
95 * (14) Same as (13), but multiplied by SQRT( overflow threshold )
96 * (15) Same as (13), but multiplied by SQRT( underflow threshold )
97 * (16) Same as (8), but diagonal elements are all positive.
98 * (17) Same as (9), but diagonal elements are all positive.
99 * (18) Same as (10), but diagonal elements are all positive.
100 * (19) Same as (16), but multiplied by SQRT( overflow threshold )
101 * (20) Same as (16), but multiplied by SQRT( underflow threshold )
102 * (21) A tridiagonal matrix that is a direct sum of smaller diagonally
103 * dominant submatrices. Each unreduced submatrix has geometrically
104 * spaced diagonal entries 1, ..., ULP.
105 * (22) A matrix of the form U' D U, where U is orthogonal and
106 * D has ceil(lgN) "clusters" at 0,1,2,...,ceil(lgN)-1. The
107 * size of the cluster at the value I is 2^I.
108 *
109 * SUBTESTS (global input) CHARACTER*1
110 * 'Y' - Perform subset tests
111 * 'N' - Do not perform subset tests
112 *
113 * THRESH (global input) REAL
114 * A test will count as "failed" if the "error", computed as
115 * described below, exceeds THRESH. Note that the error
116 * is scaled to be O(1), so THRESH should be a reasonably
117 * small multiple of 1, e.g., 10 or 100. In particular,
118 * it should not depend on the precision (single vs. double)
119 * or the size of the matrix. It must be at least zero.
120 *
121 * ORDER (global input) INTEGER
122 * Number of reflectors used in test matrix creation.
123 * If ORDER is large, it will
124 * take more time to create the test matrices but they will
125 * be closer to random.
126 * ORDER .lt. N not implemented
127 *
128 * ABSTOL (global input) REAL
129 * The absolute tolerance for the eigenvalues. An
130 * eigenvalue is considered to be located if it has
131 * been determined to lie in an interval whose width
132 * is "abstol" or less. If "abstol" is less than or equal
133 * to zero, then ulp*|T| will be used, where |T| is
134 * the 1-norm of the matrix. If eigenvectors are
135 * desired later by inverse iteration ("PCSTEIN"),
136 * "abstol" MUST NOT be bigger than ulp*|T|.
137 *
138 * For the purposes of this test, ABSTOL=0.0 is fine.
139 * THis test does not test for high relative accuracy.
140 *
141 * ISEED (global input/output) INTEGER array, dimension (4)
142 * On entry, the seed of the random number generator; the array
143 * elements must be between 0 and 4095, and ISEED(4) must be
144 * odd.
145 * On exit, the seed is updated.
146 *
147 * A (local workspace) COMPLEX array, dim (N*N)
148 * global dimension (N, N), local dimension (LDA, NQ)
149 * A is distributed in a block cyclic manner over both rows
150 * and columns. The actual location of a particular element
151 * in A is controlled by the values of NPROW, NPCOL, and NB.
152 * The test matrix, which is then modified by PCHEEVX
153 *
154 * COPYA (local workspace) COMPLEX array, dim (N, N)
155 * COPYA is used to hold an identical copy of the array A
156 * identical in both form and content to A
157 *
158 * Z (local workspace) COMPLEX array, dim (N*N)
159 * Z is distributed in the same manner as A
160 * Z is used as workspace by the test routines
161 * PCSEPCHK and PCSEPQTQ
162 *
163 * W (local workspace) REAL array, dimension (N)
164 * On normal exit from PCHEEVX, the first M entries
165 * contain the selected eigenvalues in ascending order.
166 *
167 * IFAIL (global workspace) INTEGER array, dimension (N)
168 *
169 * WORK (local workspace) COMPLEX array, dimension (LWORK)
170 *
171 * LWORK (local input) INTEGER
172 * The length of the array WORK. LWORK >= SIZETST as
173 * returned by PCLASIZESEP
174 *
175 * RWORK (local workspace) COMPLEX array, dimension (LWORK)
176 *
177 * LRWORK (local input) INTEGER
178 * The length of the array WORK. LRWORK >= RSIZETST as
179 * returned by PCLASIZESEP
180 *
181 * IWORK (local workspace) INTEGER array, dimension (LIWORK)
182 *
183 * LIWORK (local input) INTEGER
184 * The length of the array IWORK. LIWORK >= ISIZETST as
185 * returned by PCLASIZESEP
186 *
187 * NOUT (local input) INTEGER
188 * The unit number for output file. Only used on node 0.
189 * NOUT = 6, output to screen,
190 * NOUT = 0, output to stderr.
191 * NOUT = 13, output to file, divide thresh by 10.0
192 * NOUT = 14, output to file, divide thresh by 20.0
193 * (This hack allows us to test more stringently internally
194 * so that when errors on found on other computers they will
195 * be serious enough to warrant our attention.)
196 *
197 * INFO (global output) INTEGER
198 * -3 This process is not involved
199 * 0 Test succeeded (passed |AQ -QL| and |QT*Q - I| tests)
200 * 1 At least one test failed
201 * 2 Residual test were not performed, thresh <= 0.0
202 * 3 Test was skipped because of inadequate memory space
203 *
204 * .. Parameters ..
205  INTEGER BLOCK_CYCLIC_2D, DLEN_, DTYPE_, CTXT_, M_, N_,
206  $ MB_, NB_, RSRC_, CSRC_, LLD_
207  PARAMETER ( BLOCK_CYCLIC_2D = 1, dlen_ = 9, dtype_ = 1,
208  $ ctxt_ = 2, m_ = 3, n_ = 4, mb_ = 5, nb_ = 6,
209  $ rsrc_ = 7, csrc_ = 8, lld_ = 9 )
210  REAL ZERO, ONE, TEN, HALF
211  parameter( zero = 0.0e+0, one = 1.0e+0, ten = 10.0e+0,
212  $ half = 0.5e+0 )
213  COMPLEX PADVAL
214  parameter( padval = ( 19.25e+0, 1.1e+1 ) )
215  COMPLEX CZERO
216  PARAMETER ( CZERO = ( 0.0e+0, 0.0e+0 ) )
217  COMPLEX CONE
218  parameter( cone = ( 1.0e+0, 0.0e+0 ) )
219  INTEGER MAXTYP
220  parameter( maxtyp = 22 )
221 * ..
222 *
223 * .. Local Scalars ..
224  LOGICAL WKNOWN
225  CHARACTER JOBZ, RANGE
226  CHARACTER*14 PASSED
227  INTEGER CONTEXT, I, IAM, IINFO, IL, IMODE, IN, INDD,
228  $ indrwork, indwork, isizeheevd, isizeheevx,
229  $ isizesubtst, isizetst, itype, iu, j,
230  $ lheevdsize, lheevxsize, llrwork, llwork,
231  $ maxsize, mycol, myrow, nb, ngen, nloc, nnodes,
232  $ np, np0, npcol, nprow, nq, nq0, res, rsizechk,
233  $ rsizeheevd, rsizeheevx, rsizeqtq, rsizesubtst,
234  $ rsizetst, sizeheevd, sizeheevx, sizemqrleft,
235  $ sizemqrright, sizeqrf, sizesubtst, sizetms,
236  $ sizetst, valsize, vecsize
237  REAL ANINV, ANORM, COND, MAXQTQNRM, MAXTSTNRM, OVFL,
238  $ QTQNRM, RTOVFL, RTUNFL, TEMP1, TSTNRM, ULP,
239  $ ULPINV, UNFL, VL, VU
240 * ..
241 * .. Local Arrays ..
242  INTEGER ISEEDIN( 4 ), KMAGN( MAXTYP ), KMODE( MAXTYP ),
243  $ KTYPE( MAXTYP )
244  DOUBLE PRECISION CTIME( 10 ), WTIME( 10 )
245 * ..
246 * .. External Functions ..
247  LOGICAL LSAME
248  INTEGER NUMROC
249  REAL PSLAMCH, SLARAN
250  EXTERNAL LSAME, NUMROC, PSLAMCH, SLARAN
251 * ..
252 * .. External Subroutines ..
253  EXTERNAL blacs_gridinfo, blacs_pinfo, clatms, igamx2d,
254  $ igebr2d, igebs2d, pcchekpad, pcelset,
257  $ slabad, slasrt, slcombine
258 * ..
259 * .. Intrinsic Functions ..
260  INTRINSIC abs, int, max, min, real, sqrt
261 * ..
262 * .. Data statements ..
263  DATA ktype / 1, 2, 4, 4, 4, 4, 4, 5, 5, 5, 5, 5, 8,
264  $ 8, 8, 9, 9, 9, 9, 9, 10, 11 /
265  DATA kmagn / 1, 1, 1, 1, 1, 2, 3, 1, 1, 1, 2, 3, 1,
266  $ 2, 3, 1, 1, 1, 2, 3, 1, 1 /
267  DATA kmode / 0, 0, 4, 3, 1, 4, 4, 4, 3, 1, 4, 4, 0,
268  $ 0, 0, 4, 3, 1, 4, 4, 3, 0 /
269 * ..
270 * .. Executable Statements ..
271 * This is just to keep ftnchek happy
272  IF( block_cyclic_2d*csrc_*ctxt_*dlen_*dtype_*lld_*mb_*m_*nb_*n_*
273  $ rsrc_.LT.0 )RETURN
274 *
275  info = 0
276  passed = 'PASSED EEVX'
277  context = desca( ctxt_ )
278  nb = desca( nb_ )
279 *
280  CALL blacs_pinfo( iam, nnodes )
281  CALL blacs_gridinfo( context, nprow, npcol, myrow, mycol )
282 *
283 *
284 * Make sure that we have enough memory
285 *
286 *
287  CALL pclasizesep( desca, iprepad, ipostpad, sizemqrleft,
288  $ sizemqrright, sizeqrf, sizetms, rsizeqtq,
289  $ rsizechk, sizeheevx, rsizeheevx, isizeheevx,
290  $ sizeheevd, rsizeheevd, isizeheevd, sizesubtst,
291  $ rsizesubtst, isizesubtst, sizetst, rsizetst,
292  $ isizetst )
293 *
294  IF( lrwork.LT.rsizetst ) THEN
295  info = 3
296  END IF
297 *
298  CALL igamx2d( context, 'a', ' ', 1, 1, info, 1, 1, 1, -1, -1, 0 )
299 *
300  IF( info.EQ.0 ) THEN
301 *
302  indd = 1
303  indrwork = indd + n
304  indwork = 1
305  llwork = lwork - indwork + 1
306  llrwork = lrwork - indrwork + 1
307 *
308  ulp = pslamch( context, 'P' )
309  ulpinv = one / ulp
310  unfl = pslamch( context, 'Safe min' )
311  ovfl = one / unfl
312  CALL slabad( unfl, ovfl )
313  rtunfl = sqrt( unfl )
314  rtovfl = sqrt( ovfl )
315  aninv = one / real( max( 1, n ) )
316 *
317 * This ensures that everyone starts out with the same seed.
318 *
319  IF( myrow.EQ.0 .AND. mycol.EQ.0 ) THEN
320  CALL igebs2d( context, 'a', ' ', 4, 1, iseed, 4 )
321  ELSE
322  CALL igebr2d( context, 'a', ' ', 4, 1, iseed, 4, 0, 0 )
323  END IF
324  iseedin( 1 ) = iseed( 1 )
325  iseedin( 2 ) = iseed( 2 )
326  iseedin( 3 ) = iseed( 3 )
327  iseedin( 4 ) = iseed( 4 )
328 *
329 * Compute the matrix A
330 *
331 * Control parameters:
332 *
333 * KMAGN KMODE KTYPE
334 * =1 O(1) clustered 1 zero
335 * =2 large clustered 2 identity
336 * =3 small exponential (none)
337 * =4 arithmetic diagonal, (w/ eigenvalues)
338 * =5 random log Hermitian, w/ eigenvalues
339 * =6 random (none)
340 * =7 random diagonal
341 * =8 random Hermitian
342 * =9 positive definite
343 * =10 block diagonal with tridiagonal blocks
344 * =11 Geometrically sized clusters.
345 *
346  itype = ktype( mattype )
347  imode = kmode( mattype )
348 *
349 * Compute norm
350 *
351  GO TO ( 10, 20, 30 )kmagn( mattype )
352 *
353  10 CONTINUE
354  anorm = one
355  GO TO 40
356 *
357  20 CONTINUE
358  anorm = ( rtovfl*ulp )*aninv
359  GO TO 40
360 *
361  30 CONTINUE
362  anorm = rtunfl*n*ulpinv
363  GO TO 40
364 *
365  40 CONTINUE
366  IF( mattype.LE.15 ) THEN
367  cond = ulpinv
368  ELSE
369  cond = ulpinv*aninv / ten
370  END IF
371 *
372 * Special Matrices
373 *
374 * Zero
375 *
376 *
377  IF( itype.EQ.1 ) THEN
378 *
379 * Zero Matrix
380 *
381  DO 50 i = 1, n
382  rwork( indd+i-1 ) = zero
383  50 CONTINUE
384  CALL pclaset( 'All', n, n, czero, czero, copya, 1, 1,
385  $ desca )
386  wknown = .true.
387 *
388  ELSE IF( itype.EQ.2 ) THEN
389 *
390 * Identity Matrix
391 *
392  DO 60 i = 1, n
393  rwork( indd+i-1 ) = one
394  60 CONTINUE
395  CALL pclaset( 'All', n, n, czero, cone, copya, 1, 1, desca )
396  wknown = .true.
397 *
398  ELSE IF( itype.EQ.4 ) THEN
399 *
400 * Diagonal Matrix, [Eigen]values Specified
401 *
402  CALL pcfillpad( desca( ctxt_ ), sizetms, 1, work( indwork ),
403  $ sizetms, iprepad, ipostpad, padval+1.0e+0 )
404 *
405  CALL pclatms( n, n, 'S', iseed, 'S', rwork( indd ), imode,
406  $ cond, anorm, 0, 0, 'N', copya, 1, 1, desca,
407  $ order, work( indwork+iprepad ), sizetms,
408  $ iinfo )
409  wknown = .true.
410 *
411  CALL pcchekpad( desca( ctxt_ ), 'PCLATMS1-WORK', sizetms, 1,
412  $ work( indwork ), sizetms, iprepad, ipostpad,
413  $ padval+1.0e+0 )
414 *
415  ELSE IF( itype.EQ.5 ) THEN
416 *
417 * Hermitian, eigenvalues specified
418 *
419  CALL pcfillpad( desca( ctxt_ ), sizetms, 1, work( indwork ),
420  $ sizetms, iprepad, ipostpad, padval+2.0e+0 )
421 *
422  CALL pclatms( n, n, 'S', iseed, 'S', rwork( indd ), imode,
423  $ cond, anorm, n, n, 'N', copya, 1, 1, desca,
424  $ order, work( indwork+iprepad ), sizetms,
425  $ iinfo )
426 *
427  CALL pcchekpad( desca( ctxt_ ), 'PCLATMS2-WORK', sizetms, 1,
428  $ work( indwork ), sizetms, iprepad, ipostpad,
429  $ padval+2.0e+0 )
430 *
431  wknown = .true.
432 *
433  ELSE IF( itype.EQ.8 ) THEN
434 *
435 * Hermitian, random eigenvalues
436 *
437  np = numroc( n, desca( mb_ ), myrow, 0, nprow )
438  nq = numroc( n, desca( nb_ ), mycol, 0, npcol )
439  CALL pcmatgen( desca( ctxt_ ), 'H', 'N', n, n, desca( mb_ ),
440  $ desca( nb_ ), copya, desca( lld_ ),
441  $ desca( rsrc_ ), desca( csrc_ ), iseed( 1 ),
442  $ 0, np, 0, nq, myrow, mycol, nprow, npcol )
443  info = 0
444  wknown = .false.
445 *
446  ELSE IF( itype.EQ.9 ) THEN
447 *
448 * Positive definite, eigenvalues specified.
449 *
450 *
451  CALL pcfillpad( desca( ctxt_ ), sizetms, 1, work( indwork ),
452  $ sizetms, iprepad, ipostpad, padval+3.0e+0 )
453 *
454  CALL pclatms( n, n, 'S', iseed, 'S', rwork( indd ), imode,
455  $ cond, anorm, n, n, 'N', copya, 1, 1, desca,
456  $ order, work( indwork+iprepad ), sizetms,
457  $ iinfo )
458 *
459  wknown = .true.
460 *
461  CALL pcchekpad( desca( ctxt_ ), 'PCLATMS3-WORK', sizetms, 1,
462  $ work( indwork ), sizetms, iprepad, ipostpad,
463  $ padval+3.0e+0 )
464 *
465  ELSE IF( itype.EQ.10 ) THEN
466 *
467 * Block diagonal matrix with each block being a positive
468 * definite tridiagonal submatrix.
469 *
470  CALL pclaset( 'All', n, n, czero, czero, copya, 1, 1,
471  $ desca )
472  np = numroc( n, desca( mb_ ), 0, 0, nprow )
473  nq = numroc( n, desca( nb_ ), 0, 0, npcol )
474  nloc = min( np, nq )
475  ngen = 0
476  70 CONTINUE
477 *
478  IF( ngen.LT.n ) THEN
479  in = min( 1+int( slaran( iseed )*real( nloc ) ), n-ngen )
480 *
481  CALL clatms( in, in, 'S', iseed, 'P', rwork( indd ),
482  $ imode, cond, anorm, 1, 1, 'N', a, lda,
483  $ work( indwork ), iinfo )
484 *
485  DO 80 i = 2, in
486  temp1 = abs( a( i-1, i ) ) /
487  $ sqrt( abs( a( i-1, i-1 )*a( i, i ) ) )
488  IF( temp1.GT.half ) THEN
489  a( i-1, i ) = half*sqrt( abs( a( i-1, i-1 )*a( i,
490  $ i ) ) )
491  a( i, i-1 ) = a( i-1, i )
492  END IF
493  80 CONTINUE
494  CALL pcelset( copya, ngen+1, ngen+1, desca, a( 1, 1 ) )
495  DO 90 i = 2, in
496  CALL pcelset( copya, ngen+i, ngen+i, desca,
497  $ a( i, i ) )
498  CALL pcelset( copya, ngen+i-1, ngen+i, desca,
499  $ a( i-1, i ) )
500  CALL pcelset( copya, ngen+i, ngen+i-1, desca,
501  $ a( i, i-1 ) )
502  90 CONTINUE
503  ngen = ngen + in
504  GO TO 70
505  END IF
506  wknown = .false.
507 *
508  ELSE IF( itype.EQ.11 ) THEN
509 *
510 * Geometrically sized clusters. Eigenvalues: 0,1,1,2,2,2,2, ...
511 *
512  ngen = 0
513  j = 1
514  temp1 = zero
515  100 CONTINUE
516  IF( ngen.LT.n ) THEN
517  in = min( j, n-ngen )
518  DO 110 i = 0, in - 1
519  rwork( indd+ngen+i ) = temp1
520  110 CONTINUE
521  temp1 = temp1 + one
522  j = 2*j
523  ngen = ngen + in
524  GO TO 100
525  END IF
526 *
527 *
528  CALL pcfillpad( desca( ctxt_ ), sizetms, 1, work( indwork ),
529  $ sizetms, iprepad, ipostpad, padval+4.0e+0 )
530 *
531  CALL pclatms( n, n, 'S', iseed, 'S', rwork( indd ), imode,
532  $ cond, anorm, 0, 0, 'N', copya, 1, 1, desca,
533  $ order, work( indwork+iprepad ), sizetms,
534  $ iinfo )
535 *
536  CALL pcchekpad( desca( ctxt_ ), 'PCLATMS4-WORK', sizetms, 1,
537  $ work( indwork ), sizetms, iprepad, ipostpad,
538  $ padval+4.0e+0 )
539 *
540 *
541 * WKNOWN ... NOT SET, GUESS A DEFAULT
542 *
543  wknown = .true.
544  ELSE
545  iinfo = 1
546  END IF
547 *
548  IF( wknown )
549  $ CALL slasrt( 'I', n, rwork( indd ), iinfo )
550 *
551 *
552 * These values aren't actually used, but they make ftncheck happy.
553 *
554  il = -1
555  iu = -2
556  vl = one
557  vu = -one
558 *
559  CALL pclasizeheevx( wknown, 'A', n, desca, vl, vu, il, iu,
560  $ iseed, rwork( indd ), maxsize, vecsize,
561  $ valsize )
562 *
563  lheevxsize = min( maxsize, llrwork )
564 *
565  CALL pcsepsubtst( wknown, 'v', 'a', uplo, n, vl, vu, il, iu,
566  $ thresh, abstol, a, copya, z, 1, 1, desca,
567  $ rwork( indd ), win, ifail, iclustr, gap,
568  $ iprepad, ipostpad, work( indwork ), llwork,
569  $ rwork( indrwork ), llrwork, lheevxsize,
570  $ iwork, isizeheevx, res, tstnrm, qtqnrm,
571  $ nout )
572 *
573 *
574 *
575  maxtstnrm = tstnrm
576  maxqtqnrm = qtqnrm
577 *
578  IF( thresh.LE.zero ) THEN
579  passed = 'SKIPPED '
580  info = 2
581  ELSE IF( res.NE.0 ) THEN
582  passed = 'FAILED '
583  info = 1
584  END IF
585  END IF
586 *
587  IF( thresh.GT.zero .AND. lsame( subtests, 'Y' ) ) THEN
588 *
589 * Subtest 1: JOBZ = 'V', RANGE = 'A', minimum memory
590 *
591  IF( info.EQ.0 ) THEN
592 *
593  jobz = 'V'
594  range = 'A'
595  CALL pclasizeheevx( .true., range, n, desca, vl, vu, il, iu,
596  $ iseed, win( 1+iprepad ), maxsize,
597  $ vecsize, valsize )
598 *
599  lheevxsize = vecsize
600 *
601  CALL pcsepsubtst( .true., jobz, range, uplo, n, vl, vu, il,
602  $ iu, thresh, abstol, a, copya, z, 1, 1,
603  $ desca, win( 1+iprepad ), wnew, ifail,
604  $ iclustr, gap, iprepad, ipostpad,
605  $ work( indwork ), llwork, rwork, lrwork,
606  $ lheevxsize, iwork, isizeheevx, res,
607  $ tstnrm, qtqnrm, nout )
608 *
609  IF( res.NE.0 ) THEN
610  passed = 'FAILED stest 1'
611  maxtstnrm = max( tstnrm, maxtstnrm )
612  maxqtqnrm = max( qtqnrm, maxqtqnrm )
613  info = 1
614  END IF
615  END IF
616 *
617 * Subtest 2: JOBZ = 'V', RANGE = 'A', random memory
618 *
619  IF( info.EQ.0 ) THEN
620  jobz = 'V'
621  range = 'A'
622  CALL pclasizeheevx( .true., range, n, desca, vl, vu, il, iu,
623  $ iseed, win( 1+iprepad ), maxsize,
624  $ vecsize, valsize )
625 *
626  lheevxsize = vecsize + int( slaran( iseed )*
627  $ real( maxsize-vecsize ) )
628 *
629  CALL pcsepsubtst( .true., jobz, range, uplo, n, vl, vu, il,
630  $ iu, thresh, abstol, a, copya, z, 1, 1,
631  $ desca, win( 1+iprepad ), wnew, ifail,
632  $ iclustr, gap, iprepad, ipostpad,
633  $ work( indwork ), llwork, rwork, lrwork,
634  $ lheevxsize, iwork, isizeheevx, res,
635  $ tstnrm, qtqnrm, nout )
636 *
637  IF( res.NE.0 ) THEN
638  passed = 'FAILED stest 2'
639  maxtstnrm = max( tstnrm, maxtstnrm )
640  maxqtqnrm = max( qtqnrm, maxqtqnrm )
641  info = 1
642  END IF
643  END IF
644 *
645 * Subtest 3: JOBZ = 'N', RANGE = 'A', minimum memory
646 *
647  IF( info.EQ.0 ) THEN
648 *
649  jobz = 'N'
650  range = 'A'
651  CALL pclasizeheevx( .true., range, n, desca, vl, vu, il, iu,
652  $ iseed, win( 1+iprepad ), maxsize,
653  $ vecsize, valsize )
654 *
655  lheevxsize = valsize
656  CALL pcsepsubtst( .true., jobz, range, uplo, n, vl, vu, il,
657  $ iu, thresh, abstol, a, copya, z, 1, 1,
658  $ desca, win( 1+iprepad ), wnew, ifail,
659  $ iclustr, gap, iprepad, ipostpad,
660  $ work( indwork ), llwork, rwork, lrwork,
661  $ lheevxsize, iwork, isizeheevx, res,
662  $ tstnrm, qtqnrm, nout )
663 *
664  IF( res.NE.0 ) THEN
665  maxtstnrm = max( tstnrm, maxtstnrm )
666  maxqtqnrm = max( qtqnrm, maxqtqnrm )
667  passed = 'FAILED stest 3'
668  info = 1
669  END IF
670  END IF
671 *
672 * Subtest 4: JOBZ = 'N', RANGE = 'I', minimum memory
673 *
674  IF( info.EQ.0 ) THEN
675 *
676  il = -1
677  iu = -1
678  jobz = 'N'
679  range = 'I'
680 *
681 * We use PCLASIZEHEEVX to choose IL and IU for us.
682 *
683  CALL pclasizeheevx( .true., range, n, desca, vl, vu, il, iu,
684  $ iseed, win( 1+iprepad ), maxsize,
685  $ vecsize, valsize )
686 *
687  lheevxsize = valsize
688 *
689  CALL pcsepsubtst( .true., jobz, range, uplo, n, vl, vu, il,
690  $ iu, thresh, abstol, a, copya, z, 1, 1,
691  $ desca, win( 1+iprepad ), wnew, ifail,
692  $ iclustr, gap, iprepad, ipostpad,
693  $ work( indwork ), llwork, rwork, lrwork,
694  $ lheevxsize, iwork, isizeheevx, res,
695  $ tstnrm, qtqnrm, nout )
696 *
697  IF( res.NE.0 ) THEN
698  maxtstnrm = max( tstnrm, maxtstnrm )
699  maxqtqnrm = max( qtqnrm, maxqtqnrm )
700  passed = 'FAILED stest 4'
701  info = 1
702  END IF
703  END IF
704 *
705 * Subtest 5: JOBZ = 'V', RANGE = 'I', maximum memory
706 *
707  IF( info.EQ.0 ) THEN
708 *
709  il = -1
710  iu = -1
711  jobz = 'V'
712  range = 'I'
713 *
714 * We use PCLASIZEHEEVX to choose IL and IU for us.
715 *
716  CALL pclasizeheevx( .true., range, n, desca, vl, vu, il, iu,
717  $ iseed, win( 1+iprepad ), maxsize,
718  $ vecsize, valsize )
719 *
720  lheevxsize = maxsize
721 *
722  CALL pcsepsubtst( .true., jobz, range, uplo, n, vl, vu, il,
723  $ iu, thresh, abstol, a, copya, z, 1, 1,
724  $ desca, win( 1+iprepad ), wnew, ifail,
725  $ iclustr, gap, iprepad, ipostpad,
726  $ work( indwork ), llwork, rwork, lrwork,
727  $ lheevxsize, iwork, isizeheevx, res,
728  $ tstnrm, qtqnrm, nout )
729 *
730  IF( res.NE.0 ) THEN
731  maxtstnrm = max( tstnrm, maxtstnrm )
732  maxqtqnrm = max( qtqnrm, maxqtqnrm )
733  passed = 'FAILED stest 5'
734  info = 1
735  END IF
736  END IF
737 *
738 * Subtest 6: JOBZ = 'V', RANGE = 'I', minimum memory
739 *
740  IF( info.EQ.0 ) THEN
741  il = -1
742  iu = -1
743  jobz = 'V'
744  range = 'I'
745 *
746 * We use PCLASIZEHEEVX to choose IL and IU for us.
747 *
748  CALL pclasizeheevx( .true., range, n, desca, vl, vu, il, iu,
749  $ iseed, win( 1+iprepad ), maxsize,
750  $ vecsize, valsize )
751 *
752  lheevxsize = vecsize
753 *
754  CALL pcsepsubtst( .true., jobz, range, uplo, n, vl, vu, il,
755  $ iu, thresh, abstol, a, copya, z, 1, 1,
756  $ desca, win( 1+iprepad ), wnew, ifail,
757  $ iclustr, gap, iprepad, ipostpad,
758  $ work( indwork ), llwork, rwork, lrwork,
759  $ lheevxsize, iwork, isizeheevx, res,
760  $ tstnrm, qtqnrm, nout )
761 *
762  IF( res.NE.0 ) THEN
763  maxtstnrm = max( tstnrm, maxtstnrm )
764  maxqtqnrm = max( qtqnrm, maxqtqnrm )
765  passed = 'FAILED stest 6'
766  info = 1
767  END IF
768  END IF
769 *
770 * Subtest 7: JOBZ = 'V', RANGE = 'I', random memory
771 *
772  IF( info.EQ.0 ) THEN
773  il = -1
774  iu = -1
775  jobz = 'V'
776  range = 'I'
777 *
778 * We use PCLASIZEHEEVX to choose IL and IU for us.
779 *
780  CALL pclasizeheevx( .true., range, n, desca, vl, vu, il, iu,
781  $ iseed, win( 1+iprepad ), maxsize,
782  $ vecsize, valsize )
783  lheevxsize = vecsize + int( slaran( iseed )*
784  $ real( maxsize-vecsize ) )
785 *
786  CALL pcsepsubtst( .true., jobz, range, uplo, n, vl, vu, il,
787  $ iu, thresh, abstol, a, copya, z, 1, 1,
788  $ desca, win( 1+iprepad ), wnew, ifail,
789  $ iclustr, gap, iprepad, ipostpad,
790  $ work( indwork ), llwork, rwork, lrwork,
791  $ lheevxsize, iwork, isizeheevx, res,
792  $ tstnrm, qtqnrm, nout )
793 *
794  IF( res.NE.0 ) THEN
795  maxtstnrm = max( tstnrm, maxtstnrm )
796  maxqtqnrm = max( qtqnrm, maxqtqnrm )
797  passed = 'FAILED stest 7'
798  info = 1
799  END IF
800  END IF
801 *
802 * Subtest 8: JOBZ = 'N', RANGE = 'V', minimum memory
803 *
804  IF( info.EQ.0 ) THEN
805  vl = one
806  vu = -one
807  jobz = 'N'
808  range = 'V'
809 *
810 * We use PCLASIZEHEEVX to choose VL and VU for us.
811 *
812  CALL pclasizeheevx( .true., range, n, desca, vl, vu, il, iu,
813  $ iseed, win( 1+iprepad ), maxsize,
814  $ vecsize, valsize )
815 *
816  lheevxsize = valsize
817 *
818  CALL pcsepsubtst( .true., jobz, range, uplo, n, vl, vu, il,
819  $ iu, thresh, abstol, a, copya, z, 1, 1,
820  $ desca, win( 1+iprepad ), wnew, ifail,
821  $ iclustr, gap, iprepad, ipostpad,
822  $ work( indwork ), llwork, rwork, lrwork,
823  $ lheevxsize, iwork, isizeheevx, res,
824  $ tstnrm, qtqnrm, nout )
825 *
826  IF( res.NE.0 ) THEN
827  maxtstnrm = max( tstnrm, maxtstnrm )
828  maxqtqnrm = max( qtqnrm, maxqtqnrm )
829  passed = 'FAILED stest 8'
830  info = 1
831  END IF
832  END IF
833 *
834 * Subtest 9: JOBZ = 'V', RANGE = 'V', maximum memory
835 *
836  IF( info.EQ.0 ) THEN
837  vl = one
838  vu = -one
839  jobz = 'V'
840  range = 'V'
841 *
842 * We use PCLASIZEHEEVX to choose VL and VU for us.
843 *
844  CALL pclasizeheevx( .true., range, n, desca, vl, vu, il, iu,
845  $ iseed, win( 1+iprepad ), maxsize,
846  $ vecsize, valsize )
847 *
848  lheevxsize = maxsize
849 *
850  CALL pcsepsubtst( .true., jobz, range, uplo, n, vl, vu, il,
851  $ iu, thresh, abstol, a, copya, z, 1, 1,
852  $ desca, win( 1+iprepad ), wnew, ifail,
853  $ iclustr, gap, iprepad, ipostpad,
854  $ work( indwork ), llwork, rwork, lrwork,
855  $ lheevxsize, iwork, isizeheevx, res,
856  $ tstnrm, qtqnrm, nout )
857 *
858  IF( res.NE.0 ) THEN
859  maxtstnrm = max( tstnrm, maxtstnrm )
860  maxqtqnrm = max( qtqnrm, maxqtqnrm )
861  passed = 'FAILED stest 9'
862  info = 1
863  END IF
864  END IF
865 *
866 * Subtest 10: JOBZ = 'V', RANGE = 'V',
867 * minimum memory required for eigenvectors
868 *
869  IF( info.EQ.0 ) THEN
870  vl = one
871  vu = -one
872  jobz = 'V'
873  range = 'V'
874 *
875 * We use PCLASIZEHEEVX to choose VL and VU for us.
876 *
877  CALL pclasizeheevx( .true., range, n, desca, vl, vu, il, iu,
878  $ iseed, win( 1+iprepad ), maxsize,
879  $ vecsize, valsize )
880 *
881  lheevxsize = vecsize
882 *
883  CALL pcsepsubtst( .true., jobz, range, uplo, n, vl, vu, il,
884  $ iu, thresh, abstol, a, copya, z, 1, 1,
885  $ desca, win( 1+iprepad ), wnew, ifail,
886  $ iclustr, gap, iprepad, ipostpad,
887  $ work( indwork ), llwork, rwork, lrwork,
888  $ lheevxsize, iwork, isizeheevx, res,
889  $ tstnrm, qtqnrm, nout )
890 *
891  IF( res.NE.0 ) THEN
892  maxtstnrm = max( tstnrm, maxtstnrm )
893  maxqtqnrm = max( qtqnrm, maxqtqnrm )
894  passed = 'FAILED stest10'
895  info = 1
896  END IF
897  END IF
898 *
899 * Subtest 11: JOBZ = 'V', RANGE = 'V',
900 * random memory (enough for all eigenvectors
901 * but not enough to guarantee orthogonality
902 *
903  IF( info.EQ.0 ) THEN
904  vl = one
905  vu = -one
906  jobz = 'V'
907  range = 'V'
908 *
909 * We use PCLASIZEHEEVX to choose VL and VU for us.
910 *
911  CALL pclasizeheevx( .true., range, n, desca, vl, vu, il, iu,
912  $ iseed, win( 1+iprepad ), maxsize,
913  $ vecsize, valsize )
914 *
915 *
916  CALL pcsepsubtst( .true., jobz, range, uplo, n, vl, vu, il,
917  $ iu, thresh, abstol, a, copya, z, 1, 1,
918  $ desca, win( 1+iprepad ), wnew, ifail,
919  $ iclustr, gap, iprepad, ipostpad,
920  $ work( indwork ), llwork, rwork, lrwork,
921  $ lheevxsize, iwork, isizeheevx, res,
922  $ tstnrm, qtqnrm, nout )
923 *
924  IF( res.NE.0 ) THEN
925  maxtstnrm = max( tstnrm, maxtstnrm )
926  maxqtqnrm = max( qtqnrm, maxqtqnrm )
927  passed = 'FAILED stest11'
928  info = 1
929  END IF
930  END IF
931 *
932 * Subtest 12: JOBZ = 'V', RANGE = 'V',
933 * miniimum memory required for eigenvalues only
934 *
935  IF( info.EQ.0 ) THEN
936  vl = one
937  vu = -one
938  jobz = 'V'
939  range = 'V'
940 *
941 * We use PCLASIZEHEEVX to choose VL and VU for us.
942 *
943  CALL pclasizeheevx( .true., range, n, desca, vl, vu, il, iu,
944  $ iseed, win( 1+iprepad ), maxsize,
945  $ vecsize, valsize )
946 *
947  lheevxsize = valsize
948 *
949  CALL pcsepsubtst( .true., jobz, range, uplo, n, vl, vu, il,
950  $ iu, thresh, abstol, a, copya, z, 1, 1,
951  $ desca, win( 1+iprepad ), wnew, ifail,
952  $ iclustr, gap, iprepad, ipostpad,
953  $ work( indwork ), llwork, rwork, lrwork,
954  $ lheevxsize, iwork, isizeheevx, res,
955  $ tstnrm, qtqnrm, nout )
956 *
957  IF( res.NE.0 ) THEN
958  maxtstnrm = max( tstnrm, maxtstnrm )
959  maxqtqnrm = max( qtqnrm, maxqtqnrm )
960  passed = 'FAILED stest12'
961  info = 1
962  END IF
963  END IF
964 *
965 * Subtest 13: JOBZ = 'V', RANGE = 'V',
966 * random memory (more than minimum required
967 * for eigenvalues, less than required for vectors)
968 *
969  IF( info.EQ.0 ) THEN
970  vl = one
971  vu = -one
972  jobz = 'V'
973  range = 'V'
974 *
975 * We use PCLASIZEHEEVX to choose VL and VU for us.
976 *
977  CALL pclasizeheevx( .true., range, n, desca, vl, vu, il, iu,
978  $ iseed, win( 1+iprepad ), maxsize,
979  $ vecsize, valsize )
980 *
981 *
982  CALL pcsepsubtst( .true., jobz, range, uplo, n, vl, vu, il,
983  $ iu, thresh, abstol, a, copya, z, 1, 1,
984  $ desca, win( 1+iprepad ), wnew, ifail,
985  $ iclustr, gap, iprepad, ipostpad,
986  $ work( indwork ), llwork, rwork, lrwork,
987  $ lheevxsize, iwork, isizeheevx, res,
988  $ tstnrm, qtqnrm, nout )
989 *
990  IF( res.NE.0 ) THEN
991  maxtstnrm = max( tstnrm, maxtstnrm )
992  maxqtqnrm = max( qtqnrm, maxqtqnrm )
993  passed = 'FAILED stest13'
994  info = 1
995  END IF
996  END IF
997  END IF
998 *
999 *
1000 *
1001  CALL igamx2d( context, 'All', ' ', 1, 1, info, 1, -1, -1, -1, -1,
1002  $ -1 )
1003 *
1004  IF( info.EQ.1 ) THEN
1005  IF( iam.EQ.0 ) THEN
1006  WRITE( nout, fmt = 9994 )'C '
1007  WRITE( nout, fmt = 9993 )iseedin( 1 )
1008  WRITE( nout, fmt = 9992 )iseedin( 2 )
1009  WRITE( nout, fmt = 9991 )iseedin( 3 )
1010  WRITE( nout, fmt = 9990 )iseedin( 4 )
1011  IF( lsame( uplo, 'L' ) ) THEN
1012  WRITE( nout, fmt = 9994 )' UPLO= ''L'' '
1013  ELSE
1014  WRITE( nout, fmt = 9994 )' UPLO= ''U'' '
1015  END IF
1016  IF( lsame( subtests, 'Y' ) ) THEN
1017  WRITE( nout, fmt = 9994 )' SUBTESTS= ''Y'' '
1018  ELSE
1019  WRITE( nout, fmt = 9994 )' SUBTESTS= ''N'' '
1020  END IF
1021  WRITE( nout, fmt = 9989 )n
1022  WRITE( nout, fmt = 9988 )nprow
1023  WRITE( nout, fmt = 9987 )npcol
1024  WRITE( nout, fmt = 9986 )nb
1025  WRITE( nout, fmt = 9985 )mattype
1026  WRITE( nout, fmt = 9982 )abstol
1027  WRITE( nout, fmt = 9981 )thresh
1028  WRITE( nout, fmt = 9994 )'C '
1029  END IF
1030  END IF
1031 *
1032  CALL slcombine( context, 'All', '>', 'W', 6, 1, wtime )
1033  CALL slcombine( context, 'All', '>', 'C', 6, 1, ctime )
1034  IF( iam.EQ.0 ) THEN
1035  IF( info.EQ.0 .OR. info.EQ.1 ) THEN
1036  IF( wtime( 1 ).GE.0.0 ) THEN
1037  WRITE( nout, fmt = 9999 )n, nb, nprow, npcol, mattype,
1038  $ subtests, wtime( 1 ), ctime( 1 ), maxtstnrm,
1039  $ maxqtqnrm, passed
1040  ELSE
1041  WRITE( nout, fmt = 9998 )n, nb, nprow, npcol, mattype,
1042  $ subtests, ctime( 1 ), maxtstnrm, maxqtqnrm, passed
1043  END IF
1044  ELSE IF( info.EQ.2 ) THEN
1045  IF( wtime( 1 ).GE.0.0 ) THEN
1046  WRITE( nout, fmt = 9997 )n, nb, nprow, npcol, mattype,
1047  $ subtests, wtime( 1 ), ctime( 1 )
1048  ELSE
1049  WRITE( nout, fmt = 9996 )n, nb, nprow, npcol, mattype,
1050  $ subtests, ctime( 1 )
1051  END IF
1052  ELSE IF( info.EQ.3 ) THEN
1053  WRITE( nout, fmt = 9995 )n, nb, nprow, npcol, mattype,
1054  $ subtests
1055  END IF
1056  END IF
1057 *
1058 * Now that PCHEEVX been tested, we check PCHEEVD
1059 *
1060  passed = 'PASSED EEVD'
1061 *
1062 * PCHEEVD test1:
1063 *
1064  IF( info.EQ.0 ) THEN
1065 *
1066  np0 = numroc( n, nb, 0, 0, nprow )
1067  nq0 = numroc( max( n, 1 ), nb, 0, 0, npcol )
1068  lheevdsize = 1 + 9*n + 3*np0*nq0
1069  isizeheevd = max( 1, 2+7*n+8*npcol )
1070 *
1071  CALL pcsdpsubtst( wknown, uplo, n, thresh, abstol, a, copya, z,
1072  $ 1, 1, desca, win, wnew, iprepad, ipostpad,
1073  $ work( indwork ), llwork, rwork, lrwork,
1074  $ lheevdsize, iwork, isizeheevd, res, tstnrm,
1075  $ qtqnrm, nout )
1076 *
1077  maxtstnrm = tstnrm
1078  maxqtqnrm = qtqnrm
1079 
1080  IF( res.NE.0 ) THEN
1081  passed = 'FAILED EEVD'
1082  info = 1
1083  END IF
1084  END IF
1085 *
1086 *
1087 *
1088  CALL igamx2d( context, 'All', ' ', 1, 1, info, 1, -1, -1, -1, -1,
1089  $ -1 )
1090 *
1091  IF( info.EQ.1 ) THEN
1092  IF( iam.EQ.0 ) THEN
1093  WRITE( nout, fmt = 9994 )'C '
1094  WRITE( nout, fmt = 9993 )iseedin( 1 )
1095  WRITE( nout, fmt = 9992 )iseedin( 2 )
1096  WRITE( nout, fmt = 9991 )iseedin( 3 )
1097  WRITE( nout, fmt = 9990 )iseedin( 4 )
1098  IF( lsame( uplo, 'L' ) ) THEN
1099  WRITE( nout, fmt = 9994 )' UPLO= ''L'' '
1100  ELSE
1101  WRITE( nout, fmt = 9994 )' UPLO= ''U'' '
1102  END IF
1103  IF( lsame( subtests, 'Y' ) ) THEN
1104  WRITE( nout, fmt = 9994 )' SUBTESTS= ''Y'' '
1105  ELSE
1106  WRITE( nout, fmt = 9994 )' SUBTESTS= ''N'' '
1107  END IF
1108  WRITE( nout, fmt = 9989 )n
1109  WRITE( nout, fmt = 9988 )nprow
1110  WRITE( nout, fmt = 9987 )npcol
1111  WRITE( nout, fmt = 9986 )nb
1112  WRITE( nout, fmt = 9985 )mattype
1113  WRITE( nout, fmt = 9982 )abstol
1114  WRITE( nout, fmt = 9981 )thresh
1115  WRITE( nout, fmt = 9994 )'C '
1116  END IF
1117  END IF
1118 *
1119  CALL slcombine( context, 'All', '>', 'W', 6, 1, wtime )
1120  CALL slcombine( context, 'All', '>', 'C', 6, 1, ctime )
1121  IF( iam.EQ.0 ) THEN
1122  IF( info.EQ.0 .OR. info.EQ.1 ) THEN
1123  IF( wtime( 1 ).GE.0.0 ) THEN
1124  WRITE( nout, fmt = 9999 )n, nb, nprow, npcol, mattype,
1125  $ subtests, wtime( 1 ), ctime( 1 ), maxtstnrm,
1126  $ maxqtqnrm, passed
1127  ELSE
1128  WRITE( nout, fmt = 9998 )n, nb, nprow, npcol, mattype,
1129  $ subtests, ctime( 1 ), maxtstnrm, maxqtqnrm, passed
1130  END IF
1131  ELSE IF( info.EQ.2 ) THEN
1132  IF( wtime( 1 ).GE.0.0 ) THEN
1133  WRITE( nout, fmt = 9997 )n, nb, nprow, npcol, mattype,
1134  $ subtests, wtime( 1 ), ctime( 1 )
1135  ELSE
1136  WRITE( nout, fmt = 9996 )n, nb, nprow, npcol, mattype,
1137  $ subtests, ctime( 1 )
1138  END IF
1139  ELSE IF( info.EQ.3 ) THEN
1140  WRITE( nout, fmt = 9995 )n, nb, nprow, npcol, mattype,
1141  $ subtests
1142  END IF
1143  END IF
1144  120 CONTINUE
1145 *
1146  RETURN
1147  9999 FORMAT( 1x, i5, 1x, i3, 1x, i3, 1x, i3, 1x, i3, 3x, a1, 1x, f8.2,
1148  $ 1x, f8.2, 1x, g9.2, 1x, g9.2, 1x, a14 )
1149  9998 FORMAT( 1x, i5, 1x, i3, 1x, i3, 1x, i3, 1x, i3, 3x, a1, 1x, 8x,
1150  $ 1x, f8.2, 1x, g9.2, 1x, g9.2, a14 )
1151  9997 FORMAT( 1x, i5, 1x, i3, 1x, i3, 1x, i3, 1x, i3, 3x, a1, 1x, f8.2,
1152  $ 1x, f8.2, 21x, 'Bypassed' )
1153  9996 FORMAT( 1x, i5, 1x, i3, 1x, i3, 1x, i3, 1x, i3, 3x, a1, 1x, 8x,
1154  $ 1x, f8.2, 21x, 'Bypassed' )
1155  9995 FORMAT( 1x, i5, 1x, i3, 1x, i3, 1x, i3, 1x, i3, 3x, a1, 32x,
1156  $ 'Bad MEMORY parameters' )
1157  9994 FORMAT( a )
1158  9993 FORMAT( ' ISEED( 1 ) =', i8 )
1159  9992 FORMAT( ' ISEED( 2 ) =', i8 )
1160  9991 FORMAT( ' ISEED( 3 ) =', i8 )
1161  9990 FORMAT( ' ISEED( 4 ) =', i8 )
1162  9989 FORMAT( ' N=', i8 )
1163  9988 FORMAT( ' NPROW=', i8 )
1164  9987 FORMAT( ' NPCOL=', i8 )
1165  9986 FORMAT( ' NB=', i8 )
1166  9985 FORMAT( ' MATTYPE=', i8 )
1167  9984 FORMAT( ' IBTYPE=', i8 )
1168  9983 FORMAT( ' SUBTESTS=', a1 )
1169  9982 FORMAT( ' ABSTOL=', d16.6 )
1170  9981 FORMAT( ' THRESH=', d16.6 )
1171  9980 FORMAT( ' Increase TOTMEM in PCSEPDRIVER' )
1172 *
1173 * End of PCSEPTST
1174 *
1175  END
max
#define max(A, B)
Definition: pcgemr.c:180
clatms
subroutine clatms(M, N, DIST, ISEED, SYM, D, MODE, COND, DMAX, KL, KU, PACK, A, LDA, WORK, INFO)
Definition: clatms.f:3
pcsdpsubtst
subroutine pcsdpsubtst(WKNOWN, UPLO, N, THRESH, ABSTOL, A, COPYA, Z, IA, JA, DESCA, WIN, WNEW, IPREPAD, IPOSTPAD, WORK, LWORK, RWORK, LRWORK, LWORK1, IWORK, LIWORK, RESULT, TSTNRM, QTQNRM, NOUT)
Definition: pcsdpsubtst.f:6
pcseptst
subroutine pcseptst(DESCA, UPLO, N, MATTYPE, SUBTESTS, THRESH, ORDER, ABSTOL, ISEED, A, COPYA, Z, LDA, WIN, WNEW, IFAIL, ICLUSTR, GAP, IPREPAD, IPOSTPAD, WORK, LWORK, RWORK, LRWORK, IWORK, LIWORK, NOUT, INFO)
Definition: pcseptst.f:8
pclasizesep
subroutine pclasizesep(DESCA, IPREPAD, IPOSTPAD, SIZEMQRLEFT, SIZEMQRRIGHT, SIZEQRF, SIZETMS, RSIZEQTQ, RSIZECHK, SIZEHEEVX, RSIZEHEEVX, ISIZEHEEVX, SIZEHEEVD, RSIZEHEEVD, ISIZEHEEVD, SIZESUBTST, RSIZESUBTST, ISIZESUBTST, SIZETST, RSIZETST, ISIZETST)
Definition: pclasizesep.f:7
pcchekpad
subroutine pcchekpad(ICTXT, MESS, M, N, A, LDA, IPRE, IPOST, CHKVAL)
Definition: pcchekpad.f:3
pclatms
subroutine pclatms(M, N, DIST, ISEED, SYM, D, MODE, COND, DMAX, KL, KU, PACK, A, IA, JA, DESCA, ORDER, WORK, LWORK, INFO)
Definition: pclatms.f:6
pcmatgen
subroutine pcmatgen(ICTXT, AFORM, DIAG, M, N, MB, NB, A, LDA, IAROW, IACOL, ISEED, IROFF, IRNUM, ICOFF, ICNUM, MYROW, MYCOL, NPROW, NPCOL)
Definition: pcmatgen.f:4
pclasizeheevx
subroutine pclasizeheevx(WKNOWN, RANGE, N, DESCA, VL, VU, IL, IU, ISEED, WIN, MAXSIZE, VECSIZE, VALSIZE)
Definition: pclasizeheevx.f:5
pcsepsubtst
subroutine pcsepsubtst(WKNOWN, JOBZ, RANGE, UPLO, N, VL, VU, IL, IU, THRESH, ABSTOL, A, COPYA, Z, IA, JA, DESCA, WIN, WNEW, IFAIL, ICLUSTR, GAP, IPREPAD, IPOSTPAD, WORK, LWORK, RWORK, LRWORK, LWORK1, IWORK, LIWORK, RESULT, TSTNRM, QTQNRM, NOUT)
Definition: pcsepsubtst.f:9
pcelset
subroutine pcelset(A, IA, JA, DESCA, ALPHA)
Definition: pcelset.f:2
pclaset
subroutine pclaset(UPLO, M, N, ALPHA, BETA, A, IA, JA, DESCA)
Definition: pcblastst.f:7508
pcfillpad
subroutine pcfillpad(ICTXT, M, N, A, LDA, IPRE, IPOST, CHKVAL)
Definition: pcfillpad.f:2
slcombine
subroutine slcombine(ICTXT, SCOPE, OP, TIMETYPE, N, IBEG, TIMES)
Definition: sltimer.f:267
min
#define min(A, B)
Definition: pcgemr.c:181