summaryrefslogtreecommitdiffstats
path: root/otherlibs/num
diff options
context:
space:
mode:
authorXavier Leroy <xavier.leroy@inria.fr>2002-03-11 08:34:47 +0000
committerXavier Leroy <xavier.leroy@inria.fr>2002-03-11 08:34:47 +0000
commitab2a1a5959b27285ae19a7b684df38121bfe3f9e (patch)
treeffb791dcd599a3831c5cd5a6c12bc842f92eb6d4 /otherlibs/num
parent8e945874cb05f5ef445986910dae59f4d184583b (diff)
Renommage modexp -> mod_power pour coherence avec le reste de la bibliotheque
git-svn-id: http://caml.inria.fr/svn/ocaml/trunk@4493 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02
Diffstat (limited to 'otherlibs/num')
-rw-r--r--otherlibs/num/big_int.ml6
-rw-r--r--otherlibs/num/big_int.mli2
-rw-r--r--otherlibs/num/nat.ml2
-rw-r--r--otherlibs/num/nat.mli2
-rw-r--r--otherlibs/num/test/test_big_ints.ml16
5 files changed, 14 insertions, 14 deletions
diff --git a/otherlibs/num/big_int.ml b/otherlibs/num/big_int.ml
index 7b1091096..253cee749 100644
--- a/otherlibs/num/big_int.ml
+++ b/otherlibs/num/big_int.ml
@@ -533,14 +533,14 @@ let base_power_big_int base n bi =
(* Modular exponentiation *)
-let modexp_big_int a b c =
+let mod_power_big_int a b c =
if b.sign < 0 || c.sign < 0 then invalid_arg "modexp_big_int";
if c.sign = 0 then raise Division_by_zero;
let na =
if a.sign < 0 || ge_big_int a c
- then mod_big_int a c
+ then mod_big_int a c (* normalize a in the range [0...c[ *)
else a in
- let res_nat = modexp_nat na.abs_value b.abs_value c.abs_value in
+ let res_nat = mod_power_nat na.abs_value b.abs_value c.abs_value in
{ sign = if is_zero_nat res_nat 0 (length_nat res_nat) then 0 else 1;
abs_value = res_nat }
diff --git a/otherlibs/num/big_int.mli b/otherlibs/num/big_int.mli
index a92354c47..9762fb93b 100644
--- a/otherlibs/num/big_int.mli
+++ b/otherlibs/num/big_int.mli
@@ -78,7 +78,7 @@ val power_big_int_positive_big_int: big_int -> big_int -> big_int
(the second argument). Depending
on the function, [a] and [b] can be either small integers
or big integers. Raise [Invalid_argument] if [b] is negative. *)
-val modexp_big_int: big_int -> big_int -> big_int -> big_int
+val mod_power_big_int: big_int -> big_int -> big_int -> big_int
(** Modular exponentiation. [modexp_big_int a b c] returns
[a] to the [b]-th power, modulo [c]. Raise [Invalid_argument]
if [b] or [c] are negative, and [Division_by_zero] if [c]
diff --git a/otherlibs/num/nat.ml b/otherlibs/num/nat.ml
index 3cc0fca4b..a8ab0f6a9 100644
--- a/otherlibs/num/nat.ml
+++ b/otherlibs/num/nat.ml
@@ -237,7 +237,7 @@ let sqrt_nat rad off len =
(* Modular exponentiation. Return a fresh nat equal to (a ^ b) mod c.
We assume c > 0 and a < c. *)
-let modexp_nat a b c =
+let mod_power_nat a b c =
let len_c = length_nat c in
let res = make_nat len_c in
set_digit_nat res 0 1;
diff --git a/otherlibs/num/nat.mli b/otherlibs/num/nat.mli
index a024e927a..21de1995f 100644
--- a/otherlibs/num/nat.mli
+++ b/otherlibs/num/nat.mli
@@ -63,7 +63,7 @@ external lxor_digit_nat: nat -> int -> nat -> int -> unit = "lxor_digit_nat"
val square_nat : nat -> int -> int -> nat -> int -> int -> int
val gcd_nat : nat -> int -> int -> nat -> int -> int -> int
val sqrt_nat : nat -> int -> int -> nat
-val modexp_nat : nat -> nat -> nat -> nat
+val mod_power_nat : nat -> nat -> nat -> nat
val string_of_nat : nat -> string
val nat_of_string : string -> nat
val sys_nat_of_string : int -> string -> int -> int -> nat
diff --git a/otherlibs/num/test/test_big_ints.ml b/otherlibs/num/test/test_big_ints.ml
index 2335d2edd..ed7dcdcdf 100644
--- a/otherlibs/num/test/test_big_ints.ml
+++ b/otherlibs/num/test/test_big_ints.ml
@@ -467,23 +467,23 @@ test 3 eq_big_int
test 4 eq_big_int
(square_big_int (big_int_of_string "-7"), big_int_of_string "49");;
-testing_function "modexp_big_int";;
+testing_function "mod_power_big_int";;
test 1 eq_big_int
- (modexp_big_int (big_int_of_int 0) (big_int_of_int 0) (big_int_of_int 42),
+ (mod_power_big_int (big_int_of_int 0) (big_int_of_int 0) (big_int_of_int 42),
big_int_of_int 1);;
test 2 eq_big_int
- (modexp_big_int (big_int_of_int 0) (big_int_of_int 1) (big_int_of_int 42),
+ (mod_power_big_int (big_int_of_int 0) (big_int_of_int 1) (big_int_of_int 42),
big_int_of_int 0);;
test 3 eq_big_int
- (modexp_big_int (big_int_of_int 12345) (big_int_of_int 6789)
- (big_int_of_string "4782546123567"),
+ (mod_power_big_int (big_int_of_int 12345) (big_int_of_int 6789)
+ (big_int_of_string "4782546123567"),
big_int_of_string "3726846414024");;
test 4 eq_big_int
- (modexp_big_int (big_int_of_int (-12345)) (big_int_of_int 6789)
+ (mod_power_big_int (big_int_of_int (-12345)) (big_int_of_int 6789)
(big_int_of_string "4782546123567"),
big_int_of_string "1055699709543");;
test 5 eq_big_int
- (modexp_big_int (big_int_of_string "200866937202159") (big_int_of_int 6789)
- (big_int_of_string "4782546123567"),
+ (mod_power_big_int (big_int_of_string "200866937202159") (big_int_of_int 6789)
+ (big_int_of_string "4782546123567"),
big_int_of_string "3726846414024");;