diff options
-rw-r--r-- | otherlibs/num/arith_status.mli | 23 | ||||
-rw-r--r-- | otherlibs/num/big_int.mli | 83 | ||||
-rw-r--r-- | otherlibs/num/num.mli | 93 |
3 files changed, 111 insertions, 88 deletions
diff --git a/otherlibs/num/arith_status.mli b/otherlibs/num/arith_status.mli index 41c15f962..13a3e12fd 100644 --- a/otherlibs/num/arith_status.mli +++ b/otherlibs/num/arith_status.mli @@ -12,38 +12,47 @@ (* $Id$ *) -(* Module [Arith_status]: flags that control rational arithmetic *) +(** Flags that control rational arithmetic. *) val arith_status: unit -> unit - (* Print the current status of the arithmetic flags. *) + (** Print the current status of the arithmetic flags. *) val get_error_when_null_denominator : unit -> bool + (** See {!Arith_status.set_error_when_null_denominator}.*) val set_error_when_null_denominator : bool -> unit - (* Get or set the flag [null_denominator]. When on, attempting to + (** Get or set the flag [null_denominator]. When on, attempting to create a rational with a null denominator raises an exception. When off, rationals with null denominators are accepted. Initially: on. *) + val get_normalize_ratio : unit -> bool + (** See {!Arith_status.set_normalize_ratio}.*) val set_normalize_ratio : bool -> unit - (* Get or set the flag [normalize_ratio]. When on, rational + (** Get or set the flag [normalize_ratio]. When on, rational numbers are normalized after each operation. When off, rational numbers are not normalized until printed. Initially: off. *) + val get_normalize_ratio_when_printing : unit -> bool + (** See {!Arith_status.set_normalize_ratio_when_printing}.*) val set_normalize_ratio_when_printing : bool -> unit - (* Get or set the flag [normalize_ratio_when_printing]. + (** Get or set the flag [normalize_ratio_when_printing]. When on, rational numbers are normalized before being printed. When off, rational numbers are printed as is, without normalization. Initially: on. *) + val get_approx_printing : unit -> bool + (** See {!Arith_status.set_approx_printing}.*) val set_approx_printing : bool -> unit - (* Get or set the flag [approx_printing]. + (** Get or set the flag [approx_printing]. When on, rational numbers are printed as a decimal approximation. When off, rational numbers are printed as a fraction. Initially: off. *) + val get_floating_precision : unit -> int + (** See {!Arith_status.set_floating_precision}.*) val set_floating_precision : int -> unit - (* Get or set the parameter [floating_precision]. + (** Get or set the parameter [floating_precision]. This parameter is the number of digits displayed when [approx_printing] is on. Initially: 12. *) diff --git a/otherlibs/num/big_int.mli b/otherlibs/num/big_int.mli index c2dc034d4..715111709 100644 --- a/otherlibs/num/big_int.mli +++ b/otherlibs/num/big_int.mli @@ -12,78 +12,79 @@ (* $Id$ *) -(* Module [Big_int]: operations on arbitrary-precision integers *) +(** Operations on arbitrary-precision integers. -(* Big integers (type [big_int]) are signed integers of arbitrary size. *) + Big integers (type [big_int]) are signed integers of arbitrary size. +*) open Nat type big_int - (* The type of big integers. *) + (** The type of big integers. *) val zero_big_int : big_int - (* The big integer [0]. *) + (** The big integer [0]. *) val unit_big_int : big_int - (* The big integer [1]. *) + (** The big integer [1]. *) -(*** Arithmetic operations *) +(** {2 Arithmetic operations} *) val minus_big_int : big_int -> big_int - (* Unary negation. *) + (** Unary negation. *) val abs_big_int : big_int -> big_int - (* Absolute value. *) + (** Absolute value. *) val add_big_int : big_int -> big_int -> big_int - (* Addition. *) + (** Addition. *) val succ_big_int : big_int -> big_int - (* Successor (add 1). *) + (** Successor (add 1). *) val add_int_big_int : int -> big_int -> big_int - (* Addition of a small integer to a big integer. *) + (** Addition of a small integer to a big integer. *) val sub_big_int : big_int -> big_int -> big_int - (* Subtraction. *) + (** Subtraction. *) val pred_big_int : big_int -> big_int - (* Predecessor (subtract 1). *) + (** Predecessor (subtract 1). *) val mult_big_int : big_int -> big_int -> big_int - (* Multiplication of two big integers. *) + (** Multiplication of two big integers. *) val mult_int_big_int : int -> big_int -> big_int - (* Multiplication of a big integer by a small integer *) + (** Multiplication of a big integer by a small integer *) val square_big_int: big_int -> big_int - (* Return the square of the given big integer *) + (** Return the square of the given big integer *) val sqrt_big_int: big_int -> big_int - (* [sqrt_big_int a] returns the integer square root of [a], + (** [sqrt_big_int a] returns the integer square root of [a], that is, the largest big integer [r] such that [r * r <= a]. Raise [Invalid_argument] if [a] is negative. *) val quomod_big_int : big_int -> big_int -> big_int * big_int - (* Euclidean division of two big integers. + (** Euclidean division of two big integers. The first part of the result is the quotient, the second part is the remainder. Writing [(q,r) = quomod_big_int a b], we have [a = q * b + r] and [0 <= r < |b|]. Raise [Division_by_zero] if the divisor is zero. *) val div_big_int : big_int -> big_int -> big_int - (* Euclidean quotient of two big integers. + (** Euclidean quotient of two big integers. This is the first result [q] of [quomod_big_int] (see above). *) val mod_big_int : big_int -> big_int -> big_int - (* Euclidean modulus of two big integers. + (** Euclidean modulus of two big integers. This is the second result [r] of [quomod_big_int] (see above). *) val gcd_big_int : big_int -> big_int -> big_int - (* Greatest common divisor of two big integers. *) + (** Greatest common divisor of two big integers. *) val power_int_positive_int: int -> int -> big_int val power_big_int_positive_int: big_int -> int -> big_int val power_int_positive_big_int: int -> big_int -> big_int val power_big_int_positive_big_int: big_int -> big_int -> big_int - (* Exponentiation functions. Return the big integer + (** Exponentiation functions. Return the big integer representing the first argument [a] raised to the power [b] (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. *) -(*** Comparisons and tests *) +(** {2 Comparisons and tests} *) val sign_big_int : big_int -> int - (* Return [0] if the given big integer is zero, + (** Return [0] if the given big integer is zero, [1] if it is positive, and [-1] if it is negative. *) val compare_big_int : big_int -> big_int -> int - (* [compare_big_int a b] returns [0] if [a] and [b] are equal, + (** [compare_big_int a b] returns [0] if [a] and [b] are equal, [1] if [a] is greater than [b], and [-1] if [a] is smaller than [b]. *) val eq_big_int : big_int -> big_int -> bool @@ -91,48 +92,48 @@ val le_big_int : big_int -> big_int -> bool val ge_big_int : big_int -> big_int -> bool val lt_big_int : big_int -> big_int -> bool val gt_big_int : big_int -> big_int -> bool - (* Usual boolean comparisons between two big integers. *) + (** Usual boolean comparisons between two big integers. *) val max_big_int : big_int -> big_int -> big_int - (* Return the greater of its two arguments. *) + (** Return the greater of its two arguments. *) val min_big_int : big_int -> big_int -> big_int - (* Return the smaller of its two arguments. *) + (** Return the smaller of its two arguments. *) val num_digits_big_int : big_int -> int - (* Return the number of machine words used to store the + (** Return the number of machine words used to store the given big integer. *) -(*** Conversions to and from strings *) +(** {2 Conversions to and from strings} *) val string_of_big_int : big_int -> string - (* Return the string representation of the given big integer, + (** Return the string representation of the given big integer, in decimal (base 10). *) val big_int_of_string : string -> big_int - (* Convert a string to a big integer, in decimal. + (** Convert a string to a big integer, in decimal. The string consists of an optional [-] or [+] sign, followed by one or several decimal digits. *) -(*** Conversions to and from other numerical types *) +(** {2 Conversions to and from other numerical types} *) val big_int_of_int : int -> big_int - (* Convert a small integer to a big integer. *) + (** Convert a small integer to a big integer. *) val is_int_big_int : big_int -> bool - (* Test whether the given big integer is small enough to + (** Test whether the given big integer is small enough to be representable as a small integer (type [int]) without loss of precision. On a 32-bit platform, [is_int_big_int a] returns [true] if and only if - [a] is between $-2^{30}$ and $2^{30}-1$. On a 64-bit platform, + [a] is between 2{^30} and 2{^30}-1. On a 64-bit platform, [is_int_big_int a] returns [true] if and only if - [a] is between $-2^{62}$ and $2^{62}-1$. *) + [a] is between -2{^62} and 2{^62}-1. *) val int_of_big_int : big_int -> int - (* Convert a big integer to a small integer (type [int]). + (** Convert a big integer to a small integer (type [int]). Raises [Failure "int_of_big_int"] if the big integer is not representable as a small integer. *) val float_of_big_int : big_int -> float - (* Returns a floating-point number approximating the + (** Returns a floating-point number approximating the given big integer. *) -(*--*) +(**/**) -(*** For internal use *) +(** {2 For internal use} *) val nat_of_big_int : big_int -> nat val big_int_of_nat : nat -> big_int val base_power_big_int: int -> int -> big_int -> big_int diff --git a/otherlibs/num/num.mli b/otherlibs/num/num.mli index 26b0d9be8..9f60d613a 100644 --- a/otherlibs/num/num.mli +++ b/otherlibs/num/num.mli @@ -22,126 +22,139 @@ open Nat open Big_int open Ratio - (** The type of numbers. *) -type num = Int of int | Big_int of big_int | Ratio of ratio +type num = + Int of int + | Big_int of big_int + | Ratio of ratio (** {2 Arithmetic operations} *) +val ( +/ ) : num -> num -> num (** Same as {!Num.add_num}.*) -val (+/) : num -> num -> num -(** Addition *) + val add_num : num -> num -> num +(** Addition *) -(** Unary negation. *) val minus_num : num -> num +(** Unary negation. *) +val ( -/ ) : num -> num -> num (** Same as {!Num.sub_num}.*) -val (-/) : num -> num -> num -(** Subtraction *) + val sub_num : num -> num -> num +(** Subtraction *) -(** Same as {!Num.mult_num}.*) val ( */ ) : num -> num -> num -(** Multiplication *) +(** Same as {!Num.mult_num}.*) + val mult_num : num -> num -> num +(** Multiplication *) -(** Squaring *) val square_num : num -> num +(** Squaring *) +val ( // ) : num -> num -> num (** Same as {!Num.div_num}.*) -val (//) : num -> num -> num -(** Division *) + val div_num : num -> num -> num +(** Division *) -(** Euclidean division: quotient. *) val quo_num : num -> num -> num -(** Euclidean division: remainder. *) +(** Euclidean division: quotient. *) + val mod_num : num -> num -> num +(** Euclidean division: remainder. *) -(** Same as {!Num.power_num}. *) val ( **/ ) : num -> num -> num -(** Exponentiation *) +(** Same as {!Num.power_num}. *) + val power_num : num -> num -> num +(** Exponentiation *) -(** Absolute value. *) val abs_num : num -> num +(** Absolute value. *) +val succ_num : num -> num (** [succ n] is [n+1] *) -val succ_num: num -> num +val pred_num : num -> num (** [pred n] is [n-1] *) -val pred_num: num -> num +val incr_num : num ref -> unit (** [incr r] is [r:=!r+1], where [r] is a reference to a number. *) -val incr_num: num ref -> unit +val decr_num : num ref -> unit (** [decr r] is [r:=!r-1], where [r] is a reference to a number. *) -val decr_num: num ref -> unit -(** Test if a number is an integer *) val is_integer_num : num -> bool +(** Test if a number is an integer *) (** The four following functions approximate a number by an integer : *) +val integer_num : num -> num (** [integer_num n] returns the integer closest to [n]. In case of ties, rounds towards zero. *) -val integer_num : num -> num -(** [floor_num n] returns the largest integer smaller or equal to [n]. *) + val floor_num : num -> num +(** [floor_num n] returns the largest integer smaller or equal to [n]. *) + +val round_num : num -> num (** [round_num n] returns the integer closest to [n]. In case of ties, rounds off zero. *) -val round_num : num -> num -(** [ceiling_num n] returns the smallest integer bigger or equal to [n]. *) + val ceiling_num : num -> num +(** [ceiling_num n] returns the smallest integer bigger or equal to [n]. *) -(** Return [-1], [0] or [1] according to the sign of the argument. *) val sign_num : num -> int +(** Return [-1], [0] or [1] according to the sign of the argument. *) (** {3 Comparisons between numbers} *) -val (=/) : num -> num -> bool -val (</) : num -> num -> bool -val (>/) : num -> num -> bool -val (<=/) : num -> num -> bool -val (>=/) : num -> num -> bool -val (<>/) : num -> num -> bool +val ( =/ ) : num -> num -> bool +val ( </ ) : num -> num -> bool +val ( >/ ) : num -> num -> bool +val ( <=/ ) : num -> num -> bool +val ( >=/ ) : num -> num -> bool +val ( <>/ ) : num -> num -> bool val eq_num : num -> num -> bool val lt_num : num -> num -> bool val le_num : num -> num -> bool val gt_num : num -> num -> bool val ge_num : num -> num -> bool +val compare_num : num -> num -> int (** Return [-1], [0] or [1] if the first argument is less than, equal to, or greater than the second argument. *) -val compare_num : num -> num -> int -(** Return the greater of the two arguments. *) val max_num : num -> num -> num -(** Return the smaller of the two arguments. *) +(** Return the greater of the two arguments. *) + val min_num : num -> num -> num +(** Return the smaller of the two arguments. *) (** {2 Coercions with strings} *) -(** Convert a number to a string, using fractional notation. *) val string_of_num : num -> string +(** Convert a number to a string, using fractional notation. *) -(** See {!Num.approx_num_exp}.*) val approx_num_fix : int -> num -> string +(** See {!Num.approx_num_exp}.*) + +val approx_num_exp : int -> num -> string (** Approximate a number by a decimal. The first argument is the required precision. The second argument is the number to approximate. {!Num.approx_num_fix} uses decimal notation; the first argument is the number of digits after the decimal point. [approx_num_exp] uses scientific (exponential) notation; the first argument is the number of digits in the mantissa. *) -val approx_num_exp : int -> num -> string -(** Convert a string to a number. *) val num_of_string : string -> num +(** Convert a string to a number. *) (** {2 Coercions between numerical types} *) |