Skip to content

Commit

Permalink
FIXED: gcd function for LibBF on platforms with 32 bit long.
Browse files Browse the repository at this point in the history
  • Loading branch information
JanWielemaker committed Nov 2, 2023
1 parent e76940f commit 5b6ed48
Show file tree
Hide file tree
Showing 3 changed files with 19 additions and 3 deletions.
4 changes: 2 additions & 2 deletions src/Tests/rational/test_rational.pl
Original file line number Diff line number Diff line change
Expand Up @@ -202,11 +202,11 @@
test(roundtrip_rational) :-
forall(between(1,1000,_),
( rfloat(F),
F =:= rational(F))).
assertion(F =:= rational(F)))).
test(roundtrip_rationalize) :-
forall(between(1,1000,_),
( rfloat(F),
F =:= rationalize(F))).
assertion(F =:= rationalize(F)))).

:- end_tests(rationalize).

Expand Down
2 changes: 1 addition & 1 deletion src/libbf/bf_gmp.c
Original file line number Diff line number Diff line change
Expand Up @@ -163,7 +163,7 @@ mpz_gcd(mpz_t r, const mpz_t n1, const mpz_t n2)
{ // a and b always odd at start of loop
if ((a->expn < INT64BITSIZE) && (b->expn <INT64BITSIZE))
{ // both fit in 64 bit integers; get int64 values and use int64 gcd
mpz_set_ui(r, (unsigned long)i64_gcd(mpz_get_si(a), mpz_get_si(b)));
mpz_set_ui64(r, i64_gcd(mpz_get_si64(a), mpz_get_si64(b)));
break; // we're done, exit while loop
}
mpz_sub(r,a,b); // a-b -> r is now even, b still odd
Expand Down
16 changes: 16 additions & 0 deletions src/libbf/bf_gmp.h
Original file line number Diff line number Diff line change
Expand Up @@ -135,6 +135,11 @@ mpz_set_ui(mpz_t r, unsigned long n)
{ bf_set_ui(r, n);
}

static inline void
mpz_set_ui64(mpz_t r, int64_t n)
{ bf_set_ui(r, n);
}

static inline void
mpz_set_si(mpz_t r, long n)
{ bf_set_si(r, n);
Expand Down Expand Up @@ -177,6 +182,17 @@ mpz_get_si(const mpz_t n)
return 0;
}

static inline int64_t
mpz_get_si64(const mpz_t n)
{ int64_t nv;

if ( bf_get_int64(&nv, n, BF_RNDN) == 0 )
return nv;

assert(0); /* TBD: return least significant bits */
return 0;
}

static inline unsigned long
mpz_get_ui(const mpz_t n)
{ int64_t v;
Expand Down

0 comments on commit 5b6ed48

Please sign in to comment.