root / src / lapack / util / dlamch.f @ 7
Historique | Voir | Annoter | Télécharger (23,96 ko)
1 | 1 | pfleura2 | DOUBLE PRECISION FUNCTION DLAMCH( CMACH ) |
---|---|---|---|
2 | 1 | pfleura2 | * |
3 | 1 | pfleura2 | * -- LAPACK auxiliary routine (version 3.2) -- |
4 | 1 | pfleura2 | * Univ. of Tennessee, Univ. of California Berkeley and NAG Ltd.. |
5 | 1 | pfleura2 | * November 2006 |
6 | 1 | pfleura2 | * |
7 | 1 | pfleura2 | * .. Scalar Arguments .. |
8 | 1 | pfleura2 | CHARACTER CMACH |
9 | 1 | pfleura2 | * .. |
10 | 1 | pfleura2 | * |
11 | 1 | pfleura2 | * Purpose |
12 | 1 | pfleura2 | * ======= |
13 | 1 | pfleura2 | * |
14 | 1 | pfleura2 | * DLAMCH determines double precision machine parameters. |
15 | 1 | pfleura2 | * |
16 | 1 | pfleura2 | * Arguments |
17 | 1 | pfleura2 | * ========= |
18 | 1 | pfleura2 | * |
19 | 1 | pfleura2 | * CMACH (input) CHARACTER*1 |
20 | 1 | pfleura2 | * Specifies the value to be returned by DLAMCH: |
21 | 1 | pfleura2 | * = 'E' or 'e', DLAMCH := eps |
22 | 1 | pfleura2 | * = 'S' or 's , DLAMCH := sfmin |
23 | 1 | pfleura2 | * = 'B' or 'b', DLAMCH := base |
24 | 1 | pfleura2 | * = 'P' or 'p', DLAMCH := eps*base |
25 | 1 | pfleura2 | * = 'N' or 'n', DLAMCH := t |
26 | 1 | pfleura2 | * = 'R' or 'r', DLAMCH := rnd |
27 | 1 | pfleura2 | * = 'M' or 'm', DLAMCH := emin |
28 | 1 | pfleura2 | * = 'U' or 'u', DLAMCH := rmin |
29 | 1 | pfleura2 | * = 'L' or 'l', DLAMCH := emax |
30 | 1 | pfleura2 | * = 'O' or 'o', DLAMCH := rmax |
31 | 1 | pfleura2 | * |
32 | 1 | pfleura2 | * where |
33 | 1 | pfleura2 | * |
34 | 1 | pfleura2 | * eps = relative machine precision |
35 | 1 | pfleura2 | * sfmin = safe minimum, such that 1/sfmin does not overflow |
36 | 1 | pfleura2 | * base = base of the machine |
37 | 1 | pfleura2 | * prec = eps*base |
38 | 1 | pfleura2 | * t = number of (base) digits in the mantissa |
39 | 1 | pfleura2 | * rnd = 1.0 when rounding occurs in addition, 0.0 otherwise |
40 | 1 | pfleura2 | * emin = minimum exponent before (gradual) underflow |
41 | 1 | pfleura2 | * rmin = underflow threshold - base**(emin-1) |
42 | 1 | pfleura2 | * emax = largest exponent before overflow |
43 | 1 | pfleura2 | * rmax = overflow threshold - (base**emax)*(1-eps) |
44 | 1 | pfleura2 | * |
45 | 1 | pfleura2 | * ===================================================================== |
46 | 1 | pfleura2 | * |
47 | 1 | pfleura2 | * .. Parameters .. |
48 | 1 | pfleura2 | DOUBLE PRECISION ONE, ZERO |
49 | 1 | pfleura2 | PARAMETER ( ONE = 1.0D+0, ZERO = 0.0D+0 ) |
50 | 1 | pfleura2 | * .. |
51 | 1 | pfleura2 | * .. Local Scalars .. |
52 | 1 | pfleura2 | LOGICAL FIRST, LRND |
53 | 1 | pfleura2 | INTEGER BETA, IMAX, IMIN, IT |
54 | 1 | pfleura2 | DOUBLE PRECISION BASE, EMAX, EMIN, EPS, PREC, RMACH, RMAX, RMIN, |
55 | 1 | pfleura2 | $ RND, SFMIN, SMALL, T |
56 | 1 | pfleura2 | * .. |
57 | 1 | pfleura2 | * .. External Functions .. |
58 | 1 | pfleura2 | LOGICAL LSAME |
59 | 1 | pfleura2 | EXTERNAL LSAME |
60 | 1 | pfleura2 | * .. |
61 | 1 | pfleura2 | * .. External Subroutines .. |
62 | 1 | pfleura2 | EXTERNAL DLAMC2 |
63 | 1 | pfleura2 | * .. |
64 | 1 | pfleura2 | * .. Save statement .. |
65 | 1 | pfleura2 | SAVE FIRST, EPS, SFMIN, BASE, T, RND, EMIN, RMIN, |
66 | 1 | pfleura2 | $ EMAX, RMAX, PREC |
67 | 1 | pfleura2 | * .. |
68 | 1 | pfleura2 | * .. Data statements .. |
69 | 1 | pfleura2 | DATA FIRST / .TRUE. / |
70 | 1 | pfleura2 | * .. |
71 | 1 | pfleura2 | * .. Executable Statements .. |
72 | 1 | pfleura2 | * |
73 | 1 | pfleura2 | IF( FIRST ) THEN |
74 | 1 | pfleura2 | CALL DLAMC2( BETA, IT, LRND, EPS, IMIN, RMIN, IMAX, RMAX ) |
75 | 1 | pfleura2 | BASE = BETA |
76 | 1 | pfleura2 | T = IT |
77 | 1 | pfleura2 | IF( LRND ) THEN |
78 | 1 | pfleura2 | RND = ONE |
79 | 1 | pfleura2 | EPS = ( BASE**( 1-IT ) ) / 2 |
80 | 1 | pfleura2 | ELSE |
81 | 1 | pfleura2 | RND = ZERO |
82 | 1 | pfleura2 | EPS = BASE**( 1-IT ) |
83 | 1 | pfleura2 | END IF |
84 | 1 | pfleura2 | PREC = EPS*BASE |
85 | 1 | pfleura2 | EMIN = IMIN |
86 | 1 | pfleura2 | EMAX = IMAX |
87 | 1 | pfleura2 | SFMIN = RMIN |
88 | 1 | pfleura2 | SMALL = ONE / RMAX |
89 | 1 | pfleura2 | IF( SMALL.GE.SFMIN ) THEN |
90 | 1 | pfleura2 | * |
91 | 1 | pfleura2 | * Use SMALL plus a bit, to avoid the possibility of rounding |
92 | 1 | pfleura2 | * causing overflow when computing 1/sfmin. |
93 | 1 | pfleura2 | * |
94 | 1 | pfleura2 | SFMIN = SMALL*( ONE+EPS ) |
95 | 1 | pfleura2 | END IF |
96 | 1 | pfleura2 | END IF |
97 | 1 | pfleura2 | * |
98 | 1 | pfleura2 | IF( LSAME( CMACH, 'E' ) ) THEN |
99 | 1 | pfleura2 | RMACH = EPS |
100 | 1 | pfleura2 | ELSE IF( LSAME( CMACH, 'S' ) ) THEN |
101 | 1 | pfleura2 | RMACH = SFMIN |
102 | 1 | pfleura2 | ELSE IF( LSAME( CMACH, 'B' ) ) THEN |
103 | 1 | pfleura2 | RMACH = BASE |
104 | 1 | pfleura2 | ELSE IF( LSAME( CMACH, 'P' ) ) THEN |
105 | 1 | pfleura2 | RMACH = PREC |
106 | 1 | pfleura2 | ELSE IF( LSAME( CMACH, 'N' ) ) THEN |
107 | 1 | pfleura2 | RMACH = T |
108 | 1 | pfleura2 | ELSE IF( LSAME( CMACH, 'R' ) ) THEN |
109 | 1 | pfleura2 | RMACH = RND |
110 | 1 | pfleura2 | ELSE IF( LSAME( CMACH, 'M' ) ) THEN |
111 | 1 | pfleura2 | RMACH = EMIN |
112 | 1 | pfleura2 | ELSE IF( LSAME( CMACH, 'U' ) ) THEN |
113 | 1 | pfleura2 | RMACH = RMIN |
114 | 1 | pfleura2 | ELSE IF( LSAME( CMACH, 'L' ) ) THEN |
115 | 1 | pfleura2 | RMACH = EMAX |
116 | 1 | pfleura2 | ELSE IF( LSAME( CMACH, 'O' ) ) THEN |
117 | 1 | pfleura2 | RMACH = RMAX |
118 | 1 | pfleura2 | END IF |
119 | 1 | pfleura2 | * |
120 | 1 | pfleura2 | DLAMCH = RMACH |
121 | 1 | pfleura2 | FIRST = .FALSE. |
122 | 1 | pfleura2 | RETURN |
123 | 1 | pfleura2 | * |
124 | 1 | pfleura2 | * End of DLAMCH |
125 | 1 | pfleura2 | * |
126 | 1 | pfleura2 | END |
127 | 1 | pfleura2 | * |
128 | 1 | pfleura2 | ************************************************************************ |
129 | 1 | pfleura2 | * |
130 | 1 | pfleura2 | SUBROUTINE DLAMC1( BETA, T, RND, IEEE1 ) |
131 | 1 | pfleura2 | * |
132 | 1 | pfleura2 | * -- LAPACK auxiliary routine (version 3.2) -- |
133 | 1 | pfleura2 | * Univ. of Tennessee, Univ. of California Berkeley and NAG Ltd.. |
134 | 1 | pfleura2 | * November 2006 |
135 | 1 | pfleura2 | * |
136 | 1 | pfleura2 | * .. Scalar Arguments .. |
137 | 1 | pfleura2 | LOGICAL IEEE1, RND |
138 | 1 | pfleura2 | INTEGER BETA, T |
139 | 1 | pfleura2 | * .. |
140 | 1 | pfleura2 | * |
141 | 1 | pfleura2 | * Purpose |
142 | 1 | pfleura2 | * ======= |
143 | 1 | pfleura2 | * |
144 | 1 | pfleura2 | * DLAMC1 determines the machine parameters given by BETA, T, RND, and |
145 | 1 | pfleura2 | * IEEE1. |
146 | 1 | pfleura2 | * |
147 | 1 | pfleura2 | * Arguments |
148 | 1 | pfleura2 | * ========= |
149 | 1 | pfleura2 | * |
150 | 1 | pfleura2 | * BETA (output) INTEGER |
151 | 1 | pfleura2 | * The base of the machine. |
152 | 1 | pfleura2 | * |
153 | 1 | pfleura2 | * T (output) INTEGER |
154 | 1 | pfleura2 | * The number of ( BETA ) digits in the mantissa. |
155 | 1 | pfleura2 | * |
156 | 1 | pfleura2 | * RND (output) LOGICAL |
157 | 1 | pfleura2 | * Specifies whether proper rounding ( RND = .TRUE. ) or |
158 | 1 | pfleura2 | * chopping ( RND = .FALSE. ) occurs in addition. This may not |
159 | 1 | pfleura2 | * be a reliable guide to the way in which the machine performs |
160 | 1 | pfleura2 | * its arithmetic. |
161 | 1 | pfleura2 | * |
162 | 1 | pfleura2 | * IEEE1 (output) LOGICAL |
163 | 1 | pfleura2 | * Specifies whether rounding appears to be done in the IEEE |
164 | 1 | pfleura2 | * 'round to nearest' style. |
165 | 1 | pfleura2 | * |
166 | 1 | pfleura2 | * Further Details |
167 | 1 | pfleura2 | * =============== |
168 | 1 | pfleura2 | * |
169 | 1 | pfleura2 | * The routine is based on the routine ENVRON by Malcolm and |
170 | 1 | pfleura2 | * incorporates suggestions by Gentleman and Marovich. See |
171 | 1 | pfleura2 | * |
172 | 1 | pfleura2 | * Malcolm M. A. (1972) Algorithms to reveal properties of |
173 | 1 | pfleura2 | * floating-point arithmetic. Comms. of the ACM, 15, 949-951. |
174 | 1 | pfleura2 | * |
175 | 1 | pfleura2 | * Gentleman W. M. and Marovich S. B. (1974) More on algorithms |
176 | 1 | pfleura2 | * that reveal properties of floating point arithmetic units. |
177 | 1 | pfleura2 | * Comms. of the ACM, 17, 276-277. |
178 | 1 | pfleura2 | * |
179 | 1 | pfleura2 | * ===================================================================== |
180 | 1 | pfleura2 | * |
181 | 1 | pfleura2 | * .. Local Scalars .. |
182 | 1 | pfleura2 | LOGICAL FIRST, LIEEE1, LRND |
183 | 1 | pfleura2 | INTEGER LBETA, LT |
184 | 1 | pfleura2 | DOUBLE PRECISION A, B, C, F, ONE, QTR, SAVEC, T1, T2 |
185 | 1 | pfleura2 | * .. |
186 | 1 | pfleura2 | * .. External Functions .. |
187 | 1 | pfleura2 | DOUBLE PRECISION DLAMC3 |
188 | 1 | pfleura2 | EXTERNAL DLAMC3 |
189 | 1 | pfleura2 | * .. |
190 | 1 | pfleura2 | * .. Save statement .. |
191 | 1 | pfleura2 | SAVE FIRST, LIEEE1, LBETA, LRND, LT |
192 | 1 | pfleura2 | * .. |
193 | 1 | pfleura2 | * .. Data statements .. |
194 | 1 | pfleura2 | DATA FIRST / .TRUE. / |
195 | 1 | pfleura2 | * .. |
196 | 1 | pfleura2 | * .. Executable Statements .. |
197 | 1 | pfleura2 | * |
198 | 1 | pfleura2 | IF( FIRST ) THEN |
199 | 1 | pfleura2 | ONE = 1 |
200 | 1 | pfleura2 | * |
201 | 1 | pfleura2 | * LBETA, LIEEE1, LT and LRND are the local values of BETA, |
202 | 1 | pfleura2 | * IEEE1, T and RND. |
203 | 1 | pfleura2 | * |
204 | 1 | pfleura2 | * Throughout this routine we use the function DLAMC3 to ensure |
205 | 1 | pfleura2 | * that relevant values are stored and not held in registers, or |
206 | 1 | pfleura2 | * are not affected by optimizers. |
207 | 1 | pfleura2 | * |
208 | 1 | pfleura2 | * Compute a = 2.0**m with the smallest positive integer m such |
209 | 1 | pfleura2 | * that |
210 | 1 | pfleura2 | * |
211 | 1 | pfleura2 | * fl( a + 1.0 ) = a. |
212 | 1 | pfleura2 | * |
213 | 1 | pfleura2 | A = 1 |
214 | 1 | pfleura2 | C = 1 |
215 | 1 | pfleura2 | * |
216 | 1 | pfleura2 | *+ WHILE( C.EQ.ONE )LOOP |
217 | 1 | pfleura2 | 10 CONTINUE |
218 | 1 | pfleura2 | IF( C.EQ.ONE ) THEN |
219 | 1 | pfleura2 | A = 2*A |
220 | 1 | pfleura2 | C = DLAMC3( A, ONE ) |
221 | 1 | pfleura2 | C = DLAMC3( C, -A ) |
222 | 1 | pfleura2 | GO TO 10 |
223 | 1 | pfleura2 | END IF |
224 | 1 | pfleura2 | *+ END WHILE |
225 | 1 | pfleura2 | * |
226 | 1 | pfleura2 | * Now compute b = 2.0**m with the smallest positive integer m |
227 | 1 | pfleura2 | * such that |
228 | 1 | pfleura2 | * |
229 | 1 | pfleura2 | * fl( a + b ) .gt. a. |
230 | 1 | pfleura2 | * |
231 | 1 | pfleura2 | B = 1 |
232 | 1 | pfleura2 | C = DLAMC3( A, B ) |
233 | 1 | pfleura2 | * |
234 | 1 | pfleura2 | *+ WHILE( C.EQ.A )LOOP |
235 | 1 | pfleura2 | 20 CONTINUE |
236 | 1 | pfleura2 | IF( C.EQ.A ) THEN |
237 | 1 | pfleura2 | B = 2*B |
238 | 1 | pfleura2 | C = DLAMC3( A, B ) |
239 | 1 | pfleura2 | GO TO 20 |
240 | 1 | pfleura2 | END IF |
241 | 1 | pfleura2 | *+ END WHILE |
242 | 1 | pfleura2 | * |
243 | 1 | pfleura2 | * Now compute the base. a and c are neighbouring floating point |
244 | 1 | pfleura2 | * numbers in the interval ( beta**t, beta**( t + 1 ) ) and so |
245 | 1 | pfleura2 | * their difference is beta. Adding 0.25 to c is to ensure that it |
246 | 1 | pfleura2 | * is truncated to beta and not ( beta - 1 ). |
247 | 1 | pfleura2 | * |
248 | 1 | pfleura2 | QTR = ONE / 4 |
249 | 1 | pfleura2 | SAVEC = C |
250 | 1 | pfleura2 | C = DLAMC3( C, -A ) |
251 | 1 | pfleura2 | LBETA = C + QTR |
252 | 1 | pfleura2 | * |
253 | 1 | pfleura2 | * Now determine whether rounding or chopping occurs, by adding a |
254 | 1 | pfleura2 | * bit less than beta/2 and a bit more than beta/2 to a. |
255 | 1 | pfleura2 | * |
256 | 1 | pfleura2 | B = LBETA |
257 | 1 | pfleura2 | F = DLAMC3( B / 2, -B / 100 ) |
258 | 1 | pfleura2 | C = DLAMC3( F, A ) |
259 | 1 | pfleura2 | IF( C.EQ.A ) THEN |
260 | 1 | pfleura2 | LRND = .TRUE. |
261 | 1 | pfleura2 | ELSE |
262 | 1 | pfleura2 | LRND = .FALSE. |
263 | 1 | pfleura2 | END IF |
264 | 1 | pfleura2 | F = DLAMC3( B / 2, B / 100 ) |
265 | 1 | pfleura2 | C = DLAMC3( F, A ) |
266 | 1 | pfleura2 | IF( ( LRND ) .AND. ( C.EQ.A ) ) |
267 | 1 | pfleura2 | $ LRND = .FALSE. |
268 | 1 | pfleura2 | * |
269 | 1 | pfleura2 | * Try and decide whether rounding is done in the IEEE 'round to |
270 | 1 | pfleura2 | * nearest' style. B/2 is half a unit in the last place of the two |
271 | 1 | pfleura2 | * numbers A and SAVEC. Furthermore, A is even, i.e. has last bit |
272 | 1 | pfleura2 | * zero, and SAVEC is odd. Thus adding B/2 to A should not change |
273 | 1 | pfleura2 | * A, but adding B/2 to SAVEC should change SAVEC. |
274 | 1 | pfleura2 | * |
275 | 1 | pfleura2 | T1 = DLAMC3( B / 2, A ) |
276 | 1 | pfleura2 | T2 = DLAMC3( B / 2, SAVEC ) |
277 | 1 | pfleura2 | LIEEE1 = ( T1.EQ.A ) .AND. ( T2.GT.SAVEC ) .AND. LRND |
278 | 1 | pfleura2 | * |
279 | 1 | pfleura2 | * Now find the mantissa, t. It should be the integer part of |
280 | 1 | pfleura2 | * log to the base beta of a, however it is safer to determine t |
281 | 1 | pfleura2 | * by powering. So we find t as the smallest positive integer for |
282 | 1 | pfleura2 | * which |
283 | 1 | pfleura2 | * |
284 | 1 | pfleura2 | * fl( beta**t + 1.0 ) = 1.0. |
285 | 1 | pfleura2 | * |
286 | 1 | pfleura2 | LT = 0 |
287 | 1 | pfleura2 | A = 1 |
288 | 1 | pfleura2 | C = 1 |
289 | 1 | pfleura2 | * |
290 | 1 | pfleura2 | *+ WHILE( C.EQ.ONE )LOOP |
291 | 1 | pfleura2 | 30 CONTINUE |
292 | 1 | pfleura2 | IF( C.EQ.ONE ) THEN |
293 | 1 | pfleura2 | LT = LT + 1 |
294 | 1 | pfleura2 | A = A*LBETA |
295 | 1 | pfleura2 | C = DLAMC3( A, ONE ) |
296 | 1 | pfleura2 | C = DLAMC3( C, -A ) |
297 | 1 | pfleura2 | GO TO 30 |
298 | 1 | pfleura2 | END IF |
299 | 1 | pfleura2 | *+ END WHILE |
300 | 1 | pfleura2 | * |
301 | 1 | pfleura2 | END IF |
302 | 1 | pfleura2 | * |
303 | 1 | pfleura2 | BETA = LBETA |
304 | 1 | pfleura2 | T = LT |
305 | 1 | pfleura2 | RND = LRND |
306 | 1 | pfleura2 | IEEE1 = LIEEE1 |
307 | 1 | pfleura2 | FIRST = .FALSE. |
308 | 1 | pfleura2 | RETURN |
309 | 1 | pfleura2 | * |
310 | 1 | pfleura2 | * End of DLAMC1 |
311 | 1 | pfleura2 | * |
312 | 1 | pfleura2 | END |
313 | 1 | pfleura2 | * |
314 | 1 | pfleura2 | ************************************************************************ |
315 | 1 | pfleura2 | * |
316 | 1 | pfleura2 | SUBROUTINE DLAMC2( BETA, T, RND, EPS, EMIN, RMIN, EMAX, RMAX ) |
317 | 1 | pfleura2 | * |
318 | 1 | pfleura2 | * -- LAPACK auxiliary routine (version 3.2) -- |
319 | 1 | pfleura2 | * Univ. of Tennessee, Univ. of California Berkeley and NAG Ltd.. |
320 | 1 | pfleura2 | * November 2006 |
321 | 1 | pfleura2 | * |
322 | 1 | pfleura2 | * .. Scalar Arguments .. |
323 | 1 | pfleura2 | LOGICAL RND |
324 | 1 | pfleura2 | INTEGER BETA, EMAX, EMIN, T |
325 | 1 | pfleura2 | DOUBLE PRECISION EPS, RMAX, RMIN |
326 | 1 | pfleura2 | * .. |
327 | 1 | pfleura2 | * |
328 | 1 | pfleura2 | * Purpose |
329 | 1 | pfleura2 | * ======= |
330 | 1 | pfleura2 | * |
331 | 1 | pfleura2 | * DLAMC2 determines the machine parameters specified in its argument |
332 | 1 | pfleura2 | * list. |
333 | 1 | pfleura2 | * |
334 | 1 | pfleura2 | * Arguments |
335 | 1 | pfleura2 | * ========= |
336 | 1 | pfleura2 | * |
337 | 1 | pfleura2 | * BETA (output) INTEGER |
338 | 1 | pfleura2 | * The base of the machine. |
339 | 1 | pfleura2 | * |
340 | 1 | pfleura2 | * T (output) INTEGER |
341 | 1 | pfleura2 | * The number of ( BETA ) digits in the mantissa. |
342 | 1 | pfleura2 | * |
343 | 1 | pfleura2 | * RND (output) LOGICAL |
344 | 1 | pfleura2 | * Specifies whether proper rounding ( RND = .TRUE. ) or |
345 | 1 | pfleura2 | * chopping ( RND = .FALSE. ) occurs in addition. This may not |
346 | 1 | pfleura2 | * be a reliable guide to the way in which the machine performs |
347 | 1 | pfleura2 | * its arithmetic. |
348 | 1 | pfleura2 | * |
349 | 1 | pfleura2 | * EPS (output) DOUBLE PRECISION |
350 | 1 | pfleura2 | * The smallest positive number such that |
351 | 1 | pfleura2 | * |
352 | 1 | pfleura2 | * fl( 1.0 - EPS ) .LT. 1.0, |
353 | 1 | pfleura2 | * |
354 | 1 | pfleura2 | * where fl denotes the computed value. |
355 | 1 | pfleura2 | * |
356 | 1 | pfleura2 | * EMIN (output) INTEGER |
357 | 1 | pfleura2 | * The minimum exponent before (gradual) underflow occurs. |
358 | 1 | pfleura2 | * |
359 | 1 | pfleura2 | * RMIN (output) DOUBLE PRECISION |
360 | 1 | pfleura2 | * The smallest normalized number for the machine, given by |
361 | 1 | pfleura2 | * BASE**( EMIN - 1 ), where BASE is the floating point value |
362 | 1 | pfleura2 | * of BETA. |
363 | 1 | pfleura2 | * |
364 | 1 | pfleura2 | * EMAX (output) INTEGER |
365 | 1 | pfleura2 | * The maximum exponent before overflow occurs. |
366 | 1 | pfleura2 | * |
367 | 1 | pfleura2 | * RMAX (output) DOUBLE PRECISION |
368 | 1 | pfleura2 | * The largest positive number for the machine, given by |
369 | 1 | pfleura2 | * BASE**EMAX * ( 1 - EPS ), where BASE is the floating point |
370 | 1 | pfleura2 | * value of BETA. |
371 | 1 | pfleura2 | * |
372 | 1 | pfleura2 | * Further Details |
373 | 1 | pfleura2 | * =============== |
374 | 1 | pfleura2 | * |
375 | 1 | pfleura2 | * The computation of EPS is based on a routine PARANOIA by |
376 | 1 | pfleura2 | * W. Kahan of the University of California at Berkeley. |
377 | 1 | pfleura2 | * |
378 | 1 | pfleura2 | * ===================================================================== |
379 | 1 | pfleura2 | * |
380 | 1 | pfleura2 | * .. Local Scalars .. |
381 | 1 | pfleura2 | LOGICAL FIRST, IEEE, IWARN, LIEEE1, LRND |
382 | 1 | pfleura2 | INTEGER GNMIN, GPMIN, I, LBETA, LEMAX, LEMIN, LT, |
383 | 1 | pfleura2 | $ NGNMIN, NGPMIN |
384 | 1 | pfleura2 | DOUBLE PRECISION A, B, C, HALF, LEPS, LRMAX, LRMIN, ONE, RBASE, |
385 | 1 | pfleura2 | $ SIXTH, SMALL, THIRD, TWO, ZERO |
386 | 1 | pfleura2 | * .. |
387 | 1 | pfleura2 | * .. External Functions .. |
388 | 1 | pfleura2 | DOUBLE PRECISION DLAMC3 |
389 | 1 | pfleura2 | EXTERNAL DLAMC3 |
390 | 1 | pfleura2 | * .. |
391 | 1 | pfleura2 | * .. External Subroutines .. |
392 | 1 | pfleura2 | EXTERNAL DLAMC1, DLAMC4, DLAMC5 |
393 | 1 | pfleura2 | * .. |
394 | 1 | pfleura2 | * .. Intrinsic Functions .. |
395 | 1 | pfleura2 | INTRINSIC ABS, MAX, MIN |
396 | 1 | pfleura2 | * .. |
397 | 1 | pfleura2 | * .. Save statement .. |
398 | 1 | pfleura2 | SAVE FIRST, IWARN, LBETA, LEMAX, LEMIN, LEPS, LRMAX, |
399 | 1 | pfleura2 | $ LRMIN, LT |
400 | 1 | pfleura2 | * .. |
401 | 1 | pfleura2 | * .. Data statements .. |
402 | 1 | pfleura2 | DATA FIRST / .TRUE. / , IWARN / .FALSE. / |
403 | 1 | pfleura2 | * .. |
404 | 1 | pfleura2 | * .. Executable Statements .. |
405 | 1 | pfleura2 | * |
406 | 1 | pfleura2 | IF( FIRST ) THEN |
407 | 1 | pfleura2 | ZERO = 0 |
408 | 1 | pfleura2 | ONE = 1 |
409 | 1 | pfleura2 | TWO = 2 |
410 | 1 | pfleura2 | * |
411 | 1 | pfleura2 | * LBETA, LT, LRND, LEPS, LEMIN and LRMIN are the local values of |
412 | 1 | pfleura2 | * BETA, T, RND, EPS, EMIN and RMIN. |
413 | 1 | pfleura2 | * |
414 | 1 | pfleura2 | * Throughout this routine we use the function DLAMC3 to ensure |
415 | 1 | pfleura2 | * that relevant values are stored and not held in registers, or |
416 | 1 | pfleura2 | * are not affected by optimizers. |
417 | 1 | pfleura2 | * |
418 | 1 | pfleura2 | * DLAMC1 returns the parameters LBETA, LT, LRND and LIEEE1. |
419 | 1 | pfleura2 | * |
420 | 1 | pfleura2 | CALL DLAMC1( LBETA, LT, LRND, LIEEE1 ) |
421 | 1 | pfleura2 | * |
422 | 1 | pfleura2 | * Start to find EPS. |
423 | 1 | pfleura2 | * |
424 | 1 | pfleura2 | B = LBETA |
425 | 1 | pfleura2 | A = B**( -LT ) |
426 | 1 | pfleura2 | LEPS = A |
427 | 1 | pfleura2 | * |
428 | 1 | pfleura2 | * Try some tricks to see whether or not this is the correct EPS. |
429 | 1 | pfleura2 | * |
430 | 1 | pfleura2 | B = TWO / 3 |
431 | 1 | pfleura2 | HALF = ONE / 2 |
432 | 1 | pfleura2 | SIXTH = DLAMC3( B, -HALF ) |
433 | 1 | pfleura2 | THIRD = DLAMC3( SIXTH, SIXTH ) |
434 | 1 | pfleura2 | B = DLAMC3( THIRD, -HALF ) |
435 | 1 | pfleura2 | B = DLAMC3( B, SIXTH ) |
436 | 1 | pfleura2 | B = ABS( B ) |
437 | 1 | pfleura2 | IF( B.LT.LEPS ) |
438 | 1 | pfleura2 | $ B = LEPS |
439 | 1 | pfleura2 | * |
440 | 1 | pfleura2 | LEPS = 1 |
441 | 1 | pfleura2 | * |
442 | 1 | pfleura2 | *+ WHILE( ( LEPS.GT.B ).AND.( B.GT.ZERO ) )LOOP |
443 | 1 | pfleura2 | 10 CONTINUE |
444 | 1 | pfleura2 | IF( ( LEPS.GT.B ) .AND. ( B.GT.ZERO ) ) THEN |
445 | 1 | pfleura2 | LEPS = B |
446 | 1 | pfleura2 | C = DLAMC3( HALF*LEPS, ( TWO**5 )*( LEPS**2 ) ) |
447 | 1 | pfleura2 | C = DLAMC3( HALF, -C ) |
448 | 1 | pfleura2 | B = DLAMC3( HALF, C ) |
449 | 1 | pfleura2 | C = DLAMC3( HALF, -B ) |
450 | 1 | pfleura2 | B = DLAMC3( HALF, C ) |
451 | 1 | pfleura2 | GO TO 10 |
452 | 1 | pfleura2 | END IF |
453 | 1 | pfleura2 | *+ END WHILE |
454 | 1 | pfleura2 | * |
455 | 1 | pfleura2 | IF( A.LT.LEPS ) |
456 | 1 | pfleura2 | $ LEPS = A |
457 | 1 | pfleura2 | * |
458 | 1 | pfleura2 | * Computation of EPS complete. |
459 | 1 | pfleura2 | * |
460 | 1 | pfleura2 | * Now find EMIN. Let A = + or - 1, and + or - (1 + BASE**(-3)). |
461 | 1 | pfleura2 | * Keep dividing A by BETA until (gradual) underflow occurs. This |
462 | 1 | pfleura2 | * is detected when we cannot recover the previous A. |
463 | 1 | pfleura2 | * |
464 | 1 | pfleura2 | RBASE = ONE / LBETA |
465 | 1 | pfleura2 | SMALL = ONE |
466 | 1 | pfleura2 | DO 20 I = 1, 3 |
467 | 1 | pfleura2 | SMALL = DLAMC3( SMALL*RBASE, ZERO ) |
468 | 1 | pfleura2 | 20 CONTINUE |
469 | 1 | pfleura2 | A = DLAMC3( ONE, SMALL ) |
470 | 1 | pfleura2 | CALL DLAMC4( NGPMIN, ONE, LBETA ) |
471 | 1 | pfleura2 | CALL DLAMC4( NGNMIN, -ONE, LBETA ) |
472 | 1 | pfleura2 | CALL DLAMC4( GPMIN, A, LBETA ) |
473 | 1 | pfleura2 | CALL DLAMC4( GNMIN, -A, LBETA ) |
474 | 1 | pfleura2 | IEEE = .FALSE. |
475 | 1 | pfleura2 | * |
476 | 1 | pfleura2 | IF( ( NGPMIN.EQ.NGNMIN ) .AND. ( GPMIN.EQ.GNMIN ) ) THEN |
477 | 1 | pfleura2 | IF( NGPMIN.EQ.GPMIN ) THEN |
478 | 1 | pfleura2 | LEMIN = NGPMIN |
479 | 1 | pfleura2 | * ( Non twos-complement machines, no gradual underflow; |
480 | 1 | pfleura2 | * e.g., VAX ) |
481 | 1 | pfleura2 | ELSE IF( ( GPMIN-NGPMIN ).EQ.3 ) THEN |
482 | 1 | pfleura2 | LEMIN = NGPMIN - 1 + LT |
483 | 1 | pfleura2 | IEEE = .TRUE. |
484 | 1 | pfleura2 | * ( Non twos-complement machines, with gradual underflow; |
485 | 1 | pfleura2 | * e.g., IEEE standard followers ) |
486 | 1 | pfleura2 | ELSE |
487 | 1 | pfleura2 | LEMIN = MIN( NGPMIN, GPMIN ) |
488 | 1 | pfleura2 | * ( A guess; no known machine ) |
489 | 1 | pfleura2 | IWARN = .TRUE. |
490 | 1 | pfleura2 | END IF |
491 | 1 | pfleura2 | * |
492 | 1 | pfleura2 | ELSE IF( ( NGPMIN.EQ.GPMIN ) .AND. ( NGNMIN.EQ.GNMIN ) ) THEN |
493 | 1 | pfleura2 | IF( ABS( NGPMIN-NGNMIN ).EQ.1 ) THEN |
494 | 1 | pfleura2 | LEMIN = MAX( NGPMIN, NGNMIN ) |
495 | 1 | pfleura2 | * ( Twos-complement machines, no gradual underflow; |
496 | 1 | pfleura2 | * e.g., CYBER 205 ) |
497 | 1 | pfleura2 | ELSE |
498 | 1 | pfleura2 | LEMIN = MIN( NGPMIN, NGNMIN ) |
499 | 1 | pfleura2 | * ( A guess; no known machine ) |
500 | 1 | pfleura2 | IWARN = .TRUE. |
501 | 1 | pfleura2 | END IF |
502 | 1 | pfleura2 | * |
503 | 1 | pfleura2 | ELSE IF( ( ABS( NGPMIN-NGNMIN ).EQ.1 ) .AND. |
504 | 1 | pfleura2 | $ ( GPMIN.EQ.GNMIN ) ) THEN |
505 | 1 | pfleura2 | IF( ( GPMIN-MIN( NGPMIN, NGNMIN ) ).EQ.3 ) THEN |
506 | 1 | pfleura2 | LEMIN = MAX( NGPMIN, NGNMIN ) - 1 + LT |
507 | 1 | pfleura2 | * ( Twos-complement machines with gradual underflow; |
508 | 1 | pfleura2 | * no known machine ) |
509 | 1 | pfleura2 | ELSE |
510 | 1 | pfleura2 | LEMIN = MIN( NGPMIN, NGNMIN ) |
511 | 1 | pfleura2 | * ( A guess; no known machine ) |
512 | 1 | pfleura2 | IWARN = .TRUE. |
513 | 1 | pfleura2 | END IF |
514 | 1 | pfleura2 | * |
515 | 1 | pfleura2 | ELSE |
516 | 1 | pfleura2 | LEMIN = MIN( NGPMIN, NGNMIN, GPMIN, GNMIN ) |
517 | 1 | pfleura2 | * ( A guess; no known machine ) |
518 | 1 | pfleura2 | IWARN = .TRUE. |
519 | 1 | pfleura2 | END IF |
520 | 1 | pfleura2 | FIRST = .FALSE. |
521 | 1 | pfleura2 | *** |
522 | 1 | pfleura2 | * Comment out this if block if EMIN is ok |
523 | 1 | pfleura2 | IF( IWARN ) THEN |
524 | 1 | pfleura2 | FIRST = .TRUE. |
525 | 1 | pfleura2 | WRITE( 6, FMT = 9999 )LEMIN |
526 | 1 | pfleura2 | END IF |
527 | 1 | pfleura2 | *** |
528 | 1 | pfleura2 | * |
529 | 1 | pfleura2 | * Assume IEEE arithmetic if we found denormalised numbers above, |
530 | 1 | pfleura2 | * or if arithmetic seems to round in the IEEE style, determined |
531 | 1 | pfleura2 | * in routine DLAMC1. A true IEEE machine should have both things |
532 | 1 | pfleura2 | * true; however, faulty machines may have one or the other. |
533 | 1 | pfleura2 | * |
534 | 1 | pfleura2 | IEEE = IEEE .OR. LIEEE1 |
535 | 1 | pfleura2 | * |
536 | 1 | pfleura2 | * Compute RMIN by successive division by BETA. We could compute |
537 | 1 | pfleura2 | * RMIN as BASE**( EMIN - 1 ), but some machines underflow during |
538 | 1 | pfleura2 | * this computation. |
539 | 1 | pfleura2 | * |
540 | 1 | pfleura2 | LRMIN = 1 |
541 | 1 | pfleura2 | DO 30 I = 1, 1 - LEMIN |
542 | 1 | pfleura2 | LRMIN = DLAMC3( LRMIN*RBASE, ZERO ) |
543 | 1 | pfleura2 | 30 CONTINUE |
544 | 1 | pfleura2 | * |
545 | 1 | pfleura2 | * Finally, call DLAMC5 to compute EMAX and RMAX. |
546 | 1 | pfleura2 | * |
547 | 1 | pfleura2 | CALL DLAMC5( LBETA, LT, LEMIN, IEEE, LEMAX, LRMAX ) |
548 | 1 | pfleura2 | END IF |
549 | 1 | pfleura2 | * |
550 | 1 | pfleura2 | BETA = LBETA |
551 | 1 | pfleura2 | T = LT |
552 | 1 | pfleura2 | RND = LRND |
553 | 1 | pfleura2 | EPS = LEPS |
554 | 1 | pfleura2 | EMIN = LEMIN |
555 | 1 | pfleura2 | RMIN = LRMIN |
556 | 1 | pfleura2 | EMAX = LEMAX |
557 | 1 | pfleura2 | RMAX = LRMAX |
558 | 1 | pfleura2 | * |
559 | 1 | pfleura2 | RETURN |
560 | 1 | pfleura2 | * |
561 | 1 | pfleura2 | 9999 FORMAT( / / ' WARNING. The value EMIN may be incorrect:-', |
562 | 1 | pfleura2 | $ ' EMIN = ', I8, / |
563 | 1 | pfleura2 | $ ' If, after inspection, the value EMIN looks', |
564 | 1 | pfleura2 | $ ' acceptable please comment out ', |
565 | 1 | pfleura2 | $ / ' the IF block as marked within the code of routine', |
566 | 1 | pfleura2 | $ ' DLAMC2,', / ' otherwise supply EMIN explicitly.', / ) |
567 | 1 | pfleura2 | * |
568 | 1 | pfleura2 | * End of DLAMC2 |
569 | 1 | pfleura2 | * |
570 | 1 | pfleura2 | END |
571 | 1 | pfleura2 | * |
572 | 1 | pfleura2 | ************************************************************************ |
573 | 1 | pfleura2 | * |
574 | 1 | pfleura2 | DOUBLE PRECISION FUNCTION DLAMC3( A, B ) |
575 | 1 | pfleura2 | * |
576 | 1 | pfleura2 | * -- LAPACK auxiliary routine (version 3.2) -- |
577 | 1 | pfleura2 | * Univ. of Tennessee, Univ. of California Berkeley and NAG Ltd.. |
578 | 1 | pfleura2 | * November 2006 |
579 | 1 | pfleura2 | * |
580 | 1 | pfleura2 | * .. Scalar Arguments .. |
581 | 1 | pfleura2 | DOUBLE PRECISION A, B |
582 | 1 | pfleura2 | * .. |
583 | 1 | pfleura2 | * |
584 | 1 | pfleura2 | * Purpose |
585 | 1 | pfleura2 | * ======= |
586 | 1 | pfleura2 | * |
587 | 1 | pfleura2 | * DLAMC3 is intended to force A and B to be stored prior to doing |
588 | 1 | pfleura2 | * the addition of A and B , for use in situations where optimizers |
589 | 1 | pfleura2 | * might hold one of these in a register. |
590 | 1 | pfleura2 | * |
591 | 1 | pfleura2 | * Arguments |
592 | 1 | pfleura2 | * ========= |
593 | 1 | pfleura2 | * |
594 | 1 | pfleura2 | * A (input) DOUBLE PRECISION |
595 | 1 | pfleura2 | * B (input) DOUBLE PRECISION |
596 | 1 | pfleura2 | * The values A and B. |
597 | 1 | pfleura2 | * |
598 | 1 | pfleura2 | * ===================================================================== |
599 | 1 | pfleura2 | * |
600 | 1 | pfleura2 | * .. Executable Statements .. |
601 | 1 | pfleura2 | * |
602 | 1 | pfleura2 | DLAMC3 = A + B |
603 | 1 | pfleura2 | * |
604 | 1 | pfleura2 | RETURN |
605 | 1 | pfleura2 | * |
606 | 1 | pfleura2 | * End of DLAMC3 |
607 | 1 | pfleura2 | * |
608 | 1 | pfleura2 | END |
609 | 1 | pfleura2 | * |
610 | 1 | pfleura2 | ************************************************************************ |
611 | 1 | pfleura2 | * |
612 | 1 | pfleura2 | SUBROUTINE DLAMC4( EMIN, START, BASE ) |
613 | 1 | pfleura2 | * |
614 | 1 | pfleura2 | * -- LAPACK auxiliary routine (version 3.2) -- |
615 | 1 | pfleura2 | * Univ. of Tennessee, Univ. of California Berkeley and NAG Ltd.. |
616 | 1 | pfleura2 | * November 2006 |
617 | 1 | pfleura2 | * |
618 | 1 | pfleura2 | * .. Scalar Arguments .. |
619 | 1 | pfleura2 | INTEGER BASE, EMIN |
620 | 1 | pfleura2 | DOUBLE PRECISION START |
621 | 1 | pfleura2 | * .. |
622 | 1 | pfleura2 | * |
623 | 1 | pfleura2 | * Purpose |
624 | 1 | pfleura2 | * ======= |
625 | 1 | pfleura2 | * |
626 | 1 | pfleura2 | * DLAMC4 is a service routine for DLAMC2. |
627 | 1 | pfleura2 | * |
628 | 1 | pfleura2 | * Arguments |
629 | 1 | pfleura2 | * ========= |
630 | 1 | pfleura2 | * |
631 | 1 | pfleura2 | * EMIN (output) INTEGER |
632 | 1 | pfleura2 | * The minimum exponent before (gradual) underflow, computed by |
633 | 1 | pfleura2 | * setting A = START and dividing by BASE until the previous A |
634 | 1 | pfleura2 | * can not be recovered. |
635 | 1 | pfleura2 | * |
636 | 1 | pfleura2 | * START (input) DOUBLE PRECISION |
637 | 1 | pfleura2 | * The starting point for determining EMIN. |
638 | 1 | pfleura2 | * |
639 | 1 | pfleura2 | * BASE (input) INTEGER |
640 | 1 | pfleura2 | * The base of the machine. |
641 | 1 | pfleura2 | * |
642 | 1 | pfleura2 | * ===================================================================== |
643 | 1 | pfleura2 | * |
644 | 1 | pfleura2 | * .. Local Scalars .. |
645 | 1 | pfleura2 | INTEGER I |
646 | 1 | pfleura2 | DOUBLE PRECISION A, B1, B2, C1, C2, D1, D2, ONE, RBASE, ZERO |
647 | 1 | pfleura2 | * .. |
648 | 1 | pfleura2 | * .. External Functions .. |
649 | 1 | pfleura2 | DOUBLE PRECISION DLAMC3 |
650 | 1 | pfleura2 | EXTERNAL DLAMC3 |
651 | 1 | pfleura2 | * .. |
652 | 1 | pfleura2 | * .. Executable Statements .. |
653 | 1 | pfleura2 | * |
654 | 1 | pfleura2 | A = START |
655 | 1 | pfleura2 | ONE = 1 |
656 | 1 | pfleura2 | RBASE = ONE / BASE |
657 | 1 | pfleura2 | ZERO = 0 |
658 | 1 | pfleura2 | EMIN = 1 |
659 | 1 | pfleura2 | B1 = DLAMC3( A*RBASE, ZERO ) |
660 | 1 | pfleura2 | C1 = A |
661 | 1 | pfleura2 | C2 = A |
662 | 1 | pfleura2 | D1 = A |
663 | 1 | pfleura2 | D2 = A |
664 | 1 | pfleura2 | *+ WHILE( ( C1.EQ.A ).AND.( C2.EQ.A ).AND. |
665 | 1 | pfleura2 | * $ ( D1.EQ.A ).AND.( D2.EQ.A ) )LOOP |
666 | 1 | pfleura2 | 10 CONTINUE |
667 | 1 | pfleura2 | IF( ( C1.EQ.A ) .AND. ( C2.EQ.A ) .AND. ( D1.EQ.A ) .AND. |
668 | 1 | pfleura2 | $ ( D2.EQ.A ) ) THEN |
669 | 1 | pfleura2 | EMIN = EMIN - 1 |
670 | 1 | pfleura2 | A = B1 |
671 | 1 | pfleura2 | B1 = DLAMC3( A / BASE, ZERO ) |
672 | 1 | pfleura2 | C1 = DLAMC3( B1*BASE, ZERO ) |
673 | 1 | pfleura2 | D1 = ZERO |
674 | 1 | pfleura2 | DO 20 I = 1, BASE |
675 | 1 | pfleura2 | D1 = D1 + B1 |
676 | 1 | pfleura2 | 20 CONTINUE |
677 | 1 | pfleura2 | B2 = DLAMC3( A*RBASE, ZERO ) |
678 | 1 | pfleura2 | C2 = DLAMC3( B2 / RBASE, ZERO ) |
679 | 1 | pfleura2 | D2 = ZERO |
680 | 1 | pfleura2 | DO 30 I = 1, BASE |
681 | 1 | pfleura2 | D2 = D2 + B2 |
682 | 1 | pfleura2 | 30 CONTINUE |
683 | 1 | pfleura2 | GO TO 10 |
684 | 1 | pfleura2 | END IF |
685 | 1 | pfleura2 | *+ END WHILE |
686 | 1 | pfleura2 | * |
687 | 1 | pfleura2 | RETURN |
688 | 1 | pfleura2 | * |
689 | 1 | pfleura2 | * End of DLAMC4 |
690 | 1 | pfleura2 | * |
691 | 1 | pfleura2 | END |
692 | 1 | pfleura2 | * |
693 | 1 | pfleura2 | ************************************************************************ |
694 | 1 | pfleura2 | * |
695 | 1 | pfleura2 | SUBROUTINE DLAMC5( BETA, P, EMIN, IEEE, EMAX, RMAX ) |
696 | 1 | pfleura2 | * |
697 | 1 | pfleura2 | * -- LAPACK auxiliary routine (version 3.2) -- |
698 | 1 | pfleura2 | * Univ. of Tennessee, Univ. of California Berkeley and NAG Ltd.. |
699 | 1 | pfleura2 | * November 2006 |
700 | 1 | pfleura2 | * |
701 | 1 | pfleura2 | * .. Scalar Arguments .. |
702 | 1 | pfleura2 | LOGICAL IEEE |
703 | 1 | pfleura2 | INTEGER BETA, EMAX, EMIN, P |
704 | 1 | pfleura2 | DOUBLE PRECISION RMAX |
705 | 1 | pfleura2 | * .. |
706 | 1 | pfleura2 | * |
707 | 1 | pfleura2 | * Purpose |
708 | 1 | pfleura2 | * ======= |
709 | 1 | pfleura2 | * |
710 | 1 | pfleura2 | * DLAMC5 attempts to compute RMAX, the largest machine floating-point |
711 | 1 | pfleura2 | * number, without overflow. It assumes that EMAX + abs(EMIN) sum |
712 | 1 | pfleura2 | * approximately to a power of 2. It will fail on machines where this |
713 | 1 | pfleura2 | * assumption does not hold, for example, the Cyber 205 (EMIN = -28625, |
714 | 1 | pfleura2 | * EMAX = 28718). It will also fail if the value supplied for EMIN is |
715 | 1 | pfleura2 | * too large (i.e. too close to zero), probably with overflow. |
716 | 1 | pfleura2 | * |
717 | 1 | pfleura2 | * Arguments |
718 | 1 | pfleura2 | * ========= |
719 | 1 | pfleura2 | * |
720 | 1 | pfleura2 | * BETA (input) INTEGER |
721 | 1 | pfleura2 | * The base of floating-point arithmetic. |
722 | 1 | pfleura2 | * |
723 | 1 | pfleura2 | * P (input) INTEGER |
724 | 1 | pfleura2 | * The number of base BETA digits in the mantissa of a |
725 | 1 | pfleura2 | * floating-point value. |
726 | 1 | pfleura2 | * |
727 | 1 | pfleura2 | * EMIN (input) INTEGER |
728 | 1 | pfleura2 | * The minimum exponent before (gradual) underflow. |
729 | 1 | pfleura2 | * |
730 | 1 | pfleura2 | * IEEE (input) LOGICAL |
731 | 1 | pfleura2 | * A logical flag specifying whether or not the arithmetic |
732 | 1 | pfleura2 | * system is thought to comply with the IEEE standard. |
733 | 1 | pfleura2 | * |
734 | 1 | pfleura2 | * EMAX (output) INTEGER |
735 | 1 | pfleura2 | * The largest exponent before overflow |
736 | 1 | pfleura2 | * |
737 | 1 | pfleura2 | * RMAX (output) DOUBLE PRECISION |
738 | 1 | pfleura2 | * The largest machine floating-point number. |
739 | 1 | pfleura2 | * |
740 | 1 | pfleura2 | * ===================================================================== |
741 | 1 | pfleura2 | * |
742 | 1 | pfleura2 | * .. Parameters .. |
743 | 1 | pfleura2 | DOUBLE PRECISION ZERO, ONE |
744 | 1 | pfleura2 | PARAMETER ( ZERO = 0.0D0, ONE = 1.0D0 ) |
745 | 1 | pfleura2 | * .. |
746 | 1 | pfleura2 | * .. Local Scalars .. |
747 | 1 | pfleura2 | INTEGER EXBITS, EXPSUM, I, LEXP, NBITS, TRY, UEXP |
748 | 1 | pfleura2 | DOUBLE PRECISION OLDY, RECBAS, Y, Z |
749 | 1 | pfleura2 | * .. |
750 | 1 | pfleura2 | * .. External Functions .. |
751 | 1 | pfleura2 | DOUBLE PRECISION DLAMC3 |
752 | 1 | pfleura2 | EXTERNAL DLAMC3 |
753 | 1 | pfleura2 | * .. |
754 | 1 | pfleura2 | * .. Intrinsic Functions .. |
755 | 1 | pfleura2 | INTRINSIC MOD |
756 | 1 | pfleura2 | * .. |
757 | 1 | pfleura2 | * .. Executable Statements .. |
758 | 1 | pfleura2 | * |
759 | 1 | pfleura2 | * First compute LEXP and UEXP, two powers of 2 that bound |
760 | 1 | pfleura2 | * abs(EMIN). We then assume that EMAX + abs(EMIN) will sum |
761 | 1 | pfleura2 | * approximately to the bound that is closest to abs(EMIN). |
762 | 1 | pfleura2 | * (EMAX is the exponent of the required number RMAX). |
763 | 1 | pfleura2 | * |
764 | 1 | pfleura2 | LEXP = 1 |
765 | 1 | pfleura2 | EXBITS = 1 |
766 | 1 | pfleura2 | 10 CONTINUE |
767 | 1 | pfleura2 | TRY = LEXP*2 |
768 | 1 | pfleura2 | IF( TRY.LE.( -EMIN ) ) THEN |
769 | 1 | pfleura2 | LEXP = TRY |
770 | 1 | pfleura2 | EXBITS = EXBITS + 1 |
771 | 1 | pfleura2 | GO TO 10 |
772 | 1 | pfleura2 | END IF |
773 | 1 | pfleura2 | IF( LEXP.EQ.-EMIN ) THEN |
774 | 1 | pfleura2 | UEXP = LEXP |
775 | 1 | pfleura2 | ELSE |
776 | 1 | pfleura2 | UEXP = TRY |
777 | 1 | pfleura2 | EXBITS = EXBITS + 1 |
778 | 1 | pfleura2 | END IF |
779 | 1 | pfleura2 | * |
780 | 1 | pfleura2 | * Now -LEXP is less than or equal to EMIN, and -UEXP is greater |
781 | 1 | pfleura2 | * than or equal to EMIN. EXBITS is the number of bits needed to |
782 | 1 | pfleura2 | * store the exponent. |
783 | 1 | pfleura2 | * |
784 | 1 | pfleura2 | IF( ( UEXP+EMIN ).GT.( -LEXP-EMIN ) ) THEN |
785 | 1 | pfleura2 | EXPSUM = 2*LEXP |
786 | 1 | pfleura2 | ELSE |
787 | 1 | pfleura2 | EXPSUM = 2*UEXP |
788 | 1 | pfleura2 | END IF |
789 | 1 | pfleura2 | * |
790 | 1 | pfleura2 | * EXPSUM is the exponent range, approximately equal to |
791 | 1 | pfleura2 | * EMAX - EMIN + 1 . |
792 | 1 | pfleura2 | * |
793 | 1 | pfleura2 | EMAX = EXPSUM + EMIN - 1 |
794 | 1 | pfleura2 | NBITS = 1 + EXBITS + P |
795 | 1 | pfleura2 | * |
796 | 1 | pfleura2 | * NBITS is the total number of bits needed to store a |
797 | 1 | pfleura2 | * floating-point number. |
798 | 1 | pfleura2 | * |
799 | 1 | pfleura2 | IF( ( MOD( NBITS, 2 ).EQ.1 ) .AND. ( BETA.EQ.2 ) ) THEN |
800 | 1 | pfleura2 | * |
801 | 1 | pfleura2 | * Either there are an odd number of bits used to store a |
802 | 1 | pfleura2 | * floating-point number, which is unlikely, or some bits are |
803 | 1 | pfleura2 | * not used in the representation of numbers, which is possible, |
804 | 1 | pfleura2 | * (e.g. Cray machines) or the mantissa has an implicit bit, |
805 | 1 | pfleura2 | * (e.g. IEEE machines, Dec Vax machines), which is perhaps the |
806 | 1 | pfleura2 | * most likely. We have to assume the last alternative. |
807 | 1 | pfleura2 | * If this is true, then we need to reduce EMAX by one because |
808 | 1 | pfleura2 | * there must be some way of representing zero in an implicit-bit |
809 | 1 | pfleura2 | * system. On machines like Cray, we are reducing EMAX by one |
810 | 1 | pfleura2 | * unnecessarily. |
811 | 1 | pfleura2 | * |
812 | 1 | pfleura2 | EMAX = EMAX - 1 |
813 | 1 | pfleura2 | END IF |
814 | 1 | pfleura2 | * |
815 | 1 | pfleura2 | IF( IEEE ) THEN |
816 | 1 | pfleura2 | * |
817 | 1 | pfleura2 | * Assume we are on an IEEE machine which reserves one exponent |
818 | 1 | pfleura2 | * for infinity and NaN. |
819 | 1 | pfleura2 | * |
820 | 1 | pfleura2 | EMAX = EMAX - 1 |
821 | 1 | pfleura2 | END IF |
822 | 1 | pfleura2 | * |
823 | 1 | pfleura2 | * Now create RMAX, the largest machine number, which should |
824 | 1 | pfleura2 | * be equal to (1.0 - BETA**(-P)) * BETA**EMAX . |
825 | 1 | pfleura2 | * |
826 | 1 | pfleura2 | * First compute 1.0 - BETA**(-P), being careful that the |
827 | 1 | pfleura2 | * result is less than 1.0 . |
828 | 1 | pfleura2 | * |
829 | 1 | pfleura2 | RECBAS = ONE / BETA |
830 | 1 | pfleura2 | Z = BETA - ONE |
831 | 1 | pfleura2 | Y = ZERO |
832 | 1 | pfleura2 | DO 20 I = 1, P |
833 | 1 | pfleura2 | Z = Z*RECBAS |
834 | 1 | pfleura2 | IF( Y.LT.ONE ) |
835 | 1 | pfleura2 | $ OLDY = Y |
836 | 1 | pfleura2 | Y = DLAMC3( Y, Z ) |
837 | 1 | pfleura2 | 20 CONTINUE |
838 | 1 | pfleura2 | IF( Y.GE.ONE ) |
839 | 1 | pfleura2 | $ Y = OLDY |
840 | 1 | pfleura2 | * |
841 | 1 | pfleura2 | * Now multiply by BETA**EMAX to get RMAX. |
842 | 1 | pfleura2 | * |
843 | 1 | pfleura2 | DO 30 I = 1, EMAX |
844 | 1 | pfleura2 | Y = DLAMC3( Y*BETA, ZERO ) |
845 | 1 | pfleura2 | 30 CONTINUE |
846 | 1 | pfleura2 | * |
847 | 1 | pfleura2 | RMAX = Y |
848 | 1 | pfleura2 | RETURN |
849 | 1 | pfleura2 | * |
850 | 1 | pfleura2 | * End of DLAMC5 |
851 | 1 | pfleura2 | * |
852 | 1 | pfleura2 | END |