SCALAPACK 2.2.2
LAPACK: Linear Algebra PACKage
Loading...
Searching...
No Matches
psseprdriver.f
Go to the documentation of this file.
2*
3* Parallel REAL symmetric eigenproblem test driver for PSSYEVR
4*
5 IMPLICIT NONE
6*
7* The user should modify TOTMEM to indicate the maximum amount of
8* memory in bytes her system has. Remember to leave room in memory
9* for operating system, the BLACS buffer, etc. REALSZ
10* indicates the length in bytes on the given platform for a number,
11* real for SINGLE/DOUBLE PRECISION, and complex for COMPLEX/COMPLEX*16.
12* For example, on a standard system, the length of a
13* REAL is 4, and an integer takes up 4 bytes. Some playing around
14* to discover what the maximum value you can set MEMSIZ to may be
15* required.
16* All arrays used by factorization and solve are allocated out of
17* big array called MEM.
18*
19* TESTS PERFORMED
20* ===============
21*
22* This routine performs tests for combinations of: matrix size, process
23* configuration (nprow and npcol), block size (nb),
24* matrix type, range of eigenvalue (all, by value, by index),
25* and upper vs. lower storage.
26*
27* It returns an error message when heterogeneity is detected.
28*
29* The input file allows multiple requests where each one is
30* of the following sets:
31* matrix sizes: n
32* process configuration triples: nprow, npcol, nb
33* matrix types:
34* eigenvalue requests: all, by value, by position
35* storage (upper vs. lower): uplo
36*
37* TERMS:
38* Request - means a set of tests, which is the cross product of
39* a set of specifications from the input file.
40* Test - one element in the cross product, i.e. a specific input
41* size and type, process configuration, etc.
42*
43* .. Parameters ..
44*
45 INTEGER totmem, realsz, nin
46 parameter( totmem = 100000000, realsz = 4, nin = 11 )
47 INTEGER memsiz
48 parameter( memsiz = totmem / realsz )
49* ..
50* .. Local Scalars ..
51 CHARACTER hetero
52 CHARACTER*80 summry, usrinfo
53 INTEGER context, iam, info, isieee, maxnodes, nnocheck,
54 $ nout, npassed, nprocs, nskipped, ntests
55* ..
56* .. Local Arrays ..
57*
58 INTEGER iseed( 4 )
59 REAL mem( memsiz )
60* ..
61* .. External Functions ..
62 REAL slamch
63 EXTERNAL slamch
64* ..
65* .. External Subroutines ..
66*
67 EXTERNAL blacs_exit, blacs_get, blacs_gridexit,
68 $ blacs_gridinit, blacs_pinfo, blacs_setup,
69 $ igamn2d, pslachkieee, pslasnbt, psseprreq
70* ..
71* .. Executable Statements ..
72*
73* Get starting information
74*
75 CALL blacs_pinfo( iam, nprocs )
76*
77*
78 IF( iam.EQ.0 ) THEN
79*
80* Open file and skip data file header
81*
82 OPEN( unit = nin, file = 'SEPR.dat', status = 'OLD' )
83 READ( nin, fmt = * )summry
84 summry = ' '
85*
86* Read in user-supplied info about machine type, compiler, etc.
87*
88 READ( nin, fmt = 9999 )usrinfo
89*
90* Read name and unit number for summary output file
91*
92 READ( nin, fmt = * )summry
93 READ( nin, fmt = * )nout
94 IF( nout.NE.0 .AND. nout.NE.6 )
95 $ OPEN( nout, file = summry, status = 'UNKNOWN' )
96 READ( nin, fmt = * )maxnodes
97 READ( nin, fmt = * )hetero
98 END IF
99*
100 IF( nprocs.LT.1 ) THEN
101 CALL blacs_setup( iam, maxnodes )
102 nprocs = maxnodes
103 END IF
104*
105 CALL blacs_get( -1, 0, context )
106 CALL blacs_gridinit( context, 'R', 1, nprocs )
107*
108 CALL pslasnbt( isieee )
109*
110 CALL igamn2d( context, 'a', ' ', 1, 1, isieee, 1, 1, 1, -1, -1,
111 $ 0 )
112*
113 IF( ( isieee.NE.0 ) ) THEN
114 IF( iam.EQ.0 ) THEN
115 WRITE( nout, fmt = 9997 )
116 WRITE( nout, fmt = 9996 )
117 WRITE( nout, fmt = 9995 )
118 END IF
119*
120 CALL pslachkieee( isieee, slamch( 'O' ), slamch( 'U' ) )
121*
122 CALL igamn2d( context, 'a', ' ', 1, 1, isieee, 1, 1, 1, -1, -1,
123 $ 0 )
124*
125 IF( isieee.EQ.0 ) THEN
126 GO TO 20
127 END IF
128*
129 IF( iam.EQ.0 ) THEN
130 WRITE( nout, fmt = 9986 )
131 END IF
132*
133 END IF
134*
135 IF( iam.EQ.0 ) THEN
136 WRITE( nout, fmt = 9999 )
137 $ 'Test ScaLAPACK symmetric eigendecomposition routine.'
138 WRITE( nout, fmt = 9999 )usrinfo
139 WRITE( nout, fmt = 9999 )' '
140 WRITE( nout, fmt = 9999 )'Running tests of the parallel ' //
141 $ 'symmetric eigenvalue routine: PSSYEVR.'
142 WRITE( nout, fmt = 9999 )'The following scaled residual ' //
143 $ 'checks will be computed:'
144 WRITE( nout, fmt = 9999 )' ||AQ - QL|| ' //
145 $ '/ ((abstol + ||A|| * eps) * N)'
146 WRITE( nout, fmt = 9999 )' ||Q^T*Q - I|| ' // '/ (N * eps)'
147 WRITE( nout, fmt = 9999 )
148 WRITE( nout, fmt = 9999 )'An explanation of the ' //
149 $ 'input/output parameters follows:'
150 WRITE( nout, fmt = 9999 )'RESULT : passed; or ' //
151 $ 'an indication of which eigen request test failed'
152 WRITE( nout, fmt = 9999 )
153 $ 'N : The number of rows and columns ' //
154 $ 'of the matrix A.'
155 WRITE( nout, fmt = 9999 )
156 $ 'P : The number of process rows.'
157 WRITE( nout, fmt = 9999 )
158 $ 'Q : The number of process columns.'
159 WRITE( nout, fmt = 9999 )
160 $ 'NB : The size of the square blocks' //
161 $ ' the matrix A is split into.'
162 WRITE( nout, fmt = 9999 )
163 $ 'THRESH : If a residual value is less ' //
164 $ 'than THRESH, RESULT = PASSED.'
165 WRITE( nout, fmt = 9999 )
166 $ 'TYP : matrix type (see PSSEPRTST).'
167 WRITE( nout, fmt = 9999 )'SUB : Subtests (Y/N).'
168 WRITE( nout, fmt = 9999 )'WALL : Wallclock time.'
169 WRITE( nout, fmt = 9999 )'CPU : CPU time.'
170 WRITE( nout, fmt = 9999 )'CHK : ||AQ - QL|| ' //
171 $ '/ ((abstol + ||A|| * eps) * N)'
172 WRITE( nout, fmt = 9999 )'QTQ : ||Q^T*Q - I||/ (N * eps)'
173 WRITE( nout, fmt = 9999 )
174 $ ' : when the adjusted QTQ norm exceeds THRESH',
175 $ ' it is printed,'
176 WRITE( nout, fmt = 9999 )
177 $ ' otherwise the true QTQ norm is printed.'
178 WRITE( nout, fmt = 9999 )
179 $ ' : If more than one test is done, CHK and QTQ '
180 WRITE( nout, fmt = 9999 )
181 $ ' are the max over all eigentests performed.'
182 WRITE( nout, fmt = 9999 )
183 $ 'TEST : EVR - testing PSSYEVR'
184 WRITE( nout, fmt = 9999 )' '
185 END IF
186*
187 ntests = 0
188 npassed = 0
189 nskipped = 0
190 nnocheck = 0
191*
192 IF( iam.EQ.0 ) THEN
193 WRITE( nout, fmt = 9979 )
194 WRITE( nout, fmt = 9978 )
195 END IF
196*
197 10 CONTINUE
198*
199 iseed( 1 ) = 139
200 iseed( 2 ) = 1139
201 iseed( 3 ) = 2139
202 iseed( 4 ) = 3139
203*
204 CALL psseprreq( hetero, nin, mem, memsiz, nout, iseed, ntests,
205 $ nskipped, nnocheck, npassed, info )
206 IF( info.EQ.0 )
207 $ GO TO 10
208*
209 IF( iam.EQ.0 ) THEN
210 WRITE( nout, fmt = 9985 )ntests
211 WRITE( nout, fmt = 9984 )npassed
212 WRITE( nout, fmt = 9983 )nnocheck
213 WRITE( nout, fmt = 9982 )nskipped
214 WRITE( nout, fmt = 9981 )ntests - npassed - nskipped -
215 $ nnocheck
216 WRITE( nout, fmt = * )
217 WRITE( nout, fmt = * )
218 WRITE( nout, fmt = 9980 )
219 END IF
220*
221* Uncomment this line on SUN systems to avoid the useless print out
222*
223c CALL IEEE_FLAGS( 'clear', 'exception', 'underflow', ' ')
224*
225 20 CONTINUE
226 IF( iam.EQ.0 ) THEN
227 CLOSE ( nin )
228 IF( nout.NE.6 .AND. nout.NE.0 )
229 $ CLOSE ( nout )
230 END IF
231*
232 CALL blacs_gridexit( context )
233*
234 CALL blacs_exit( 0 )
235 stop
236*
237 9999 FORMAT( a )
238 9997 FORMAT( 'Check if overflow is handled in ieee default manner.' )
239 9996 FORMAT( 'If this is the last output you see, you should assume')
240 9995 FORMAT( 'that overflow caused a floating point exception.' )
241*
242 9986 FORMAT( 'Test ok. The system appears to handle ieee overflow.' )
243*
244 9985 FORMAT( 'Finished ', i6, ' tests, with the following results:' )
245 9984 FORMAT( i5, ' tests completed and passed residual checks.' )
246 9983 FORMAT( i5, ' tests completed without checking.' )
247 9982 FORMAT( i5, ' tests skipped for lack of memory.' )
248 9981 FORMAT( i5, ' tests completed and failed.' )
249 9980 FORMAT( 'END OF TESTS.' )
250 9979 FORMAT( ' N NB P Q TYP SUB WALL CPU ',
251 $ ' CHK QTQ CHECK TEST' )
252 9978 FORMAT( ' ----- --- --- --- --- --- -------- --------',
253 $ ' --------- --------- ----- ----' )
254*
255* End of PSSEPRDRIVER
256*
257 END
258
259
260
program psseprdriver
Definition psseprdriver.f:1
subroutine psseprreq(hetero, nin, mem, memsize, nout, iseed, ntests, nskipped, nnocheck, npassed, info)
Definition psseprreq.f:3
real function slamch(cmach)
Definition tools.f:867