1 ------------------------------------------------------------------------------
3 -- GNAT RUN-TIME COMPONENTS --
5 -- S Y S T E M . A R I T H _ 6 4 --
9 -- Copyright (C) 1992-2014, 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 3, 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. --
18 -- As a special exception under Section 7 of GPL version 3, you are granted --
19 -- additional permissions described in the GCC Runtime Library Exception, --
20 -- version 3.1, as published by the Free Software Foundation. --
22 -- You should have received a copy of the GNU General Public License and --
23 -- a copy of the GCC Runtime Library Exception along with this program; --
24 -- see the files COPYING3 and COPYING.RUNTIME respectively. If not, see --
25 -- <http://www.gnu.org/licenses/>. --
27 -- GNAT was originally developed by the GNAT team at New York University. --
28 -- Extensive contributions were provided by Ada Core Technologies Inc. --
30 ------------------------------------------------------------------------------
32 with Interfaces
; use Interfaces
;
34 with Ada
.Unchecked_Conversion
;
36 package body System
.Arith_64
is
38 pragma Suppress
(Overflow_Check
);
39 pragma Suppress
(Range_Check
);
41 subtype Uns64
is Unsigned_64
;
42 function To_Uns
is new Ada
.Unchecked_Conversion
(Int64
, Uns64
);
43 function To_Int
is new Ada
.Unchecked_Conversion
(Uns64
, Int64
);
45 subtype Uns32
is Unsigned_32
;
47 -----------------------
48 -- Local Subprograms --
49 -----------------------
51 function "+" (A
, B
: Uns32
) return Uns64
is (Uns64
(A
) + Uns64
(B
));
52 function "+" (A
: Uns64
; B
: Uns32
) return Uns64
is (A
+ Uns64
(B
));
53 -- Length doubling additions
55 function "*" (A
, B
: Uns32
) return Uns64
is (Uns64
(A
) * Uns64
(B
));
56 -- Length doubling multiplication
58 function "/" (A
: Uns64
; B
: Uns32
) return Uns64
is (A
/ Uns64
(B
));
59 -- Length doubling division
61 function "&" (Hi
, Lo
: Uns32
) return Uns64
is
62 (Shift_Left
(Uns64
(Hi
), 32) or Uns64
(Lo
));
63 -- Concatenate hi, lo values to form 64-bit result
65 function "abs" (X
: Int64
) return Uns64
is
66 (if X
= Int64
'First then 2**63 else Uns64
(Int64
'(abs X)));
67 -- Convert absolute value of X to unsigned. Note that we can't just use
68 -- the expression of the Else, because it overflows for X = Int64'First.
70 function "rem" (A : Uns64; B : Uns32) return Uns64 is (A rem Uns64 (B));
71 -- Length doubling remainder
73 function Le3 (X1, X2, X3 : Uns32; Y1, Y2, Y3 : Uns32) return Boolean;
74 -- Determines if 96 bit value X1&X2&X3 <= Y1&Y2&Y3
76 function Lo (A : Uns64) return Uns32 is (Uns32 (A and 16#FFFF_FFFF#));
77 -- Low order half of 64-bit value
79 function Hi (A : Uns64) return Uns32 is (Uns32 (Shift_Right (A, 32)));
80 -- High order half of 64-bit value
82 procedure Sub3 (X1, X2, X3 : in out Uns32; Y1, Y2, Y3 : Uns32);
83 -- Computes X1&X2&X3 := X1&X2&X3 - Y1&Y1&Y3 with mod 2**96 wrap
85 function To_Neg_Int (A : Uns64) return Int64 with Inline;
86 -- Convert to negative integer equivalent. If the input is in the range
87 -- 0 .. 2 ** 63, then the corresponding negative signed integer (obtained
88 -- by negating the given value) is returned, otherwise constraint error
91 function To_Pos_Int (A : Uns64) return Int64 with Inline;
92 -- Convert to positive integer equivalent. If the input is in the range
93 -- 0 .. 2 ** 63-1, then the corresponding non-negative signed integer is
94 -- returned, otherwise constraint error is raised.
96 procedure Raise_Error with Inline;
97 pragma No_Return (Raise_Error);
98 -- Raise constraint error with appropriate message
100 --------------------------
101 -- Add_With_Ovflo_Check --
102 --------------------------
104 function Add_With_Ovflo_Check (X, Y : Int64) return Int64 is
105 R : constant Int64 := To_Int (To_Uns (X) + To_Uns (Y));
109 if Y < 0 or else R >= 0 then
114 if Y > 0 or else R < 0 then
120 end Add_With_Ovflo_Check;
126 procedure Double_Divide
131 Xu : constant Uns64 := abs X;
132 Yu : constant Uns64 := abs Y;
134 Yhi : constant Uns32 := Hi (Yu);
135 Ylo : constant Uns32 := Lo (Yu);
137 Zu : constant Uns64 := abs Z;
138 Zhi : constant Uns32 := Hi (Zu);
139 Zlo : constant Uns32 := Lo (Zu);
146 if Yu = 0 or else Zu = 0 then
150 -- Compute Y * Z. Note that if the result overflows 64 bits unsigned,
151 -- then the rounded result is clearly zero (since the dividend is at
152 -- most 2**63 - 1, the extra bit of precision is nice here).
164 T2 := (if Zhi /= 0 then Ylo * Zhi else 0);
176 Du := Lo (T2) & Lo (T1);
178 -- Set final signs (RM 4.5.5(27-30))
180 Den_Pos := (Y < 0) = (Z < 0);
182 -- Check overflow case of largest negative number divided by 1
184 if X = Int64'First and then Du = 1 and then not Den_Pos then
188 -- Perform the actual division
193 -- Deal with rounding case
195 if Round and then Ru > (Du - Uns64'(1)) / Uns64
'(2) then
196 Qu := Qu + Uns64'(1);
199 -- Case of dividend (X) sign positive
203 Q
:= (if Den_Pos
then To_Int
(Qu
) else -To_Int
(Qu
));
205 -- Case of dividend (X) sign negative
209 Q
:= (if Den_Pos
then -To_Int
(Qu
) else To_Int
(Qu
));
217 function Le3
(X1
, X2
, X3
: Uns32
; Y1
, Y2
, Y3
: Uns32
) return Boolean is
232 -------------------------------
233 -- Multiply_With_Ovflo_Check --
234 -------------------------------
236 function Multiply_With_Ovflo_Check
(X
, Y
: Int64
) return Int64
is
237 Xu
: constant Uns64
:= abs X
;
238 Xhi
: constant Uns32
:= Hi
(Xu
);
239 Xlo
: constant Uns32
:= Lo
(Xu
);
241 Yu
: constant Uns64
:= abs Y
;
242 Yhi
: constant Uns32
:= Hi
(Yu
);
243 Ylo
: constant Uns32
:= Lo
(Yu
);
258 else -- Yhi = Xhi = 0
262 -- Here we have T2 set to the contribution to the upper half
263 -- of the result from the upper halves of the input values.
272 T2
:= Lo
(T2
) & Lo
(T1
);
276 return To_Pos_Int
(T2
);
278 return To_Neg_Int
(T2
);
282 return To_Pos_Int
(T2
);
284 return To_Neg_Int
(T2
);
288 end Multiply_With_Ovflo_Check
;
294 procedure Raise_Error
is
296 raise Constraint_Error
with "64-bit arithmetic overflow";
303 procedure Scaled_Divide
308 Xu
: constant Uns64
:= abs X
;
309 Xhi
: constant Uns32
:= Hi
(Xu
);
310 Xlo
: constant Uns32
:= Lo
(Xu
);
312 Yu
: constant Uns64
:= abs Y
;
313 Yhi
: constant Uns32
:= Hi
(Yu
);
314 Ylo
: constant Uns32
:= Lo
(Yu
);
317 Zhi
: Uns32
:= Hi
(Zu
);
318 Zlo
: Uns32
:= Lo
(Zu
);
320 D
: array (1 .. 4) of Uns32
;
321 -- The dividend, four digits (D(1) is high order)
323 Qd
: array (1 .. 2) of Uns32
;
324 -- The quotient digits, two digits (Qd(1) is high order)
327 -- Value to subtract, three digits (S1 is high order)
331 -- Unsigned quotient and remainder
334 -- Scaling factor used for multiple-precision divide. Dividend and
335 -- Divisor are multiplied by 2 ** Scale, and the final remainder
336 -- is divided by the scaling factor. The reason for this scaling
337 -- is to allow more accurate estimation of quotient digits.
343 -- First do the multiplication, giving the four digit dividend
351 T2
:= D
(3) + Lo
(T1
);
353 D
(2) := Hi
(T1
) + Hi
(T2
);
357 T2
:= D
(3) + Lo
(T1
);
359 T3
:= D
(2) + Hi
(T1
);
364 T1
:= (D
(1) & D
(2)) + Uns64
'(Xhi * Yhi);
375 T2 := D (3) + Lo (T1);
377 D (2) := Hi (T1) + Hi (T2);
386 -- Now it is time for the dreaded multiple precision division. First
387 -- an easy case, check for the simple case of a one digit divisor.
390 if D (1) /= 0 or else D (2) >= Zlo then
393 -- Here we are dividing at most three digits by one digit
397 T2 := Lo (T1 rem Zlo) & D (4);
399 Qu := Lo (T1 / Zlo) & Lo (T2 / Zlo);
403 -- If divisor is double digit and too large, raise error
405 elsif (D (1) & D (2)) >= Zu then
408 -- This is the complex case where we definitely have a double digit
409 -- divisor and a dividend of at least three digits. We use the classical
410 -- multiple division algorithm (see section (4.3.1) of Knuth's "The Art
411 -- of Computer Programming", Vol. 2 for a description (algorithm D).
414 -- First normalize the divisor so that it has the leading bit on.
415 -- We do this by finding the appropriate left shift amount.
419 if (Zhi and 16#FFFF0000#) = 0 then
421 Zu := Shift_Left (Zu, 16);
424 if (Hi (Zu) and 16#FF00_0000#) = 0 then
426 Zu := Shift_Left (Zu, 8);
429 if (Hi (Zu) and 16#F000_0000#) = 0 then
431 Zu := Shift_Left (Zu, 4);
434 if (Hi (Zu) and 16#C000_0000#) = 0 then
436 Zu := Shift_Left (Zu, 2);
439 if (Hi (Zu) and 16#8000_0000#) = 0 then
441 Zu := Shift_Left (Zu, 1);
447 -- Note that when we scale up the dividend, it still fits in four
448 -- digits, since we already tested for overflow, and scaling does
449 -- not change the invariant that (D (1) & D (2)) >= Zu.
451 T1 := Shift_Left (D (1) & D (2), Scale);
453 T2 := Shift_Left (0 & D (3), Scale);
454 D (2) := Lo (T1) or Hi (T2);
455 T3 := Shift_Left (0 & D (4), Scale);
456 D (3) := Lo (T2) or Hi (T3);
459 -- Loop to compute quotient digits, runs twice for Qd(1) and Qd(2)
463 -- Compute next quotient digit. We have to divide three digits by
464 -- two digits. We estimate the quotient by dividing the leading
465 -- two digits by the leading digit. Given the scaling we did above
466 -- which ensured the first bit of the divisor is set, this gives
467 -- an estimate of the quotient that is at most two too high.
469 Qd (J + 1) := (if D (J + 1) = Zhi
471 else Lo ((D (J + 1) & D (J + 2)) / Zhi));
473 -- Compute amount to subtract
475 T1 := Qd (J + 1) * Zlo;
476 T2 := Qd (J + 1) * Zhi;
478 T1 := Hi (T1) + Lo (T2);
480 S1 := Hi (T1) + Hi (T2);
482 -- Adjust quotient digit if it was too high
485 exit when Le3 (S1, S2, S3, D (J + 1), D (J + 2), D (J + 3));
486 Qd (J + 1) := Qd (J + 1) - 1;
487 Sub3 (S1, S2, S3, 0, Zhi, Zlo);
490 -- Now subtract S1&S2&S3 from D1&D2&D3 ready for next step
492 Sub3 (D (J + 1), D (J + 2), D (J + 3), S1, S2, S3);
495 -- The two quotient digits are now set, and the remainder of the
496 -- scaled division is in D3&D4. To get the remainder for the
497 -- original unscaled division, we rescale this dividend.
499 -- We rescale the divisor as well, to make the proper comparison
500 -- for rounding below.
502 Qu := Qd (1) & Qd (2);
503 Ru := Shift_Right (D (3) & D (4), Scale);
504 Zu := Shift_Right (Zu, Scale);
507 -- Deal with rounding case
509 if Round and then Ru > (Zu - Uns64'(1)) / Uns64
'(2) then
510 Qu := Qu + Uns64 (1);
513 -- Set final signs (RM 4.5.5(27-30))
515 -- Case of dividend (X * Y) sign positive
517 if (X >= 0 and then Y >= 0) or else (X < 0 and then Y < 0) then
518 R := To_Pos_Int (Ru);
519 Q := (if Z > 0 then To_Pos_Int (Qu) else To_Neg_Int (Qu));
521 -- Case of dividend (X * Y) sign negative
524 R := To_Neg_Int (Ru);
525 Q := (if Z > 0 then To_Neg_Int (Qu) else To_Pos_Int (Qu));
533 procedure Sub3 (X1, X2, X3 : in out Uns32; Y1, Y2, Y3 : Uns32) is
553 -------------------------------
554 -- Subtract_With_Ovflo_Check --
555 -------------------------------
557 function Subtract_With_Ovflo_Check (X, Y : Int64) return Int64 is
558 R : constant Int64 := To_Int (To_Uns (X) - To_Uns (Y));
562 if Y > 0 or else R >= 0 then
567 if Y <= 0 or else R < 0 then
573 end Subtract_With_Ovflo_Check;
579 function To_Neg_Int (A : Uns64) return Int64 is
580 R : constant Int64 := -To_Int (A);
593 function To_Pos_Int (A : Uns64) return Int64 is
594 R : constant Int64 := To_Int (A);