OpenRadioss 2025.1.11
OpenRadioss project
Loading...
Searching...
No Matches
xpjlaenv.f
Go to the documentation of this file.
1 INTEGER FUNCTION pjlaenv( ICTXT, ISPEC, NAME, OPTS, N1,
2 $ N2, N3, N4 )
3*
4* -- ScaLAPACK test routine (version 1.7) --
5* University of Tennessee, Knoxville, Oak Ridge National Laboratory,
6* and University of California, Berkeley.
7* March 2, 2000
8*
9* .. Scalar Arguments ..
10 CHARACTER*( * ) name, opts
11 INTEGER ictxt, ispec, n1, n2, n3, n4
12* ..
13*
14* xpjlaenv.f versus pjlaenv.f
15* ===========================
16*
17* xpjlaenv.f is used during testing to allow the timer/tester to
18* control pjlaenv's return values by setting common variables.
19* xpjlaenv.f guarantees that the return value is the same as the
20* corresponding value in common. xpjlaenv.f either reads values
21* from common and uses them as return values or it writes the
22* return value to common. Either way, xpjlaenv.f's return
23* value and the correpsonding value in common will always match.
24*
25* When the common variable "TIMING" is set, the other common
26* variables are set to the values returned by xpjlaenv.f, else
27* xpjlaenv.f returns the values as set in common.
28*
29* Purpose
30*
31* =======
32*
33* PJLAENV is called from the ScaLAPACK symmetric and Hermitian
34* tailored eigen-routines to choose
35* problem-dependent parameters for the local environment. See ISPEC
36* for a description of the parameters.
37*
38* This version provides a set of parameters which should give good,
39* but not optimal, performance on many of the currently available
40* computers. Users are encouraged to modify this subroutine to set
41* the tuning parameters for their particular machine using the option
42* and problem size information in the arguments.
43*
44* This routine will not function correctly if it is converted to all
45* lower case. Converting it to all upper case is allowed.
46*
47* Arguments
48* =========
49*
50* ISPEC (global input) INTEGER
51* Specifies the parameter to be returned as the value of
52* PJLAENV.
53* = 1: the data layout blocksize;
54* = 2: the panel blocking factor;
55* = 3: the algorithmic blocking factor;
56* = 4: execution path control;
57* = 5: maximum size for direct call to the LAPACK routine
58*
59* NAME (global input) CHARACTER*(*)
60* The name of the calling subroutine, in either upper case or
61* lower case.
62*
63* OPTS (global input) CHARACTER*(*)
64* The character options to the subroutine NAME, concatenated
65* into a single character string. For example, UPLO = 'U',
66* TRANS = 'T', and DIAG = 'N' for a triangular routine would
67* be specified as OPTS = 'UTN'.
68*
69* N1 (global input) INTEGER
70* N2 (global input) INTEGER
71* N3 (global input) INTEGER
72* N4 (global input) INTEGER
73* Problem dimensions for the subroutine NAME; these may not all
74* be required.
75*
76* At present, only N1 is used, and it (N1) is used only for
77* 'TTRD'
78*
79* (PJLAENV) (global or local output) INTEGER
80* >= 0: the value of the parameter specified by ISPEC
81* < 0: if PJLAENV = -k, the k-th argument had an illegal
82* value.
83*
84* Most parameters set via a call to PJLAENV must be identical
85* on all processors and hence PJLAENV will return the same
86* value to all procesors (i.e. global output). However some,
87* in particular, the panel blocking factor can be different
88* on each processor and hence PJLAENV can return different
89* values on different processors (i.e. local output).
90*
91* Further Details
92* ===============
93*
94* The following conventions have been used when calling PJLAENV from
95* the ScaLAPACK routines:
96* 1) OPTS is a concatenation of all of the character options to
97* subroutine NAME, in the same order that they appear in the
98* argument list for NAME, even if they are not used in determining
99* the value of the parameter specified by ISPEC.
100* 2) The problem dimensions N1, N2, N3, N4 are specified in the order
101* that they appear in the argument list for NAME. N1 is used
102* first, N2 second, and so on, and unused problem dimensions are
103* passed a value of -1.
104* 3) The parameter value returned by PJLAENV is checked for validity
105* in the calling subroutine. For example, PJLAENV is used to
106* retrieve the optimal blocksize for STRTRI as follows:
107*
108* NB = PJLAENV( 1, 'STRTRI', UPLO // DIAG, N, -1, -1, -1 )
109* IF( NB.LE.1 ) NB = MAX( 1, N )
110*
111* PJLAENV is patterned after ILAENV and keeps the same interface in
112* anticipation of future needs, even though PJLAENV is only sparsely
113* used at present in ScaLAPACK. Most ScaLAPACK codes use the input
114* data layout blocking factor as the algorithmic blocking factor -
115* hence there is no need or opportunity to set the algorithmic or
116* data decomposition blocking factor.
117*
118* pXYYtevx.f and pXYYtgvx.f and pXYYttrd.f are the only codes which
119* call PJLAENV in this release. pXYYtevx.f and pXYYtgvx.f redistribute
120* the data to the best data layout for each transformation. pXYYttrd.f
121* uses a data layout blocking factor of 1 and a
122*
123* =====================================================================
124*
125* .. Parameters ..
126 INTEGER BLOCK_CYCLIC_2D, csrc_, ctxt_, dlen_, DTYPE_,
127 $ lld_, mb_, m_, nb_, n_, rsrc_
128 parameter( block_cyclic_2d = 1, dlen_ = 9, dtype_ = 1,
129 $ ctxt_ = 2, m_ = 3, n_ = 4, mb_ = 5, nb_ = 6,
130 $ rsrc_ = 7, csrc_ = 8, lld_ = 9 )
131* ..
132* .. Local Scalars ..
133 LOGICAL cname, global, sname, time
134 CHARACTER c1
135 CHARACTER*2 c2, c4
136 CHARACTER*3 c3
137 CHARACTER*8 subnam
138 INTEGER i, ic, idumm, iz, msz, nb
139* ..
140* .. Intrinsic Functions ..
141 INTRINSIC char, ichar
142* ..
143*
144*
145* .. Scalars in Common ..
146 INTEGER anb, balanced, bckblock, gstblock, interleave,
147 $ lltblock, minsz, pnb, timing, trsblock,
148 $ twogemms
149* ..
150* .. External Subroutines ..
151 EXTERNAL igamx2d
152* ..
153* .. Common blocks ..
154 COMMON / blocksizes / gstblock, lltblock, bckblock,
155 $ trsblock
156 COMMON / minsize / minsz
157 COMMON / pjlaenvtiming / timing
158 COMMON / tailoredopts / pnb, anb, interleave,
159 $ balanced, twogemms
160* ..
161* .. Executable Statements ..
162*
163 time = ( timing.EQ.1 )
164*
165*
166 GO TO ( 10, 10, 10, 10, 10 )ispec
167*
168* Invalid value for ISPEC
169*
170 pjlaenv = -1
171 RETURN
172*
173 10 CONTINUE
174*
175* Convert NAME to upper case if the first character is lower case.
176*
177 pjlaenv = 1
178 subnam = name
179 ic = ichar( subnam( 1: 1 ) )
180 iz = ichar( 'Z' )
181 IF( iz.EQ.100 .OR. iz.EQ.122 ) THEN
182*
183* ASCII character set
184*
185 IF( ic.GE.97 .AND. ic.LE.122 ) THEN
186 subnam( 1: 1 ) = char( ic-32 )
187 DO 20 i = 2, 6
188 ic = ichar( subnam( i: i ) )
189 IF( ic.GE.97 .AND. ic.LE.122 )
190 $ subnam( i: i ) = char( ic-32 )
191 20 CONTINUE
192 END IF
193*
194 ELSE IF( iz.EQ.233 .OR. iz.EQ.169 ) THEN
195*
196* EBCDIC character set
197*
198 IF( ( ic.GE.129 .AND. ic.LE.137 ) .OR.
199 $ ( ic.GE.145 .AND. ic.LE.153 ) .OR.
200 $ ( ic.GE.162 .AND. ic.LE.169 ) ) THEN
201 subnam( 1: 1 ) = char( ic+64 )
202 DO 30 i = 2, 6
203 ic = ichar( subnam( i: i ) )
204 IF( ( ic.GE.129 .AND. ic.LE.137 ) .OR.
205 $ ( ic.GE.145 .AND. ic.LE.153 ) .OR.
206 $ ( ic.GE.162 .AND. ic.LE.169 ) )subnam( i:
207 $ i ) = char( ic+64 )
208 30 CONTINUE
209 END IF
210*
211 ELSE IF( iz.EQ.218 .OR. iz.EQ.250 ) THEN
212*
213* Prime machines: ASCII+128
214*
215 IF( ic.GE.225 .AND. ic.LE.250 ) THEN
216 subnam( 1: 1 ) = char( ic-32 )
217 DO 40 i = 2, 6
218 ic = ichar( subnam( i: i ) )
219 IF( ic.GE.225 .AND. ic.LE.250 )
220 $ subnam( i: i ) = char( ic-32 )
221 40 CONTINUE
222 END IF
223 END IF
224*
225 c1 = subnam( 2: 2 )
226 sname = c1.EQ.'S' .OR. c1.EQ.'D'
227 cname = c1.EQ.'C' .OR. c1.EQ.'z'
228.NOT..OR. IF( ( CNAME SNAME ) )
229 $ RETURN
230 C2 = SUBNAM( 3: 4 )
231 C3 = SUBNAM( 5: 7 )
232 C4 = C3( 2: 3 )
233*
234* This is to keep ftnchek happy
235*
236.NE. IF( ( N2+N3+N4 )*00 ) THEN
237 C4 = OPTS
238 C3 = C4
239 END IF
240*
241 GO TO ( 50, 60, 70, 80, 90 )ISPEC
242*
243 50 CONTINUE
244*
245* ISPEC = 1: data layout block size
246* (global - all processes must use the same value)
247*
248* In these examples, separate code is provided for setting NB for
249* real and complex. We assume that NB will take the same value in
250* single or double precision.
251*
252 NB = 1
253*
254.EQ. IF( C2'sy.OR..EQ.' C2'he' ) THEN
255.EQ. IF( C3'llt' ) THEN
256 IF( SNAME ) THEN
257 NB = 64
258 ELSE
259 NB = 64
260 END IF
261 IF( TIME ) THEN
262 LLTBLOCK = NB
263 ELSE
264 NB = LLTBLOCK
265.LE. IF( NB0 ) THEN
266 PRINT *, 'xpjlaenv.f error common variable lltblock',
267 $ ' may be unitialized'
268c CALL EXIT( 13 )
269 STOP
270 END IF
271 END IF
272.EQ. ELSE IF( C3'ttr' ) THEN
273 IF( SNAME ) THEN
274 NB = 1
275 ELSE
276 NB = 1
277 END IF
278.EQ. ELSE IF( C3'gst' ) THEN
279 IF( SNAME ) THEN
280 NB = 32
281 ELSE
282 NB = 32
283 END IF
284 IF( TIME ) THEN
285 GSTBLOCK = NB
286 ELSE
287 NB = GSTBLOCK
288.LE. IF( NB0 ) THEN
289 PRINT *, 'xpjlaenv.f error common variable gstblock',
290 $ ' may be unitialized'
291c CALL EXIT( 13 )
292 STOP
293 END IF
294 END IF
295.EQ. ELSE IF( C3'bck' ) THEN
296 IF( SNAME ) THEN
297 NB = 32
298 ELSE
299 NB = 32
300 END IF
301 IF( TIME ) THEN
302 BCKBLOCK = NB
303 ELSE
304 NB = BCKBLOCK
305.LE. IF( NB0 ) THEN
306 PRINT *, 'xpjlaenv.f error common variable bckblock',
307 $ ' may be unitialized'
308c CALL EXIT( 13 )
309 STOP
310 END IF
311 END IF
312.EQ. ELSE IF( C3'trs' ) THEN
313 IF( SNAME ) THEN
314 NB = 64
315 ELSE
316 NB = 64
317 END IF
318 IF( TIME ) THEN
319 TRSBLOCK = NB
320 ELSE
321 NB = TRSBLOCK
322.LE. IF( NB0 ) THEN
323 PRINT *, 'xpjlaenv.f error common variable trsblock',
324 $ ' may be unitialized'
325c CALL EXIT( 13 )
326 STOP
327 END IF
328 END IF
329 END IF
330 END IF
331*
332*
333 PJLAENV = NB
334 GLOBAL = .TRUE.
335 GO TO 100
336*
337 60 CONTINUE
338*
339* ISPEC = 2: panel blocking factor (Used only in PxyyTTRD)
340* (local - different processes may use different values)
341*
342 NB = 16
343.EQ. IF( C2'sy.OR..EQ.' C2'he' ) THEN
344.EQ. IF( C3'ttr' ) THEN
345 IF( SNAME ) THEN
346 NB = 32
347 ELSE
348 NB = 32
349 END IF
350 END IF
351 END IF
352 IF( TIME ) THEN
353 PNB = NB
354 ELSE
355 NB = PNB
356.LE. IF( NB0 ) THEN
357 PRINT *, 'xpjlaenv.f error common variable pnb',
358 $ ' may be unitialized'
359c CALL EXIT( 13 )
360 STOP
361 END IF
362 END IF
363 PJLAENV = NB
364 GLOBAL = .FALSE.
365 GO TO 100
366*
367*
368 70 CONTINUE
369*
370* ISPEC = 3: algorithmic blocking factor (Used only in PxyyTTRD)
371* (global - all processes must use the same value)
372*
373 NB = 16
374 NB = 1
375.EQ. IF( C2'sy.OR..EQ.' C2'he' ) THEN
376.EQ. IF( C3'ttr' ) THEN
377 IF( SNAME ) THEN
378 NB = 16
379 ELSE
380 NB = 16
381 END IF
382 END IF
383 END IF
384 IF( TIME ) THEN
385 ANB = NB
386 ELSE
387 NB = ANB
388.LE. IF( NB0 ) THEN
389 PRINT *, 'xpjlaenv.f error common variable anb',
390 $ ' may be unitialized'
391c CALL EXIT( 13 )
392 STOP
393 END IF
394 END IF
395 PJLAENV = NB
396 GLOBAL = .TRUE.
397 GO TO 100
398*
399 80 CONTINUE
400*
401* ISPEC = 4: Execution path options (Used only in PxyyTTRD)
402* (global - all processes must use the same value)
403*
404 PJLAENV = -4
405.EQ. IF( C2'sy.OR..EQ.' C2'he' ) THEN
406.EQ. IF( C3'ttr' ) THEN
407* V and H interleaved (default is not interleaved)
408.EQ. IF( N11 ) THEN
409 PJLAENV = 1
410 IF( TIME ) THEN
411 INTERLEAVE = PJLAENV
412 ELSE
413 PJLAENV = INTERLEAVE
414 END IF
415 END IF
416*
417* Two ZGEMMs (default is one ZGEMM)
418.EQ. IF( N12 ) THEN
419 PJLAENV = 0
420 IF( TIME ) THEN
421 TWOGEMMS = PJLAENV
422 ELSE
423 PJLAENV = TWOGEMMS
424 END IF
425 END IF
426* Balanced Update (default is minimum communication update)
427.EQ. IF( N13 ) THEN
428 PJLAENV = 0
429 IF( TIME ) THEN
430 BALANCED = PJLAENV
431 ELSE
432 PJLAENV = BALANCED
433 END IF
434 END IF
435 END IF
436 END IF
437 GLOBAL = .TRUE.
438 GO TO 100
439*
440 90 CONTINUE
441*
442* ISPEC = 5: Minimum size to justify call to parallel code
443* (global - all processes must use the same value)
444*
445 MSZ = 0
446.EQ. IF( C2'sy.OR..EQ.' C2'he' ) THEN
447.EQ. IF( C3'ttr' ) THEN
448 IF( SNAME ) THEN
449 MSZ = 100
450 ELSE
451 MSZ = 100
452 END IF
453 END IF
454 END IF
455 IF( TIME ) THEN
456 MINSZ = MSZ
457 ELSE
458 MSZ = MINSZ
459 END IF
460 PJLAENV = MSZ
461 GLOBAL = .TRUE.
462 GO TO 100
463*
464 100 CONTINUE
465*
466 IF( GLOBAL ) THEN
467 IDUMM = 0
468 CALL IGAMX2D( ICTXT, 'all', ' ', 1, 1, PJLAENV, 1, IDUMM,
469 $ IDUMM, -1, -1, IDUMM )
470 END IF
471*
472*
473*
474 RETURN
475*
476* End of PJLAENV
477*
478 END
integer function pjlaenv(ictxt, ispec, name, opts, n1, n2, n3, n4)
Definition xpjlaenv.f:3