OpenRadioss 2025.1.11
OpenRadioss project
Loading...
Searching...
No Matches
pclltinfo.f
Go to the documentation of this file.
1 SUBROUTINE pclltinfo( SUMMRY, NOUT, UPLO, NMAT, NVAL, LDNVAL, NNB,
2 $ NBVAL, LDNBVAL, NNR, NRVAL, LDNRVAL, NNBR,
3 $ NBRVAL, LDNBRVAL, NGRIDS, PVAL, LDPVAL,
4 $ QVAL, LDQVAL, THRESH, EST, WORK, IAM,
5 $ NPROCS )
6*
7* -- ScaLAPACK routine (version 1.7) --
8* University of Tennessee, Knoxville, Oak Ridge National Laboratory,
9* and University of California, Berkeley.
10* May 1, 1997
11*
12* .. Scalar Arguments ..
13 LOGICAL EST
14 CHARACTER UPLO
15 CHARACTER*(*) SUMMRY
16 INTEGER IAM, LDNBRVAL, LDNBVAL, LDNRVAL, LDNVAL,
17 $ ldpval, ldqval, ngrids, nmat, nnb, nnbr,
18 $ nprocs, nnr, nout
19 REAL THRESH
20* ..
21* .. Array Arguments ..
22 INTEGER NBRVAL( LDNBRVAL ), NBVAL( LDNBVAL ),
23 $ nrval( ldnrval ), nval( ldnval ),
24 $ pval( ldpval ), qval(ldqval), work( * )
25* ..
26*
27* Purpose
28* =======
29*
30* PCLLTINFO get needed startup information for LLt factorization
31* and transmits it to all processes.
32*
33* Arguments
34* =========
35*
36* SUMMRY (global output) CHARACTER*(*)
37* Name of output (summary) file (if any). Only defined for
38* process 0.
39*
40* NOUT (global output) INTEGER
41* The unit number for output file. NOUT = 6, ouput to screen,
42* NOUT = 0, output to stderr. Only defined for process 0.
43*
44* UPLO (global output) CHARACTER
45* Specifies whether the upper or lower triangular part of the
46* symmetric matrix A is stored.
47* = 'U': Upper triangular
48* = 'L': Lower triangular
49*
50* NMAT (global output) INTEGER
51* The number of different values that can be used for N.
52*
53* NVAL (global output) INTEGER array, dimension (LDNVAL)
54* The values of N (number of columns in matrix) to run the
55* code with.
56*
57* LDNVAL (global input) INTEGER
58* The maximum number of different values that can be used for
59* N, LDNVAL > = NMAT.
60*
61* NNB (global output) INTEGER
62* The number of different values that can be used for NB.
63*
64* NBVAL (global output) INTEGER array, dimension (LDNBVAL)
65* The values of NB (blocksize) to run the code with.
66*
67* LDNBVAL (global input) INTEGER
68* The maximum number of different values that can be used for
69* NB, LDNBVAL >= NNB.
70*
71* NNR (global output) INTEGER
72* The number of different values that can be used for NRHS.
73*
74* NRVAL (global output) INTEGER array, dimension(LDNRVAL)
75* The values of NRHS (# of Right Hand Sides) to run the code
76* with.
77*
78* LDNRVAL (global input) INTEGER
79* The maximum number of different values that can be used for
80* NRHS, LDNRVAL >= NNR.
81*
82* NNBR (global output) INTEGER
83* The number of different values that can be used for NBRHS.
84*
85* NBRVAL (global output) INTEGER array, dimension (LDNBRVAL)
86* The values of NBRHS (RHS blocksize) to run the code with.
87*
88* LDNBRVAL (global input) INTEGER
89* The maximum number of different values that can be used for
90* NBRHS, LDNBRVAL >= NBRVAL.
91*
92* NGRIDS (global output) INTEGER
93* The number of different values that can be used for P & Q.
94*
95* PVAL (global output) INTEGER array, dimension (LDPVAL)
96* The values of P (number of process rows) to run the code
97* with.
98*
99* LDPVAL (global input) INTEGER
100* The maximum number of different values that can be used for
101* P, LDPVAL >= NGRIDS.
102*
103* QVAL (global output) INTEGER array, dimension (LDQVAL)
104* The values of Q (number of process columns) to run the code
105* with.
106*
107* LDQVAL (global input) INTEGER
108* The maximum number of different values that can be used for
109* Q, LDQVAL >= NGRIDS.
110*
111* THRESH (global output) REAL
112* Indicates what error checks shall be run and printed out:
113* = 0 : Perform no error checking
114* > 0 : report all residuals greater than THRESH, perform
115* factor check only if solve check fails
116*
117* EST (global output) LOGICAL
118* Flag indicating if condition estimation and iterative
119* refinement routines are to be exercised.
120*
121* WORK (local workspace) INTEGER array of dimension >=
122* MAX( 7, LDNVAL+LDNBVAL+LDNRVAL+LDNBRVAL+LDPVAL+LDQVAL)
123* Used to pack input arrays in order to send info in one
124* message.
125*
126* IAM (local input) INTEGER
127* My process number.
128*
129* NPROCS (global input) INTEGER
130* The total number of processes.
131*
132* ======================================================================
133*
134* Note: For packing the information we assumed that the length in bytes
135* ===== of an integer is equal to the length in bytes of a real single
136* precision.
137*
138* ======================================================================
139*
140* .. Parameters ..
141 INTEGER BLOCK_CYCLIC_2D, CSRC_, CTXT_, DLEN_, DTYPE_,
142 $ LLD_, MB_, M_, NB_, N_, RSRC_
143 PARAMETER ( BLOCK_CYCLIC_2D = 1, dlen_ = 9, dtype_ = 1,
144 $ ctxt_ = 2, m_ = 3, n_ = 4, mb_ = 5, nb_ = 6,
145 $ rsrc_ = 7, csrc_ = 8, lld_ = 9 )
146 INTEGER NIN
147 parameter( nin = 11 )
148* ..
149* .. Local Scalars ..
150 INTEGER I, ICTXT
151 CHARACTER*79 USRINFO
152 REAL EPS
153* ..
154* .. External Subroutines ..
155 EXTERNAL blacs_abort, blacs_get, blacs_gridexit,
156 $ blacs_gridinit, blacs_setup, icopy, igebr2d,
157 $ igebs2d, sgebr2d, sgebs2d
158* ..
159* .. External Functions ..
160 LOGICAL LSAME
161 REAL PSLAMCH
162 EXTERNAL LSAME, PSLAMCH
163* ..
164* .. Intrinsic Functions ..
165 INTRINSIC max, min
166* ..
167* .. Executable Statements ..
168*
169* Process 0 reads the input data, broadcasts to other processes and
170* writes needed information to NOUT
171*
172 IF( iam.EQ.0 ) THEN
173*
174* Open file and skip data file header
175*
176 OPEN( nin, file = 'LLT.dat', status = 'OLD' )
177 READ( nin, fmt = * ) summry
178 summry = ' '
179*
180* Read in user-supplied info about machine type, compiler, etc.
181*
182 READ( nin, fmt = 9999 ) usrinfo
183*
184* Read name and unit number for summary output file
185*
186 READ( nin, fmt = * ) summry
187 READ( nin, fmt = * ) nout
188 IF( nout.NE.0 .AND. nout.NE.6 )
189 $ OPEN( nout, file = summry, status = 'UNKNOWN' )
190*
191* Read and check the parameter values for the tests.
192*
193* Get UPLO
194*
195 READ( nin, fmt = * ) uplo
196*
197* Get number of matrices and their dimensions
198*
199 READ( nin, fmt = * ) nmat
200 IF( nmat.LT.1 .OR. nmat.GT.ldnval ) THEN
201 WRITE( nout, fmt = 9994 ) 'N', ldnval
202 GO TO 20
203 END IF
204 READ( nin, fmt = * ) ( nval( i ), i = 1, nmat )
205*
206* Get values of NB
207*
208 READ( nin, fmt = * ) nnb
209 IF( nnb.LT.1 .OR. nnb.GT.ldnbval ) THEN
210 WRITE( nout, fmt = 9994 ) 'NB', ldnbval
211 GO TO 20
212 END IF
213 READ( nin, fmt = * ) ( nbval( i ), i = 1, nnb )
214*
215* Get values of NRHS
216*
217 READ( nin, fmt = * ) nnr
218 IF( nnr.LT.1 .OR. nnr.GT.ldnrval ) THEN
219 WRITE( nout, fmt = 9994 ) 'NRHS', ldnrval
220 GO TO 20
221 END IF
222 READ( nin, fmt = * ) ( nrval( i ), i = 1, nnr )
223*
224* Get values of NBRHS
225*
226 READ( nin, fmt = * ) nnbr
227 IF( nnbr.LT.1 .OR. nnbr.GT.ldnbrval ) THEN
228 WRITE( nout, fmt = 9994 ) 'NBRHS', ldnbrval
229 GO TO 20
230 END IF
231 READ( nin, fmt = * ) ( nbrval( i ), i = 1, nnbr )
232*
233* Get number of grids
234*
235 READ( nin, fmt = * ) ngrids
236 IF( ngrids.LT.1 .OR. ngrids.GT.ldpval ) THEN
237 WRITE( nout, fmt = 9994 ) 'Grids', ldpval
238 GO TO 20
239 ELSE IF( ngrids.GT.ldqval ) THEN
240 WRITE( nout, fmt = 9994 ) 'Grids', ldqval
241 GO TO 20
242 END IF
243*
244* Get values of P and Q
245*
246 READ( nin, fmt = * ) ( pval( i ), i = 1, ngrids )
247 READ( nin, fmt = * ) ( qval( i ), i = 1, ngrids )
248*
249* Get level of checking
250*
251 READ( nin, fmt = * ) thresh
252*
253* Read the flag that indicates whether to test the condition
254* estimation and iterative refinement routines.
255*
256 READ( nin, fmt = * ) est
257*
258* Close input file
259*
260 CLOSE( nin )
261*
262* For pvm only: if virtual machine not set up, allocate it and
263* spawn the correct number of processes.
264*
265 IF( nprocs.LT.1 ) THEN
266 nprocs = 0
267 DO 10 i = 1, ngrids
268 nprocs = max( nprocs, pval( i )*qval( i ) )
269 10 CONTINUE
270 CALL blacs_setup( iam, nprocs )
271 END IF
272*
273* Temporarily define blacs grid to include all processes so
274* information can be broadcast to all processes.
275*
276 CALL blacs_get( -1, 0, ictxt )
277 CALL blacs_gridinit( ictxt, 'Row-major', 1, nprocs )
278*
279* Compute machine epsilon
280*
281 eps = pslamch( ictxt, 'eps' )
282*
283* Pack information arrays and broadcast
284*
285 CALL sgebs2d( ictxt, 'All', ' ', 1, 1, thresh, 1 )
286 work( 1 ) = nmat
287 work( 2 ) = nnb
288 work( 3 ) = nnr
289 work( 4 ) = nnbr
290 work( 5 ) = ngrids
291 IF( lsame( uplo, 'L' ) ) THEN
292 work( 6 ) = 1
293 ELSE
294 work( 6 ) = 2
295 END IF
296 IF( est ) THEN
297 work( 7 ) = 1
298 ELSE
299 work( 7 ) = 0
300 END IF
301 CALL igebs2d( ictxt, 'all', ' ', 7, 1, WORK, 7 )
302*
303 I = 1
304 CALL ICOPY( NMAT, NVAL, 1, WORK( I ), 1 )
305 I = I + NMAT
306 CALL ICOPY( NNB, NBVAL, 1, WORK( I ), 1 )
307 I = I + NNB
308 CALL ICOPY( NNR, NRVAL, 1, WORK( I ), 1 )
309 I = I + NNR
310 CALL ICOPY( NNBR, NBRVAL, 1, WORK( I ), 1 )
311 I = I + NNBR
312 CALL ICOPY( NGRIDS, PVAL, 1, WORK( I ), 1 )
313 I = I + NGRIDS
314 CALL ICOPY( NGRIDS, QVAL, 1, WORK( I ), 1 )
315 I = I + NGRIDS - 1
316 CALL IGEBS2D( ICTXT, 'all', ' ', I, 1, WORK, I )
317*
318* regurgitate input
319*
320 WRITE( NOUT, FMT = 9999 )
321 $ 'scalapack ax=b by llt factorization.'
322 WRITE( NOUT, FMT = 9999 ) USRINFO
323 WRITE( NOUT, FMT = * )
324 WRITE( NOUT, FMT = 9999 )
325 $ 'tests of the parallel '//
326 $ 'complex single precision LLt factorization '//
327 $ 'and solve.'
328 WRITE( NOUT, FMT = 9999 )
329 $ 'The following scaled residual '//
330 $ 'checks will be computed:'
331 WRITE( NOUT, FMT = 9999 )
332 $ ' Solve residual = ||ax - b|| / '//
333 $ '(||x|| * ||a|| * eps * n)'
334 IF( LSAME( UPLO, 'l' ) ) THEN
335 WRITE( NOUT, FMT = 9999 )
336 $ ' factorization residual = ||a - ll''|| /'//
337 $ ' (||a|| * eps * n)'
338 ELSE
339 WRITE( NOUT, FMT = 9999 )
340 $ ' factorization residual = ||a - u''u|| /'//
341 $ ' (||a|| * eps * n)'
342 END IF
343 WRITE( NOUT, FMT = 9999 )
344 $ 'the matrix a is randomly '//
345 $ 'generated for each test.'
346 WRITE( NOUT, FMT = * )
347 WRITE( NOUT, FMT = 9999 )
348 $ 'an explanation of the input/output '//
349 $ 'parameters follows:'
350 WRITE( NOUT, FMT = 9999 )
351 $ 'time : indicates whether wall or '//
352 $ 'cpu time was used.'
353*
354 WRITE( NOUT, FMT = 9999 )
355 $ 'uplo : whether data is stored in ''upper'//
356 $ ''' or ''lower'' portion of array a.'
357 WRITE( NOUT, FMT = 9999 )
358 $ 'n : the number of rows and columns '//
359 $ 'in the matrix a.'
360 WRITE( NOUT, FMT = 9999 )
361 $ 'nb : the size of the square blocks the'//
362 $ ' matrix a is split into.'
363 WRITE( NOUT, FMT = 9999 )
364 $ 'nrhs : the total number of rhs to solve'//
365 $ ' for.'
366 WRITE( NOUT, FMT = 9999 )
367 $ 'nbrhs : the number of rhs to be put on '//
368 $ 'a column of processes before going'
369 WRITE( NOUT, FMT = 9999 )
370 $ ' on to the next column of processes.'
371 WRITE( NOUT, FMT = 9999 )
372 $ 'p : the number of process rows.'
373 WRITE( NOUT, FMT = 9999 )
374 $ 'q : the number of process columns.'
375 WRITE( NOUT, FMT = 9999 )
376 $ 'thresh : If a residual value is less than'//
377 $ ' thresh, check is flagged as passed'
378 WRITE( NOUT, FMT = 9999 )
379 $ 'llt time: time in seconds to factor the'//
380 $ ' matrix'
381 WRITE( NOUT, FMT = 9999 )
382 $ 'sol time: time in seconds to solve the'//
383 $ ' system.'
384 WRITE( NOUT, FMT = 9999 )
385 $ 'mflops : rate of execution for factor '//
386 $ 'and solve.'
387 WRITE( NOUT, FMT = * )
388 WRITE( NOUT, FMT = 9999 )
389 $ 'the following parameter values will be used:'
390 WRITE( NOUT, FMT = 9999 )
391 $ ' uplo : '//UPLO
392 WRITE( NOUT, FMT = 9996 )
393 $ 'n ', ( NVAL(I), I = 1, MIN(NMAT, 10) )
394.GT. IF( NMAT10 )
395 $ WRITE( NOUT, FMT = 9997 ) ( NVAL(I), I = 11, NMAT )
396 WRITE( NOUT, FMT = 9996 )
397 $ 'nb ', ( NBVAL(I), I = 1, MIN(NNB, 10) )
398.GT. IF( NNB10 )
399 $ WRITE( NOUT, FMT = 9997 ) ( NBVAL(I), I = 11, NNB )
400 WRITE( NOUT, FMT = 9996 )
401 $ 'nrhs ', ( NRVAL(I), I = 1, MIN(NNR, 10) )
402.GT. IF( NNR10 )
403 $ WRITE( NOUT, FMT = 9997 ) ( NRVAL(I), I = 11, NNR )
404 WRITE( NOUT, FMT = 9996 )
405 $ 'nbrhs', ( NBRVAL(I), I = 1, MIN(NNBR, 10) )
406.GT. IF( NNBR10 )
407 $ WRITE( NOUT, FMT = 9997 ) ( NBRVAL(I), I = 11, NNBR )
408 WRITE( NOUT, FMT = 9996 )
409 $ 'p ', ( PVAL(I), I = 1, MIN(NGRIDS, 10) )
410.GT. IF( NGRIDS10 )
411 $ WRITE( NOUT, FMT = 9997) ( PVAL(I), I = 11, NGRIDS )
412 WRITE( NOUT, FMT = 9996 )
413 $ 'q ', ( QVAL(I), I = 1, MIN(NGRIDS, 10) )
414.GT. IF( NGRIDS10 )
415 $ WRITE( NOUT, FMT = 9997 ) ( QVAL(I), I = 11, NGRIDS )
416 WRITE( NOUT, FMT = * )
417 WRITE( NOUT, FMT = 9995 ) EPS
418 WRITE( NOUT, FMT = 9998 ) THRESH
419*
420 ELSE
421*
422* If in pvm, must participate setting up virtual machine
423*
424.LT. IF( NPROCS1 )
425 $ CALL BLACS_SETUP( IAM, NPROCS )
426*
427* Temporarily define blacs grid to include all processes so
428* all processes have needed startup information
429*
430 CALL BLACS_GET( -1, 0, ICTXT )
431 CALL BLACS_GRIDINIT( ICTXT, 'row-major', 1, NPROCS )
432*
433* Compute machine epsilon
434*
435 EPS = PSLAMCH( ICTXT, 'eps' )
436*
437 CALL SGEBR2D( ICTXT, 'all', ' ', 1, 1, THRESH, 1, 0, 0 )
438 CALL IGEBR2D( ICTXT, 'all', ' ', 7, 1, WORK, 7, 0, 0 )
439 NMAT = WORK( 1 )
440 NNB = WORK( 2 )
441 NNR = WORK( 3 )
442 NNBR = WORK( 4 )
443 NGRIDS = WORK( 5 )
444.EQ. IF( WORK( 6 )1 ) THEN
445 UPLO = 'l'
446 ELSE
447 UPLO = 'u'
448 END IF
449.EQ. IF( WORK( 7 )1 ) THEN
450 EST = .TRUE.
451 ELSE
452 EST = .FALSE.
453 END IF
454*
455 I = NMAT + NNB + NNR + NNBR + 2*NGRIDS
456 CALL IGEBR2D( ICTXT, 'all', ' ', 1, I, WORK, 1, 0, 0 )
457 I = 1
458 CALL ICOPY( NMAT, WORK( I ), 1, NVAL, 1 )
459 I = I + NMAT
460 CALL ICOPY( NNB, WORK( I ), 1, NBVAL, 1 )
461 I = I + NNB
462 CALL ICOPY( NNR, WORK( I ), 1, NRVAL, 1 )
463 I = I + NNR
464 CALL ICOPY( NNBR, WORK( I ), 1, NBRVAL, 1 )
465 I = I + NNBR
466 CALL ICOPY( NGRIDS, WORK( I ), 1, PVAL, 1 )
467 I = I + NGRIDS
468 CALL ICOPY( NGRIDS, WORK( I ), 1, QVAL, 1 )
469*
470 END IF
471*
472 CALL BLACS_GRIDEXIT( ICTXT )
473*
474 RETURN
475*
476 20 WRITE( NOUT, FMT = 9993 )
477 CLOSE( NIN )
478.NE..AND..NE. IF( NOUT6 NOUT0 )
479 $ CLOSE( NOUT )
480 CALL BLACS_ABORT( ICTXT, 1 )
481 STOP
482*
483 9999 FORMAT( A )
484 9998 FORMAT( 'routines pass computational tests if scaled residual ',
485 $ 'is less than ', G12.5 )
486 9997 FORMAT( ' ', 10I6 )
487 9996 FORMAT( 2X, A5, ': ', 10I6 )
488 9995 FORMAT( 'relative machine precision(eps) is taken to be ',
489 $ E18.6 )
490 9994 FORMAT( ' number of values of ',5a, ' is less than 1 or greater ',
491 $ 'than ', i2 )
492 9993 FORMAT( ' Illegal input in file ',40a,'. Aborting run.' )
493*
494* End of PCLLTINFO
495*
496 END
end diagonal values have been computed in the(sparse) matrix id.SOL
subroutine icopy(n, sx, incx, sy, incy)
ICOPY
Definition icopy.f:75
#define min(a, b)
Definition macros.h:20
#define max(a, b)
Definition macros.h:21
subroutine sgebs2d(contxt, scope, top, m, n, a, lda)
Definition mpi.f:1072
subroutine blacs_gridinit(cntxt, c, nprow, npcol)
Definition mpi.f:745
subroutine sgebr2d(contxt, scope, top, m, n, a, lda)
Definition mpi.f:1113
subroutine blacs_gridexit(cntxt)
Definition mpi.f:762
for(i8=*sizetab-1;i8 >=0;i8--)
subroutine pclltinfo(summry, nout, uplo, nmat, nval, ldnval, nnb, nbval, ldnbval, nnr, nrval, ldnrval, nnbr, nbrval, ldnbrval, ngrids, pval, ldpval, qval, ldqval, thresh, est, work, iam, nprocs)
Definition pclltinfo.f:6
void split(mapping_t *, PORD_INT, PORD_INT, PORD_INT, PORD_INT *, PORD_INT *, FLOAT *, PORD_INT)