SCALAPACK 2.2.2
LAPACK: Linear Algebra PACKage
Loading...
Searching...
No Matches

◆ dlamc1()

subroutine dlamc1 ( integer  beta,
integer  t,
logical  rnd,
logical  ieee1 
)

Definition at line 131 of file dlamch.f.

132*
133* -- LAPACK auxiliary routine (version 2.1) --
134* Univ. of Tennessee, Univ. of California Berkeley, NAG Ltd.,
135* Courant Institute, Argonne National Lab, and Rice University
136* October 31, 1992
137*
138* .. Scalar Arguments ..
139 LOGICAL IEEE1, RND
140 INTEGER BETA, T
141* ..
142*
143* Purpose
144* =======
145*
146* DLAMC1 determines the machine parameters given by BETA, T, RND, and
147* IEEE1.
148*
149* Arguments
150* =========
151*
152* BETA (output) INTEGER
153* The base of the machine.
154*
155* T (output) INTEGER
156* The number of ( BETA ) digits in the mantissa.
157*
158* RND (output) LOGICAL
159* Specifies whether proper rounding ( RND = .TRUE. ) or
160* chopping ( RND = .FALSE. ) occurs in addition. This may not
161* be a reliable guide to the way in which the machine performs
162* its arithmetic.
163*
164* IEEE1 (output) LOGICAL
165* Specifies whether rounding appears to be done in the IEEE
166* 'round to nearest' style.
167*
168* Further Details
169* ===============
170*
171* The routine is based on the routine ENVRON by Malcolm and
172* incorporates suggestions by Gentleman and Marovich. See
173*
174* Malcolm M. A. (1972) Algorithms to reveal properties of
175* floating-point arithmetic. Comms. of the ACM, 15, 949-951.
176*
177* Gentleman W. M. and Marovich S. B. (1974) More on algorithms
178* that reveal properties of floating point arithmetic units.
179* Comms. of the ACM, 17, 276-277.
180*
181* =====================================================================
182*
183* .. Local Scalars ..
184 LOGICAL FIRST, LIEEE1, LRND
185 INTEGER LBETA, LT
186 DOUBLE PRECISION A, B, C, F, ONE, QTR, SAVEC, T1, T2
187* ..
188* .. External Functions ..
189 DOUBLE PRECISION DLAMC3
190 EXTERNAL dlamc3
191* ..
192* .. Save statement ..
193 SAVE first, lieee1, lbeta, lrnd, lt
194* ..
195* .. Data statements ..
196 DATA first / .true. /
197* ..
198* .. Executable Statements ..
199*
200 IF( first ) THEN
201 first = .false.
202 one = 1
203*
204* LBETA, LIEEE1, LT and LRND are the local values of BETA,
205* IEEE1, T and RND.
206*
207* Throughout this routine we use the function DLAMC3 to ensure
208* that relevant values are stored and not held in registers, or
209* are not affected by optimizers.
210*
211* Compute a = 2.0**m with the smallest positive integer m such
212* that
213*
214* fl( a + 1.0 ) = a.
215*
216 a = 1
217 c = 1
218*
219*+ WHILE( C.EQ.ONE )LOOP
220 10 CONTINUE
221 IF( c.EQ.one ) THEN
222 a = 2*a
223 c = dlamc3( a, one )
224 c = dlamc3( c, -a )
225 GO TO 10
226 END IF
227*+ END WHILE
228*
229* Now compute b = 2.0**m with the smallest positive integer m
230* such that
231*
232* fl( a + b ) .gt. a.
233*
234 b = 1
235 c = dlamc3( a, b )
236*
237*+ WHILE( C.EQ.A )LOOP
238 20 CONTINUE
239 IF( c.EQ.a ) THEN
240 b = 2*b
241 c = dlamc3( a, b )
242 GO TO 20
243 END IF
244*+ END WHILE
245*
246* Now compute the base. a and c are neighbouring floating point
247* numbers in the interval ( beta**t, beta**( t + 1 ) ) and so
248* their difference is beta. Adding 0.25 to c is to ensure that it
249* is truncated to beta and not ( beta - 1 ).
250*
251 qtr = one / 4
252 savec = c
253 c = dlamc3( c, -a )
254 lbeta = c + qtr
255*
256* Now determine whether rounding or chopping occurs, by adding a
257* bit less than beta/2 and a bit more than beta/2 to a.
258*
259 b = lbeta
260 f = dlamc3( b / 2, -b / 100 )
261 c = dlamc3( f, a )
262 IF( c.EQ.a ) THEN
263 lrnd = .true.
264 ELSE
265 lrnd = .false.
266 END IF
267 f = dlamc3( b / 2, b / 100 )
268 c = dlamc3( f, a )
269 IF( ( lrnd ) .AND. ( c.EQ.a ) )
270 $ lrnd = .false.
271*
272* Try and decide whether rounding is done in the IEEE 'round to
273* nearest' style. B/2 is half a unit in the last place of the two
274* numbers A and SAVEC. Furthermore, A is even, i.e. has last bit
275* zero, and SAVEC is odd. Thus adding B/2 to A should not change
276* A, but adding B/2 to SAVEC should change SAVEC.
277*
278 t1 = dlamc3( b / 2, a )
279 t2 = dlamc3( b / 2, savec )
280 lieee1 = ( t1.EQ.a ) .AND. ( t2.GT.savec ) .AND. lrnd
281*
282* Now find the mantissa, t. It should be the integer part of
283* log to the base beta of a, however it is safer to determine t
284* by powering. So we find t as the smallest positive integer for
285* which
286*
287* fl( beta**t + 1.0 ) = 1.0.
288*
289 lt = 0
290 a = 1
291 c = 1
292*
293*+ WHILE( C.EQ.ONE )LOOP
294 30 CONTINUE
295 IF( c.EQ.one ) THEN
296 lt = lt + 1
297 a = a*lbeta
298 c = dlamc3( a, one )
299 c = dlamc3( c, -a )
300 GO TO 30
301 END IF
302*+ END WHILE
303*
304 END IF
305*
306 beta = lbeta
307 t = lt
308 rnd = lrnd
309 ieee1 = lieee1
310 RETURN
311*
312* End of DLAMC1
313*
double precision function dlamc3(a, b)
Definition tools.f:586