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

◆ dlamc2()

subroutine dlamc2 ( integer  beta,
integer  t,
logical  rnd,
double precision  eps,
integer  emin,
double precision  rmin,
integer  emax,
double precision  rmax 
)

Definition at line 326 of file tools.f.

327*
328* -- LAPACK auxiliary routine (version 2.0) --
329* Univ. of Tennessee, Univ. of California Berkeley, NAG Ltd.,
330* Courant Institute, Argonne National Lab, and Rice University
331* October 31, 1992
332*
333* .. Scalar Arguments ..
334 LOGICAL RND
335 INTEGER BETA, EMAX, EMIN, T
336 DOUBLE PRECISION EPS, RMAX, RMIN
337* ..
338*
339* Purpose
340* =======
341*
342* DLAMC2 determines the machine parameters specified in its argument
343* list.
344*
345* Arguments
346* =========
347*
348* BETA (output) INTEGER
349* The base of the machine.
350*
351* T (output) INTEGER
352* The number of ( BETA ) digits in the mantissa.
353*
354* RND (output) LOGICAL
355* Specifies whether proper rounding ( RND = .TRUE. ) or
356* chopping ( RND = .FALSE. ) occurs in addition. This may not
357* be a reliable guide to the way in which the machine performs
358* its arithmetic.
359*
360* EPS (output) DOUBLE PRECISION
361* The smallest positive number such that
362*
363* fl( 1.0 - EPS ) .LT. 1.0,
364*
365* where fl denotes the computed value.
366*
367* EMIN (output) INTEGER
368* The minimum exponent before (gradual) underflow occurs.
369*
370* RMIN (output) DOUBLE PRECISION
371* The smallest normalized number for the machine, given by
372* BASE**( EMIN - 1 ), where BASE is the floating point value
373* of BETA.
374*
375* EMAX (output) INTEGER
376* The maximum exponent before overflow occurs.
377*
378* RMAX (output) DOUBLE PRECISION
379* The largest positive number for the machine, given by
380* BASE**EMAX * ( 1 - EPS ), where BASE is the floating point
381* value of BETA.
382*
383* Further Details
384* ===============
385*
386* The computation of EPS is based on a routine PARANOIA by
387* W. Kahan of the University of California at Berkeley.
388*
389* =====================================================================
390*
391* .. Local Scalars ..
392 LOGICAL FIRST, IEEE, IWARN, LIEEE1, LRND
393 INTEGER GNMIN, GPMIN, I, LBETA, LEMAX, LEMIN, LT,
394 $ NGNMIN, NGPMIN
395 DOUBLE PRECISION A, B, C, HALF, LEPS, LRMAX, LRMIN, ONE, RBASE,
396 $ SIXTH, SMALL, THIRD, TWO, ZERO
397* ..
398* .. External Functions ..
399 DOUBLE PRECISION DLAMC3
400 EXTERNAL dlamc3
401* ..
402* .. External Subroutines ..
403 EXTERNAL dlamc1, dlamc4, dlamc5
404* ..
405* .. Intrinsic Functions ..
406 INTRINSIC abs, max, min
407* ..
408* .. Save statement ..
409 SAVE first, iwarn, lbeta, lemax, lemin, leps, lrmax,
410 $ lrmin, lt
411* ..
412* .. Data statements ..
413 DATA first / .true. / , iwarn / .false. /
414* ..
415* .. Executable Statements ..
416*
417 IF( first ) THEN
418 first = .false.
419 zero = 0
420 one = 1
421 two = 2
422*
423* LBETA, LT, LRND, LEPS, LEMIN and LRMIN are the local values of
424* BETA, T, RND, EPS, EMIN and RMIN.
425*
426* Throughout this routine we use the function DLAMC3 to ensure
427* that relevant values are stored and not held in registers, or
428* are not affected by optimizers.
429*
430* DLAMC1 returns the parameters LBETA, LT, LRND and LIEEE1.
431*
432 CALL dlamc1( lbeta, lt, lrnd, lieee1 )
433*
434* Start to find EPS.
435*
436 b = lbeta
437 a = b**( -lt )
438 leps = a
439*
440* Try some tricks to see whether or not this is the correct EPS.
441*
442 b = two / 3
443 half = one / 2
444 sixth = dlamc3( b, -half )
445 third = dlamc3( sixth, sixth )
446 b = dlamc3( third, -half )
447 b = dlamc3( b, sixth )
448 b = abs( b )
449 IF( b.LT.leps )
450 $ b = leps
451*
452 leps = 1
453*
454*+ WHILE( ( LEPS.GT.B ).AND.( B.GT.ZERO ) )LOOP
455 10 CONTINUE
456 IF( ( leps.GT.b ) .AND. ( b.GT.zero ) ) THEN
457 leps = b
458 c = dlamc3( half*leps, ( two**5 )*( leps**2 ) )
459 c = dlamc3( half, -c )
460 b = dlamc3( half, c )
461 c = dlamc3( half, -b )
462 b = dlamc3( half, c )
463 GO TO 10
464 END IF
465*+ END WHILE
466*
467 IF( a.LT.leps )
468 $ leps = a
469*
470* Computation of EPS complete.
471*
472* Now find EMIN. Let A = + or - 1, and + or - (1 + BASE**(-3)).
473* Keep dividing A by BETA until (gradual) underflow occurs. This
474* is detected when we cannot recover the previous A.
475*
476 rbase = one / lbeta
477 small = one
478 DO 20 i = 1, 3
479 small = dlamc3( small*rbase, zero )
480 20 CONTINUE
481 a = dlamc3( one, small )
482 CALL dlamc4( ngpmin, one, lbeta )
483 CALL dlamc4( ngnmin, -one, lbeta )
484 CALL dlamc4( gpmin, a, lbeta )
485 CALL dlamc4( gnmin, -a, lbeta )
486 ieee = .false.
487*
488 IF( ( ngpmin.EQ.ngnmin ) .AND. ( gpmin.EQ.gnmin ) ) THEN
489 IF( ngpmin.EQ.gpmin ) THEN
490 lemin = ngpmin
491* ( Non twos-complement machines, no gradual underflow;
492* e.g., VAX )
493 ELSE IF( ( gpmin-ngpmin ).EQ.3 ) THEN
494 lemin = ngpmin - 1 + lt
495 ieee = .true.
496* ( Non twos-complement machines, with gradual underflow;
497* e.g., IEEE standard followers )
498 ELSE
499 lemin = min( ngpmin, gpmin )
500* ( A guess; no known machine )
501 iwarn = .true.
502 END IF
503*
504 ELSE IF( ( ngpmin.EQ.gpmin ) .AND. ( ngnmin.EQ.gnmin ) ) THEN
505 IF( abs( ngpmin-ngnmin ).EQ.1 ) THEN
506 lemin = max( ngpmin, ngnmin )
507* ( Twos-complement machines, no gradual underflow;
508* e.g., CYBER 205 )
509 ELSE
510 lemin = min( ngpmin, ngnmin )
511* ( A guess; no known machine )
512 iwarn = .true.
513 END IF
514*
515 ELSE IF( ( abs( ngpmin-ngnmin ).EQ.1 ) .AND.
516 $ ( gpmin.EQ.gnmin ) ) THEN
517 IF( ( gpmin-min( ngpmin, ngnmin ) ).EQ.3 ) THEN
518 lemin = max( ngpmin, ngnmin ) - 1 + lt
519* ( Twos-complement machines with gradual underflow;
520* no known machine )
521 ELSE
522 lemin = min( ngpmin, ngnmin )
523* ( A guess; no known machine )
524 iwarn = .true.
525 END IF
526*
527 ELSE
528 lemin = min( ngpmin, ngnmin, gpmin, gnmin )
529* ( A guess; no known machine )
530 iwarn = .true.
531 END IF
532***
533* Comment out this if block if EMIN is ok
534 IF( iwarn ) THEN
535 first = .true.
536 WRITE( 6, fmt = 9999 )lemin
537 END IF
538***
539*
540* Assume IEEE arithmetic if we found denormalised numbers above,
541* or if arithmetic seems to round in the IEEE style, determined
542* in routine DLAMC1. A true IEEE machine should have both things
543* true; however, faulty machines may have one or the other.
544*
545 ieee = ieee .OR. lieee1
546*
547* Compute RMIN by successive division by BETA. We could compute
548* RMIN as BASE**( EMIN - 1 ), but some machines underflow during
549* this computation.
550*
551 lrmin = 1
552 DO 30 i = 1, 1 - lemin
553 lrmin = dlamc3( lrmin*rbase, zero )
554 30 CONTINUE
555*
556* Finally, call DLAMC5 to compute EMAX and RMAX.
557*
558 CALL dlamc5( lbeta, lt, lemin, ieee, lemax, lrmax )
559 END IF
560*
561 beta = lbeta
562 t = lt
563 rnd = lrnd
564 eps = leps
565 emin = lemin
566 rmin = lrmin
567 emax = lemax
568 rmax = lrmax
569*
570 RETURN
571*
572 9999 FORMAT( / / ' WARNING. The value EMIN may be incorrect:-',
573 $ ' EMIN = ', i8, /
574 $ ' If, after inspection, the value EMIN looks',
575 $ ' acceptable please comment out ',
576 $ / ' the IF block as marked within the code of routine',
577 $ ' DLAMC2,', / ' otherwise supply EMIN explicitly.', / )
578*
579* End of DLAMC2
580*
#define max(A, B)
Definition pcgemr.c:180
#define min(A, B)
Definition pcgemr.c:181
double precision function dlamc3(a, b)
Definition tools.f:586
subroutine dlamc4(emin, start, base)
Definition tools.f:624
subroutine dlamc1(beta, t, rnd, ieee1)
Definition tools.f:140
subroutine dlamc5(beta, p, emin, ieee, emax, rmax)
Definition tools.f:708
Here is the call graph for this function:
Here is the caller graph for this function: