1 ------------------------------------------------------------------------------
3 -- GNAT COMPILER COMPONENTS --
5 -- S Y S T E M . F A T _ G E N --
9 -- Copyright (C) 1992-2004 Free Software Foundation, Inc. --
11 -- GNAT is free software; you can redistribute it and/or modify it under --
12 -- terms of the GNU General Public License as published by the Free Soft- --
13 -- ware Foundation; either version 2, or (at your option) any later ver- --
14 -- sion. GNAT is distributed in the hope that it will be useful, but WITH- --
15 -- OUT ANY WARRANTY; without even the implied warranty of MERCHANTABILITY --
16 -- or FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License --
17 -- for more details. You should have received a copy of the GNU General --
18 -- Public License distributed with GNAT; see file COPYING. If not, write --
19 -- to the Free Software Foundation, 59 Temple Place - Suite 330, Boston, --
20 -- MA 02111-1307, USA. --
22 -- As a special exception, if other files instantiate generics from this --
23 -- unit, or you link this unit with other files to produce an executable, --
24 -- this unit does not by itself cause the resulting executable to be --
25 -- covered by the GNU General Public License. This exception does not --
26 -- however invalidate any other reasons why the executable file might be --
27 -- covered by the GNU Public License. --
29 -- GNAT was originally developed by the GNAT team at New York University. --
30 -- Extensive contributions were provided by Ada Core Technologies Inc. --
32 ------------------------------------------------------------------------------
34 -- The implementation here is portable to any IEEE implementation. It does
35 -- not handle non-binary radix, and also assumes that model numbers and
36 -- machine numbers are basically identical, which is not true of all possible
37 -- floating-point implementations. On a non-IEEE machine, this body must be
38 -- specialized appropriately, or better still, its generic instantiations
39 -- should be replaced by efficient machine-specific code.
41 with Ada
.Unchecked_Conversion
;
43 package body System
.Fat_Gen
is
45 Float_Radix
: constant T
:= T
(T
'Machine_Radix);
46 Radix_To_M_Minus_1
: constant T
:= Float_Radix
** (T
'Machine_Mantissa - 1);
48 pragma Assert
(T
'Machine_Radix = 2);
49 -- This version does not handle radix 16
51 -- Constants for Decompose and Scaling
53 Rad
: constant T
:= T
(T
'Machine_Radix);
54 Invrad
: constant T
:= 1.0 / Rad
;
56 subtype Expbits
is Integer range 0 .. 6;
57 -- 2 ** (2 ** 7) might overflow. how big can radix-16 exponents get?
59 Log_Power
: constant array (Expbits
) of Integer := (1, 2, 4, 8, 16, 32, 64);
61 R_Power
: constant array (Expbits
) of T
:=
70 R_Neg_Power
: constant array (Expbits
) of T
:=
79 -----------------------
80 -- Local Subprograms --
81 -----------------------
83 procedure Decompose
(XX
: T
; Frac
: out T
; Expo
: out UI
);
84 -- Decomposes a floating-point number into fraction and exponent parts.
85 -- Both results are signed, with Frac having the sign of XX, and UI has
86 -- the sign of the exponent. The absolute value of Frac is in the range
87 -- 0.0 <= Frac < 1.0. If Frac = 0.0 or -0.0, then Expo is always zero.
89 function Gradual_Scaling
(Adjustment
: UI
) return T
;
90 -- Like Scaling with a first argument of 1.0, but returns the smallest
91 -- denormal rather than zero when the adjustment is smaller than
92 -- Machine_Emin. Used for Succ and Pred.
98 function Adjacent
(X
, Towards
: T
) return T
is
103 elsif Towards
> X
then
115 function Ceiling
(X
: T
) return T
is
116 XT
: constant T
:= Truncation
(X
);
134 function Compose
(Fraction
: T
; Exponent
: UI
) return T
is
138 Decompose
(Fraction
, Arg_Frac
, Arg_Exp
);
139 return Scaling
(Arg_Frac
, Exponent
);
146 function Copy_Sign
(Value
, Sign
: T
) return T
is
149 function Is_Negative
(V
: T
) return Boolean;
150 pragma Import
(Intrinsic
, Is_Negative
);
155 if Is_Negative
(Sign
) then
166 procedure Decompose
(XX
: T
; Frac
: out T
; Expo
: out UI
) is
167 X
: constant T
:= T
'Machine (XX
);
174 -- More useful would be defining Expo to be T'Machine_Emin - 1 or
175 -- T'Machine_Emin - T'Machine_Mantissa, which would preserve
176 -- monotonicity of the exponent function ???
178 -- Check for infinities, transfinites, whatnot.
180 elsif X
> T
'Safe_Last then
182 Expo
:= T
'Machine_Emax + 1;
184 elsif X
< T
'Safe_First then
186 Expo
:= T
'Machine_Emax + 2; -- how many extra negative values?
189 -- Case of nonzero finite x. Essentially, we just multiply
190 -- by Rad ** (+-2**N) to reduce the range.
196 -- Ax * Rad ** Ex is invariant.
200 while Ax
>= R_Power
(Expbits
'Last) loop
201 Ax
:= Ax
* R_Neg_Power
(Expbits
'Last);
202 Ex
:= Ex
+ Log_Power
(Expbits
'Last);
207 for N
in reverse Expbits
'First .. Expbits
'Last - 1 loop
208 if Ax
>= R_Power
(N
) then
209 Ax
:= Ax
* R_Neg_Power
(N
);
210 Ex
:= Ex
+ Log_Power
(N
);
224 while Ax
< R_Neg_Power
(Expbits
'Last) loop
225 Ax
:= Ax
* R_Power
(Expbits
'Last);
226 Ex
:= Ex
- Log_Power
(Expbits
'Last);
229 -- Rad ** -64 <= Ax < 1
231 for N
in reverse Expbits
'First .. Expbits
'Last - 1 loop
232 if Ax
< R_Neg_Power
(N
) then
233 Ax
:= Ax
* R_Power
(N
);
234 Ex
:= Ex
- Log_Power
(N
);
237 -- R_Neg_Power (N) <= Ax < 1
256 function Exponent
(X
: T
) return UI
is
261 Decompose
(X
, X_Frac
, X_Exp
);
269 function Floor
(X
: T
) return T
is
270 XT
: constant T
:= Truncation
(X
);
288 function Fraction
(X
: T
) return T
is
293 Decompose
(X
, X_Frac
, X_Exp
);
297 ---------------------
298 -- Gradual_Scaling --
299 ---------------------
301 function Gradual_Scaling
(Adjustment
: UI
) return T
is
304 Ex
: UI
:= Adjustment
;
307 if Adjustment
< T
'Machine_Emin - 1 then
308 Y
:= 2.0 ** T
'Machine_Emin;
310 Ex
:= Ex
- T
'Machine_Emin;
312 Y
:= T
'Machine (Y
/ 2.0);
325 return Scaling
(1.0, Adjustment
);
333 function Leading_Part
(X
: T
; Radix_Digits
: UI
) return T
is
338 if Radix_Digits
>= T
'Machine_Mantissa then
341 elsif Radix_Digits
<= 0 then
342 raise Constraint_Error
;
345 L
:= Exponent
(X
) - Radix_Digits
;
346 Y
:= Truncation
(Scaling
(X
, -L
));
356 -- The trick with Machine is to force the compiler to store the result
357 -- in memory so that we do not have extra precision used. The compiler
358 -- is clever, so we have to outwit its possible optimizations! We do
359 -- this by using an intermediate pragma Volatile location.
361 function Machine
(X
: T
) return T
is
363 pragma Volatile
(Temp
);
373 -- We treat Model as identical to Machine. This is true of IEEE and other
374 -- nice floating-point systems, but not necessarily true of all systems.
376 function Model
(X
: T
) return T
is
385 -- Subtract from the given number a number equivalent to the value of its
386 -- least significant bit. Given that the most significant bit represents
387 -- a value of 1.0 * radix ** (exp - 1), the value we want is obtained by
388 -- shifting this by (mantissa-1) bits to the right, i.e. decreasing the
389 -- exponent by that amount.
391 -- Zero has to be treated specially, since its exponent is zero
393 function Pred
(X
: T
) return T
is
402 Decompose
(X
, X_Frac
, X_Exp
);
404 -- A special case, if the number we had was a positive power of
405 -- two, then we want to subtract half of what we would otherwise
406 -- subtract, since the exponent is going to be reduced.
408 -- Note that X_Frac has the same sign as X, so if X_Frac is 0.5,
409 -- then we know that we have a positive number (and hence a
410 -- positive power of 2).
413 return X
- Gradual_Scaling
(X_Exp
- T
'Machine_Mantissa - 1);
415 -- Otherwise the exponent is unchanged
418 return X
- Gradual_Scaling
(X_Exp
- T
'Machine_Mantissa);
427 function Remainder
(X
, Y
: T
) return T
is
443 raise Constraint_Error
;
459 P_Exp
:= Exponent
(P
);
462 Decompose
(Arg
, Arg_Frac
, Arg_Exp
);
463 Decompose
(P
, P_Frac
, P_Exp
);
465 P
:= Compose
(P_Frac
, Arg_Exp
);
466 K
:= Arg_Exp
- P_Exp
;
470 for Cnt
in reverse 0 .. K
loop
471 if IEEE_Rem
>= P
then
473 IEEE_Rem
:= IEEE_Rem
- P
;
482 -- That completes the calculation of modulus remainder. The final
483 -- step is get the IEEE remainder. Here we need to compare Rem with
484 -- (abs Y) / 2. We must be careful of unrepresentable Y/2 value
485 -- caused by subnormal numbers
496 if A
> B
or else (A
= B
and then not P_Even
) then
497 IEEE_Rem
:= IEEE_Rem
- abs Y
;
500 return Sign_X
* IEEE_Rem
;
507 function Rounding
(X
: T
) return T
is
512 Result
:= Truncation
(abs X
);
513 Tail
:= abs X
- Result
;
516 Result
:= Result
+ 1.0;
525 -- For zero case, make sure sign of zero is preserved
536 -- Return x * rad ** adjustment quickly,
537 -- or quietly underflow to zero, or overflow naturally.
539 function Scaling
(X
: T
; Adjustment
: UI
) return T
is
541 if X
= 0.0 or else Adjustment
= 0 then
545 -- Nonzero x. essentially, just multiply repeatedly by Rad ** (+-2**n).
549 Ex
: UI
:= Adjustment
;
551 -- Y * Rad ** Ex is invariant
555 while Ex
<= -Log_Power
(Expbits
'Last) loop
556 Y
:= Y
* R_Neg_Power
(Expbits
'Last);
557 Ex
:= Ex
+ Log_Power
(Expbits
'Last);
562 for N
in reverse Expbits
'First .. Expbits
'Last - 1 loop
563 if Ex
<= -Log_Power
(N
) then
564 Y
:= Y
* R_Neg_Power
(N
);
565 Ex
:= Ex
+ Log_Power
(N
);
568 -- -Log_Power (N) < Ex <= 0
576 while Ex
>= Log_Power
(Expbits
'Last) loop
577 Y
:= Y
* R_Power
(Expbits
'Last);
578 Ex
:= Ex
- Log_Power
(Expbits
'Last);
583 for N
in reverse Expbits
'First .. Expbits
'Last - 1 loop
584 if Ex
>= Log_Power
(N
) then
585 Y
:= Y
* R_Power
(N
);
586 Ex
:= Ex
- Log_Power
(N
);
589 -- 0 <= Ex < Log_Power (N)
603 -- Similar computation to that of Pred: find value of least significant
604 -- bit of given number, and add. Zero has to be treated specially since
605 -- the exponent can be zero, and also we want the smallest denormal if
606 -- denormals are supported.
608 function Succ
(X
: T
) return T
is
615 X1
:= 2.0 ** T
'Machine_Emin;
617 -- Following loop generates smallest denormal
620 X2
:= T
'Machine (X1
/ 2.0);
628 Decompose
(X
, X_Frac
, X_Exp
);
630 -- A special case, if the number we had was a negative power of
631 -- two, then we want to add half of what we would otherwise add,
632 -- since the exponent is going to be reduced.
634 -- Note that X_Frac has the same sign as X, so if X_Frac is -0.5,
635 -- then we know that we have a ngeative number (and hence a
636 -- negative power of 2).
638 if X_Frac
= -0.5 then
639 return X
+ Gradual_Scaling
(X_Exp
- T
'Machine_Mantissa - 1);
641 -- Otherwise the exponent is unchanged
644 return X
+ Gradual_Scaling
(X_Exp
- T
'Machine_Mantissa);
653 -- The basic approach is to compute
655 -- T'Machine (RM1 + N) - RM1.
657 -- where N >= 0.0 and RM1 = radix ** (mantissa - 1)
659 -- This works provided that the intermediate result (RM1 + N) does not
660 -- have extra precision (which is why we call Machine). When we compute
661 -- RM1 + N, the exponent of N will be normalized and the mantissa shifted
662 -- shifted appropriately so the lower order bits, which cannot contribute
663 -- to the integer part of N, fall off on the right. When we subtract RM1
664 -- again, the significant bits of N are shifted to the left, and what we
665 -- have is an integer, because only the first e bits are different from
666 -- zero (assuming binary radix here).
668 function Truncation
(X
: T
) return T
is
674 if Result
>= Radix_To_M_Minus_1
then
678 Result
:= Machine
(Radix_To_M_Minus_1
+ Result
) - Radix_To_M_Minus_1
;
680 if Result
> abs X
then
681 Result
:= Result
- 1.0;
690 -- For zero case, make sure sign of zero is preserved
699 -----------------------
700 -- Unbiased_Rounding --
701 -----------------------
703 function Unbiased_Rounding
(X
: T
) return T
is
704 Abs_X
: constant T
:= abs X
;
709 Result
:= Truncation
(Abs_X
);
710 Tail
:= Abs_X
- Result
;
713 Result
:= Result
+ 1.0;
715 elsif Tail
= 0.5 then
716 Result
:= 2.0 * Truncation
((Result
/ 2.0) + 0.5);
725 -- For zero case, make sure sign of zero is preserved
731 end Unbiased_Rounding
;
737 function Valid
(X
: access T
) return Boolean is
739 IEEE_Emin
: constant Integer := T
'Machine_Emin - 1;
740 IEEE_Emax
: constant Integer := T
'Machine_Emax - 1;
742 IEEE_Bias
: constant Integer := -(IEEE_Emin
- 1);
744 subtype IEEE_Exponent_Range
is
745 Integer range IEEE_Emin
- 1 .. IEEE_Emax
+ 1;
747 -- The implementation of this floating point attribute uses
748 -- a representation type Float_Rep that allows direct access to
749 -- the exponent and mantissa parts of a floating point number.
751 -- The Float_Rep type is an array of Float_Word elements. This
752 -- representation is chosen to make it possible to size the
753 -- type based on a generic parameter. Since the array size is
754 -- known at compile-time, efficient code can still be generated.
755 -- The size of Float_Word elements should be large enough to allow
756 -- accessing the exponent in one read, but small enough so that all
757 -- floating point object sizes are a multiple of the Float_Word'Size.
759 -- The following conditions must be met for all possible
760 -- instantiations of the attributes package:
762 -- - T'Size is an integral multiple of Float_Word'Size
764 -- - The exponent and sign are completely contained in a single
765 -- component of Float_Rep, named Most_Significant_Word (MSW).
767 -- - The sign occupies the most significant bit of the MSW
768 -- and the exponent is in the following bits.
769 -- Unused bits (if any) are in the least significant part.
771 type Float_Word
is mod 2**Positive'Min (System
.Word_Size
, 32);
772 type Rep_Index
is range 0 .. 7;
774 Rep_Last
: constant Rep_Index
:= (T
'Size - 1) / Float_Word
'Size;
776 type Float_Rep
is array (Rep_Index
range 0 .. Rep_Last
) of Float_Word
;
778 pragma Suppress_Initialization
(Float_Rep
);
779 -- This pragma supresses the generation of an initialization procedure
780 -- for type Float_Rep when operating in Initialize/Normalize_Scalars
781 -- mode. This is not just a matter of efficiency, but of functionality,
782 -- since Valid has a pragma Inline_Always, which is not permitted if
783 -- there are nested subprograms present.
785 Most_Significant_Word
: constant Rep_Index
:=
786 Rep_Last
* Standard
'Default_Bit_Order;
787 -- Finding the location of the Exponent_Word is a bit tricky.
788 -- In general we assume Word_Order = Bit_Order.
789 -- This expression needs to be refined for VMS.
791 Exponent_Factor
: constant Float_Word
:=
792 2**(Float_Word
'Size - 1) /
793 Float_Word
(IEEE_Emax
- IEEE_Emin
+ 3) *
794 Boolean'Pos (T
'Size /= 96) +
795 Boolean'Pos (T
'Size = 96);
796 -- Factor that the extracted exponent needs to be divided by
797 -- to be in range 0 .. IEEE_Emax - IEEE_Emin + 2.
798 -- Special kludge: Exponent_Factor is 0 for x86 double extended
799 -- as GCC adds 16 unused bits to the type.
801 Exponent_Mask
: constant Float_Word
:=
802 Float_Word
(IEEE_Emax
- IEEE_Emin
+ 2) *
804 -- Value needed to mask out the exponent field.
805 -- This assumes that the range IEEE_Emin - 1 .. IEEE_Emax + 1
806 -- contains 2**N values, for some N in Natural.
808 function To_Float
is new Ada
.Unchecked_Conversion
(Float_Rep
, T
);
810 type Float_Access
is access all T
;
811 function To_Address
is
812 new Ada
.Unchecked_Conversion
(Float_Access
, System
.Address
);
814 XA
: constant System
.Address
:= To_Address
(Float_Access
(X
));
817 pragma Import
(Ada
, R
);
818 for R
'Address use XA
;
819 -- R is a view of the input floating-point parameter. Note that we
820 -- must avoid copying the actual bits of this parameter in float
821 -- form (since it may be a signalling NaN.
823 E
: constant IEEE_Exponent_Range
:=
824 Integer ((R
(Most_Significant_Word
) and Exponent_Mask
) /
827 -- Mask/Shift T to only get bits from the exponent
828 -- Then convert biased value to integer value.
831 -- Float_Rep representation of significant of X.all
836 -- All denormalized numbers are valid, so only invalid numbers
837 -- are overflows and NaN's, both with exponent = Emax + 1.
839 return E
/= IEEE_Emax
+ 1;
843 -- All denormalized numbers except 0.0 are invalid
845 -- Set exponent of X to zero, so we end up with the significand, which
846 -- definitely is a valid number and can be converted back to a float.
849 SR
(Most_Significant_Word
) :=
850 (SR
(Most_Significant_Word
)
851 and not Exponent_Mask
) + Float_Word
(IEEE_Bias
) * Exponent_Factor
;
853 return (E
in IEEE_Emin
.. IEEE_Emax
) or else
854 ((E
= IEEE_Emin
- 1) and then abs To_Float
(SR
) = 1.0);
857 ---------------------
858 -- Unaligned_Valid --
859 ---------------------
861 function Unaligned_Valid
(A
: System
.Address
) return Boolean is
862 subtype FS
is String (1 .. T
'Size / Character'Size);
863 type FSP
is access FS
;
865 function To_FSP
is new Ada
.Unchecked_Conversion
(Address
, FSP
);
870 To_FSP
(Local_T
'Address).all := To_FSP
(A
).all;
871 return Valid
(Local_T
'Access);