OpenRadioss 2025.1.11
OpenRadioss project
Loading...
Searching...
No Matches
pchrdinfo.f File Reference

Go to the source code of this file.

Functions/Subroutines

subroutine pchrdinfo (summry, nout, nmat, nval, nvlo, nvhi, ldnval, nnb, nbval, ldnbval, ngrids, pval, ldpval, qval, ldqval, thresh, work, iam, nprocs)

Function/Subroutine Documentation

◆ pchrdinfo()

subroutine pchrdinfo ( character*( * ) summry,
integer nout,
integer nmat,
integer, dimension( ldnval ) nval,
integer, dimension( ldnval ) nvlo,
integer, dimension( ldnval ) nvhi,
integer ldnval,
integer nnb,
integer, dimension( ldnbval ) nbval,
integer ldnbval,
integer ngrids,
integer, dimension( ldpval ) pval,
integer ldpval,
integer, dimension( ldqval ) qval,
integer ldqval,
real thresh,
integer, dimension( * ) work,
integer iam,
integer nprocs )

Definition at line 1 of file pchrdinfo.f.

5*
6* -- ScaLAPACK routine (version 1.7) --
7* University of Tennessee, Knoxville, Oak Ridge National Laboratory,
8* and University of California, Berkeley.
9* May 1, 1997
10*
11* .. Scalar Arguments ..
12 INTEGER IAM, LDNBVAL, LDNVAL, LDPVAL, LDQVAL,
13 $ NGRIDS, NMAT, NNB, NOUT, NPROCS
14 REAL THRESH
15* ..
16* .. Array Arguments ..
17 CHARACTER*( * ) SUMMRY
18 INTEGER NBVAL( LDNBVAL ), NVAL( LDNVAL ),
19 $ NVHI( LDNVAL ), NVLO( LDNVAL ),
20 $ PVAL( LDPVAL ), QVAL( LDQVAL ), WORK( * )
21* ..
22*
23* Purpose
24* =======
25*
26* PCHRDINFO get the needed startup information for the Hessenberg
27* reduction tests and transmits it to all processes.
28*
29* Arguments
30* =========
31*
32* SUMMRY (global output) CHARACTER*(*)
33* Name of output (summary) file (if any). Only defined for
34* process 0.
35*
36* NOUT (global output) INTEGER
37* The unit number for output file. NOUT = 6, output to screen,
38* NOUT = 0, output to stderr. Only defined for process 0.
39*
40* NMAT (global output) INTEGER
41* The number of different values that can be used for
42* N, IHI & ILO.
43*
44* NVAL (global output) INTEGER array, dimension (LDNVAL)
45* The values of N (number of rows & columns in matrix).
46*
47* NVLO (global output) INTEGER array, dimension (LDNVAL)
48* The values of ILO.
49*
50* NVHI (global output) INTEGER array, dimension (LDNVAL)
51* The values of IHI.
52*
53* LDNVAL (global input) INTEGER
54* The maximum number of different values that can be used for
55* N, ILO and IHI. LDNVAL >= NMAT.
56*
57* NNB (global output) INTEGER
58* The number of different values that can be used for NB.
59*
60* NBVAL (global output) INTEGER array, dimension (LDNBVAL)
61* The values of NB (blocksize) to run the code with.
62*
63* LDNBVAL (global input) INTEGER
64* The maximum number of different values that can be used for
65* NB, LDNBVAL >= NNB.
66*
67* NGRIDS (global output) INTEGER
68* The number of different values that can be used for P & Q.
69*
70* PVAL (global output) INTEGER array, dimension (LDPVAL)
71* The values of P (number of process rows) to run the code
72* with.
73*
74* LDPVAL (global input) INTEGER
75* The maximum number of different values that can be used for
76* P, LDPVAL >= NGRIDS.
77*
78* QVAL (global output) INTEGER array, dimension (LDQVAL)
79* The values of Q (number of process columns) to run the code
80* with.
81*
82* LDQVAL (global input) INTEGER
83* The maximum number of different values that can be used for
84* Q, LDQVAL >= NGRIDS.
85*
86* THRESH (global output) REAL
87* Indicates what error checks shall be run and printed out:
88* = 0 : Perform no error checking
89* > 0 : report all residuals greater than THRESH.
90*
91* WORK (local workspace) INTEGER array, dimension >=
92* 3*LDNVAL+LDNBVAL+2*LDPVAL. Used to pack all input arrays
93* in order to send info in one message.
94*
95* IAM (local input) INTEGER
96* My process number.
97*
98* NPROCS (global input) INTEGER
99* The total number of processes.
100*
101* Note
102* ====
103*
104* For packing the information we assumed that the length in bytes of an
105* integer is equal to the length in bytes of a real single precision.
106*
107* =====================================================================
108*
109* .. Parameters ..
110 INTEGER BLOCK_CYCLIC_2D, CSRC_, CTXT_, DLEN_, DTYPE_,
111 $ LLD_, MB_, M_, NB_, N_, RSRC_
112 parameter( block_cyclic_2d = 1, dlen_ = 9, dtype_ = 1,
113 $ ctxt_ = 2, m_ = 3, n_ = 4, mb_ = 5, nb_ = 6,
114 $ rsrc_ = 7, csrc_ = 8, lld_ = 9 )
115 INTEGER NIN
116 parameter( nin = 11 )
117* ..
118* .. Local Scalars ..
119 CHARACTER*79 USRINFO
120 INTEGER I, ICTXT
121 REAL EPS
122* ..
123* .. External Subroutines ..
124 EXTERNAL blacs_abort, blacs_get, blacs_gridexit,
125 $ blacs_gridinit, blacs_setup, icopy, igebr2d,
126 $ igebs2d, sgebr2d, sgebs2d
127* ..
128* .. External Functions ..
129 REAL PSLAMCH
130 EXTERNAL pslamch
131* ..
132* .. Intrinsic Functions ..
133 INTRINSIC max, min
134* ..
135* .. Executable Statements ..
136*
137* Process 0 reads the input data, broadcasts to other processes and
138* writes needed information to NOUT
139*
140 IF( iam.EQ.0 ) THEN
141*
142* Open file and skip data file header
143*
144 OPEN( unit = nin, file = 'HRD.dat', status = 'OLD' )
145 READ( nin, fmt = * )summry
146 summry = ' '
147*
148* Read in user-supplied info about machine type, compiler, etc.
149*
150 READ( nin, fmt = * ) usrinfo
151*
152* Read name and unit number for summary output file
153*
154 READ( nin, fmt = * ) summry
155 READ( nin, fmt = * ) nout
156 IF( nout.NE.0 .AND. nout.NE.6 )
157 $ OPEN( unit = nout, file = summry, status = 'UNKNOWN' )
158*
159* Read and check the parameter values for the tests.
160*
161* Get number of matrices
162*
163 READ( nin, fmt = * ) nmat
164 IF( nmat.LT.1. .OR. nmat.GT.ldnval ) THEN
165 WRITE( nout, fmt = 9997 ) 'N', ldnval
166 GO TO 20
167 END IF
168*
169* Get values of N, ILO, IHI
170*
171 READ( nin, fmt = * ) ( nval( i ), i = 1, nmat )
172 READ( nin, fmt = * ) ( nvlo( i ), i = 1, nmat )
173 READ( nin, fmt = * ) ( nvhi( i ), i = 1, nmat )
174*
175* Get values of NB
176*
177 READ( nin, fmt = * ) nnb
178 IF( nnb.LT.1 .OR. nnb.GT.ldnbval ) THEN
179 WRITE( nout, fmt = 9997 ) 'NB', ldnbval
180 GO TO 20
181 END IF
182 READ( nin, fmt = * ) ( nbval( i ), i = 1, nnb )
183*
184* Get number of grids
185*
186 READ( nin, fmt = * ) ngrids
187 IF( ngrids.LT.1 .OR. ngrids.GT.ldpval ) THEN
188 WRITE( nout, fmt = 9997 ) 'Grids', ldpval
189 GO TO 20
190 ELSE IF( ngrids.GT.ldqval ) THEN
191 WRITE( nout, fmt = 9997 ) 'Grids', ldqval
192 GO TO 20
193 END IF
194*
195* Get values of P and Q
196*
197 READ( nin, fmt = * ) ( pval( i ), i = 1, ngrids )
198 READ( nin, fmt = * ) ( qval( i ), i = 1, ngrids )
199*
200* Get level of checking
201*
202 READ( nin, fmt = * ) thresh
203*
204* Close input file
205*
206 CLOSE( nin )
207*
208* For pvm only: if virtual machine not set up, allocate it and
209* spawn the correct number of processes.
210*
211 IF( nprocs.LT.1 ) THEN
212 nprocs = 0
213 DO 10 i = 1, ngrids
214 nprocs = max( nprocs, pval( i )*qval( i ) )
215 10 CONTINUE
216 CALL blacs_setup( iam, nprocs )
217 END IF
218*
219* Temporarily define blacs grid to include all processes so
220* information can be broadcast to all processes
221*
222 CALL blacs_get( -1, 0, ictxt )
223 CALL blacs_gridinit( ictxt, 'Row-major', 1, nprocs )
224*
225* Compute machine epsilon
226*
227 eps = pslamch( ictxt, 'eps' )
228*
229* Pack information arrays and broadcast
230*
231 CALL sgebs2d( ictxt, 'All', ' ', 1, 1, thresh, 1 )
232*
233 work( 1 ) = nmat
234 work( 2 ) = nnb
235 work( 3 ) = ngrids
236 CALL igebs2d( ictxt, 'All', ' ', 1, 3, work, 1 )
237*
238 i = 1
239 CALL icopy( nmat, nval, 1, work( i ), 1 )
240 i = i + nmat
241 CALL icopy( nmat, nvlo, 1, work( i ), 1 )
242 i = i + nmat
243 CALL icopy( nmat, nvhi, 1, work( i ), 1 )
244 i = i + nmat
245 CALL icopy( nnb, nbval, 1, work( i ), 1 )
246 i = i + nnb
247 CALL icopy( ngrids, pval, 1, work( i ), 1 )
248 i = i + ngrids
249 CALL icopy( ngrids, qval, 1, work( i ), 1 )
250 i = i + ngrids -1
251 CALL igebs2d( ictxt, 'All', ' ', 1, i, work, 1 )
252*
253* regurgitate input
254*
255 WRITE( nout, fmt = 9999 )
256 $ 'ScaLAPACK Reduction routine to Hessenberg form.'
257 WRITE( nout, fmt = 9999 ) usrinfo
258 WRITE( nout, fmt = * )
259 WRITE( nout, fmt = 9999 )
260 $ 'Tests of the parallel '//
261 $ 'complex single precision Hessenberg '
262 WRITE( nout, fmt = 9999 ) 'reduction routines.'
263 WRITE( nout, fmt = 9999 )
264 $ 'The following scaled residual '//
265 $ 'checks will be computed:'
266 WRITE( nout, fmt = 9999 )
267 $ ' ||A - Q H Q''|| / (||A|| * eps * N)'
268 WRITE( nout, fmt = 9999 )
269 $ 'the matrix a is randomly '//
270 $ 'generated for each test.'
271 WRITE( NOUT, FMT = * )
272 WRITE( NOUT, FMT = 9999 )
273 $ 'an explanation of the input/output '//
274 $ 'parameters follows:'
275 WRITE( NOUT, FMT = 9999 )
276 $ 'time : indicates whether wall or '//
277 $ 'cpu time was used.'
278 WRITE( NOUT, FMT = 9999 )
279 $ 'n : the number of rows and columns '//
280 $ 'of the matrix a.'
281 WRITE( NOUT, FMT = 9999 )
282 $ 'nb : the size of the square blocks'//
283 $ ' the matrix a is split into.'
284 WRITE( NOUT, FMT = 9999 )
285 $ ' on to the next column of processes.'
286 WRITE( NOUT, FMT = 9999 )
287 $ 'p : the number of process rows.'
288 WRITE( NOUT, FMT = 9999 )
289 $ 'q : the number of process columns.'
290 WRITE( NOUT, FMT = 9999 )
291 $ 'hrd time : time in seconds to compute hrd '
292 WRITE( NOUT, FMT = 9999 )
293 $ 'mflops : rate of execution for hrd ' //
294 $ 'reduction.'
295 WRITE( NOUT, FMT = * )
296 WRITE( NOUT, FMT = 9999 )
297 $ 'the following parameter values will be used:'
298 WRITE( NOUT, FMT = 9995 )
299 $ 'n ', ( NVAL( I ), I = 1, MIN( NMAT, 10 ) )
300.GT. IF( NMAT10 )
301 $ WRITE( NOUT, FMT = 9994 ) ( NVAL( I ), I = 11, NMAT )
302 WRITE( NOUT, FMT = 9995 )
303 $ 'ilo ', ( NVLO( I ), I = 1, MIN( NMAT, 10 ) )
304.GT. IF( NMAT10 )
305 $ WRITE( NOUT, FMT = 9994 ) ( NVLO( I ), I = 11, NMAT )
306 WRITE( NOUT, FMT = 9995 )
307 $ 'ihi ', ( NVHI( I ), I = 1, MIN( NMAT, 10 ) )
308.GT. IF( NMAT10 )
309 $ WRITE( NOUT, FMT = 9994 ) ( NVHI( I ), I = 11, NMAT )
310 WRITE( NOUT, FMT = 9995 )
311 $ 'nb ', ( NBVAL( I ), I = 1, MIN( NNB, 10 ) )
312.GT. IF( NNB10 )
313 $ WRITE( NOUT, FMT = 9994 ) ( NBVAL( I ), I = 11, NNB )
314 WRITE( NOUT, FMT = 9995 )
315 $ 'p ', ( PVAL( I ), I = 1, MIN( NGRIDS, 10 ) )
316.GT. IF( NGRIDS10 )
317 $ WRITE( NOUT, FMT = 9994 ) ( PVAL( I ), I = 11, NGRIDS )
318 WRITE( NOUT, FMT = 9995 )
319 $ 'q ', ( QVAL( I ), I = 1, MIN( NGRIDS, 10 ) )
320.GT. IF( NGRIDS10 )
321 $ WRITE( NOUT, FMT = 9994 ) ( QVAL( I ), I = 11, NGRIDS )
322 WRITE( NOUT, FMT = * )
323 WRITE( NOUT, FMT = 9996 ) EPS
324 WRITE( NOUT, FMT = 9993 ) THRESH
325*
326 ELSE
327*
328* If in pvm, must participate setting up virtual machine
329*
330.LT. IF( NPROCS1 )
331 $ CALL BLACS_SETUP( IAM, NPROCS )
332*
333* Temporarily define blacs grid to include all processes so
334* all processes have needed startup information
335*
336 CALL BLACS_GET( -1, 0, ICTXT )
337 CALL BLACS_GRIDINIT( ICTXT, 'row-major', 1, NPROCS )
338*
339* Compute machine epsilon
340*
341 EPS = PSLAMCH( ICTXT, 'eps' )
342*
343 CALL SGEBR2D( ICTXT, 'all', ' ', 1, 1, THRESH, 1, 0, 0 )
344 CALL IGEBR2D( ICTXT, 'all', ' ', 1, 3, WORK, 1, 0, 0 )
345 NMAT = WORK( 1 )
346 NNB = WORK( 2 )
347 NGRIDS = WORK( 3 )
348*
349 I = 3*NMAT + NNB + 2*NGRIDS
350 CALL IGEBR2D( ICTXT, 'all', ' ', 1, I, WORK, 1, 0, 0 )
351*
352 I = 1
353 CALL ICOPY( NMAT, WORK( I ), 1, NVAL, 1 )
354 I = I + NMAT
355 CALL ICOPY( NMAT, WORK( I ), 1, NVLO, 1 )
356 I = I + NMAT
357 CALL ICOPY( NMAT, WORK( I ), 1, NVHI, 1 )
358 I = I + NMAT
359 CALL ICOPY( NNB, WORK( I ), 1, NBVAL, 1 )
360 I = I + NNB
361 CALL ICOPY( NGRIDS, WORK( I ), 1, PVAL, 1 )
362 I = I + NGRIDS
363 CALL ICOPY( NGRIDS, WORK( I ), 1, QVAL, 1 )
364*
365 END IF
366*
367 CALL BLACS_GRIDEXIT( ICTXT )
368*
369 RETURN
370*
371 20 CONTINUE
372 WRITE( NOUT, FMT = 9998 )
373 CLOSE( NIN )
374.NE..AND..NE. IF( NOUT6 NOUT0 )
375 $ CLOSE( NOUT )
376 CALL BLACS_ABORT( ICTXT, 1 )
377*
378 STOP
379*
380 9999 FORMAT( A )
381 9998 FORMAT( ' illegal input in file ', 40A, '. aborting run.' )
382 9997 FORMAT( ' number of values of ', 5A,
383 $ ' is less than 1 or greater ', 'than ', I2 )
384 9996 FORMAT( 'relative machine precision(eps) is taken to be ',
385 $ E18.6 )
386 9995 FORMAT( 2X, A5, ': ', 10I6 )
387 9994 FORMAT( ' ', 10I6 )
388 9993 FORMAT( 'routines pass computational tests if scaled residual is',
389 $ ' less than ', G14.7 )
390*
391* End of PCHRDINFO
392*
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--)
real function pslamch(ictxt, cmach)
Definition pcblastst.f:7455
void split(mapping_t *, PORD_INT, PORD_INT, PORD_INT, PORD_INT *, PORD_INT *, FLOAT *, PORD_INT)