Code Monkey home page Code Monkey logo

zarith's Introduction

The Zarith library

OVERVIEW

This library implements arithmetic and logical operations over arbitrary-precision integers.

The module is simply named Z. Its interface is similar to that of the Int32, Int64 and Nativeint modules from the OCaml standard library, with some additional functions. See the file z.mli for documentation.

The implementation uses GMP (the GNU Multiple Precision arithmetic library) to compute over big integers. However, small integers are represented as unboxed Caml integers, to save space and improve performance. Big integers are allocated in the Caml heap, bypassing GMP's memory management and achieving better GC behavior than e.g. the MLGMP library. Computations on small integers use a special, faster path (in C or OCaml) eschewing calls to GMP, while computations on large intergers use the low-level MPN functions from GMP.

Arbitrary-precision integers can be compared correctly using OCaml's polymorphic comparison operators (=, <, >, etc.).

Additional features include:

  • a module Q for rationals, built on top of Z (see q.mli)
  • a compatibility layer Big_int_Z that implements the same API as Big_int from the legacy Num library, but uses Z internally

Support for js_of_ocaml is provided by Zarith_stubs_js.

REQUIREMENTS

  • OCaml, version 4.04.0 or later.
  • Either the GMP library or the MPIR library, including development files.
  • GCC or Clang or a gcc-compatible C compiler and assembler (other compilers may work).
  • The Findlib package manager (optional, recommended).

INSTALLATION

  1. First, run the "configure" script by typing:
   ./configure

The configure script has a few options. Use the -help option to get a list and short description of each option.

  1. It creates a Makefile, which can be invoked by:
   make

This builds native and bytecode versions of the library.

  1. The libraries are installed by typing:
   make install

or, if you install to a system location but are not an administrator

   sudo make install

If Findlib is detected, it is used to install files. Otherwise, the files are copied to a zarith/ subdirectory of the directory given by ocamlc -where.

The libraries are named zarith.cmxa and zarith.cma, and the Findlib module is named zarith.

Compiling and linking with the library requires passing the -I +zarith option to ocamlc / ocamlopt, or the -package zarith option to ocamlfind.

  1. (optional, recommended) Test programs are built and run by the additional command
  make tests

(but these are not installed).

  1. (optional) HTML API documentation is built (using ocamldoc) by the additional command
  make doc

ONLINE DOCUMENTATION

The documentation for the latest release is hosted on GitHub Pages.

LICENSE

This Library is distributed under the terms of the GNU Library General Public License version 2, with a special exception allowing unconstrained static linking. See LICENSE file for details.

AUTHORS

  • Antoine Miné, Sorbonne Université, formerly at ENS Paris.
  • Xavier Leroy, Collège de France, formerly at Inria Paris.
  • Pascal Cuoq, TrustInSoft.
  • Christophe Troestler (toplevel module)

COPYRIGHT

Copyright (c) 2010-2011 Antoine Miné, Abstraction project. Abstraction is part of the LIENS (Laboratoire d'Informatique de l'ENS), a joint laboratory by: CNRS (Centre national de la recherche scientifique, France), ENS (École normale supérieure, Paris, France), INRIA Rocquencourt (Institut national de recherche en informatique, France).

CONTENTS

Source files Description
configure configuration script
z.ml[i] Z module and implementation for small integers
caml_z.c C implementation
big_int_z.ml[i] wrapper to provide a Big_int compatible API to Z
q.ml[i] rational library, pure OCaml on top of Z
zarith_top.ml toplevel module to provide pretty-printing
projet.mak builds Z, Q and the tests
zarith.opam package description for opam
z_mlgmpidl.ml[i] conversion between Zarith and MLGMPIDL
tests/ simple regression tests and benchmarks

zarith's People

Contributors

4y8 avatar antoinemine avatar atupone avatar avsm avatar bschommer avatar c-cube avatar chris00 avatar concatime avatar dhil avatar dra27 avatar et7f3 avatar ghilesz avatar hhugo avatar jsmolic avatar liyishuai avatar martin-neuhaeusser avatar mroch avatar murmour avatar pascal-cuoq avatar pirbo avatar psafont avatar recoules avatar silene avatar sim642 avatar snoopy0815 avatar vbgl avatar xavierleroy avatar xclerc avatar

Stargazers

 avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar

Watchers

 avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar

zarith's Issues

Q.of_string doesn't follow the documentation

In particular, it only parses fractions, e.g., 100221/19, rather than parsing decimals like 122.12.

The documentation, however, says this:

(** Converts a string to a rational.
    Plain decimals, and [/] separated decimal ratios (with optional sign) are
    understood.
    Additionally, the special [inf], [-inf], and [undef] are recognized
    (they can also be typeset respectively as [1/0], [-1/0], [0/0]).
 *)

The behavior is clear enough from looking at the implementation.

let of_string s =
  try
    let i  = String.index s '/' in
    make
      (Z.of_substring s ~pos:0 ~len:i)
      (Z.of_substring s ~pos:(i+1) ~len:(String.length s-i-1))
  with Not_found ->
    if s = "inf" || s = "+inf" then inf
    else if s = "-inf" then minus_inf
    else if s = "undef" then undef
    else of_bigint (Z.of_string s)

I do think it would be great to support "plain decimals", but I suppose the minimum fix is to update the comment.

Please document error behaviour of Z.of_string

z.mli does not mention what happens if the string given to Z.of_string does not correctly specify an integer. It would be nice to be able to catch some exception in that case. Please add error behaviour specification. (Maybe to other functions as well; Z.of_string just is the one that caught my attention.)

asking for a release

now that #79 and #94 are meged, it would be great to have a release of zarith :)

thanks a lot for your work.

install cmt{,i} files

Right now it seems that they are not installed, which prevents merlin from accessing the documentation of functions

Z.one Error : Unbound module Z

Hello

i have installed zarith with

opam depext zarith
opam install zarith

and with ocaml-top
i have to put this way

#load "/Users/uio/.opam/system/lib/zarith/zarith.cma";;

because #load "zarith.cma";; doesn't work (cannot find file zarith.cma)

with function example test from zarith source

let rec fib_z n =
if n < 2 then Z.one else Z.add (fib_z(n-1)) (fib_z(n-2))

i get

...Z.one Error : Unbound module Z

Here my PATH
echo $PATH
/Users/uio/.opam/system/bin:/Library/Frameworks/Python.framework/Versions/3.6/bin:/usr/local/bin:/usr/bin:/bin:/usr/sbin:/sbin:/opt/X11/bin

Thanks

Zarith compilation fails in 32bit OCaml switches on a 64bit host.

Ubuntu 18.04, opam 2.0, switch is 4.07.0+32bit:

./configure 
binary ocaml: found in /home/egallego/.opam/4.07.0+32bit/bin
binary ocamlc: found in /home/egallego/.opam/4.07.0+32bit/bin
binary ocamldep: found in /home/egallego/.opam/4.07.0+32bit/bin
binary ocamlmklib: found in /home/egallego/.opam/4.07.0+32bit/bin
binary ocamldoc: found in /home/egallego/.opam/4.07.0+32bit/bin
binary ar: found in /usr/bin
binary perl: found in /usr/bin
binary gcc: found in /usr/bin
binary ocamlopt: found in /home/egallego/.opam/4.07.0+32bit/bin
checking compilation with gcc -O3 -Wall -Wextra : working
include caml/mlvalues.h: found
library dynlink.cmxa: found
binary ocamlfind: found in /home/egallego/.opam/4.07.0+32bit/bin
OCaml's word size is 32
binary uname: found in /bin
include gmp.h: found
library gmp: found
OCaml extended comparison supported
OCaml new hash functions available
OCaml supports -bin-annot to produce documentation

detected configuration:

  native-code:          yes
  dynamic linking:      yes
  asm path:             x86_64
  defines:              -DZ_OCAML_HASH -DZ_OCAML_COMPARE_EXT -DHAS_GMP -DZ_ELF -DZ_DOT_LABEL_PREFIX 
  libraries:             -lgmp
  C options:            -O3 -Wall -Wextra 
  asm options           
  installation path:    /home/egallego/.opam/4.07.0+32bit/lib
  installation method   findlib
$ make
project.mak:151: depend: No existe el archivo o el directorio
./z_pp.pl x86_64
Name "main::extra" used only once: possible typo at ./z_pp.pl line 29.
found assembly file caml_z_x86_64.S
  found abs
  found add
  found div
  found divexact
  found logand
  found lognot
  found logor
  found logxor
  found mul
  found neg
  found pred
  found rem
  found shift_left
  found shift_right
  found sub
  found succ
ocamldep -native  z.ml q.ml big_int_Z.ml z.mli q.mli big_int_Z.mli > depend
ocamlc -I +compiler-libs -bin-annot  -c z.mli
ocamlc -I +compiler-libs -bin-annot  -c z.ml
ocamlc -I +compiler-libs -bin-annot  -c q.mli
ocamlc -I +compiler-libs -bin-annot  -c q.ml
ocamlc -I +compiler-libs -bin-annot  -c big_int_Z.mli
ocamlc -I +compiler-libs -bin-annot  -c big_int_Z.ml
ocamlmklib -failsafe -o zarith z.cmo q.cmo big_int_Z.cmo -lgmp
gcc -DZ_OCAML_HASH -DZ_OCAML_COMPARE_EXT -DHAS_GMP -DZ_ELF -DZ_DOT_LABEL_PREFIX     -c -o caml_z_x86_64.o caml_z_x86_64.S
ocamlc -ccopt "-I/home/egallego/.opam/4.07.0+32bit/lib/ocaml  -DZ_OCAML_HASH -DZ_OCAML_COMPARE_EXT -DHAS_GMP -DZ_ELF -DZ_DOT_LABEL_PREFIX  -O3 -Wall -Wextra " -c caml_z.c
ocamlmklib -failsafe -o zarith caml_z_x86_64.o caml_z.o -lgmp
/usr/bin/ld: la arquitectura i386:x86-64 del fichero de entrada `caml_z_x86_64.o' es incompatible con la salida i386
collect2: error: ld returned 1 exit status
ocamlc -I +compiler-libs -bin-annot  -c zarith_top.ml
ocamlc -o zarith_top.cma -a zarith_top.cmo
ocamlopt -I +compiler-libs  -c z.ml
ocamlopt -I +compiler-libs  -c q.ml
ocamlopt -I +compiler-libs  -c big_int_Z.ml
ocamlmklib -failsafe -o zarith z.cmx q.cmx big_int_Z.cmx -lgmp
ocamlopt -shared -o zarith.cmxs -I . zarith.cmxa -linkall
/usr/bin/ld: se salta el ./libzarith.a incompatible mientras se busca -lzarith
/usr/bin/ld: no se puede encontrar -lzarith
collect2: error: ld returned 1 exit status
File "caml_startup", line 1:
Error: Error during linking
project.mak:79: recipe for target 'zarith.cmxs' failed
make: *** [zarith.cmxs] Error 2

Build failure: INT_MAX undeclared (first use in this function)

$ ./configure 
binary ocaml: found in /xxx/4.08.0/bin
binary ocamlc: found in /xxx/4.08.0/bin
binary ocamldep: found in /xxx/4.08.0/bin
binary ocamlmklib: found in /xxx/4.08.0/bin
binary ocamldoc: found in /xxx/4.08.0/bin
binary ar: found in /usr/bin
binary perl: found in /usr/bin
binary gcc: found in /usr/lib64/ccache
binary ocamlopt: found in /xxx/4.08.0/bin
checking compilation with gcc -O3 -Wall -Wextra : working
include caml/mlvalues.h: found
library dynlink.cmxa: found
binary ocamlfind: found in /xxx/4.08.0/bin
OCaml's word size is 64
binary uname: found in /usr/bin
include gmp.h: found
library gmp: found
OCaml extended comparison supported
OCaml new hash functions available
OCaml supports -bin-annot to produce documentation

detected configuration:

  native-code:          yes
  dynamic linking:      yes
  asm path:             x86_64
  defines:              -DZ_OCAML_HASH -DZ_OCAML_COMPARE_EXT -DHAS_GMP -DZ_ELF -DZ_DOT_LABEL_PREFIX 
  libraries:             -lgmp
  C options:            -O3 -Wall -Wextra 
  asm options           
  installation path:    /xxx/4.08.0/lib
  installation method   findlib

configuration successful!
now type "make" to build
then type "make install" or "sudo make install" to install
$ make
project.mak:151: depend: No such file or directory
./z_pp.pl x86_64
Name "main::extra" used only once: possible typo at ./z_pp.pl line 29.
found assembly file caml_z_x86_64.S
  found abs
  found add
  found div
  found divexact
  found logand
  found lognot
  found logor
  found logxor
  found mul
  found neg
  found pred
  found rem
  found shift_left
  found shift_right
  found sub
  found succ
ocamldep -native  z.ml q.ml big_int_Z.ml z.mli q.mli big_int_Z.mli > depend
ocamlc -I +compiler-libs -bin-annot  -c z.mli
ocamlc -I +compiler-libs -bin-annot  -c z.ml
ocamlc -I +compiler-libs -bin-annot  -c q.mli
ocamlc -I +compiler-libs -bin-annot  -c q.ml
ocamlc -I +compiler-libs -bin-annot  -c big_int_Z.mli
ocamlc -I +compiler-libs -bin-annot  -c big_int_Z.ml
ocamlmklib -failsafe -o zarith z.cmo q.cmo big_int_Z.cmo -lgmp
gcc -DZ_OCAML_HASH -DZ_OCAML_COMPARE_EXT -DHAS_GMP -DZ_ELF -DZ_DOT_LABEL_PREFIX     -c -o caml_z_x86_64.o caml_z_x86_64.S
ocamlc -ccopt "-I/xxx/4.08.0/lib/ocaml  -DZ_OCAML_HASH -DZ_OCAML_COMPARE_EXT -DHAS_GMP -DZ_ELF -DZ_DOT_LABEL_PREFIX  -O3 -Wall -Wextra " -c caml_z.c
caml_z.c: In function ‘ml_z_mpz_set_z’:
caml_z.c:2573:31: error: ‘INT_MAX’ undeclared (first use in this function)
   if (size_op * Z_LIMB_BITS > INT_MAX)
                               ^
caml_z.c:2573:31: note: each undeclared identifier is reported only once for each function it appears in
caml_z.c: In function ‘ml_z_pow’:
caml_z.c:2739:16: error: ‘INT_MAX’ undeclared (first use in this function)
   if (ralloc > INT_MAX)
                ^
make: *** [caml_z.o] Error 2

min_int has two representations

Consider min_int, the smallest value of type int.

When converted to Z.t using Z.of_int, it is represented as a tagged integer:

# let a = Z.of_int min_int;;
val a : Z.t = <abstr>
# Obj.tag (Obj.repr a);;
- : int = 1000

But when min_int is produced as the result of a big int computation, it is represented as a heap-allocated custom block:

# let b = Z.succ (Z.pred a);;
val b : Z.t = <abstr>
# Obj.tag (Obj.repr b);;
- : int = 255

That's because ml_z_reduce in caml_z.c decides to return a tagged integer if abs(result) <= max_int, not if min_int <= result <= max_int.

At first I thought this double representation is harmless, since Zarith functions seem to do the right thing, even equality:

# a = b;;
- : bool = true

However, hashing is confused: (see also #81)

# Hashtbl.hash a;;
- : int = 69827754
# Hashtbl.hash b;;
- : int = 694698810

Also, if it was not for this double representation of min_int, we could optimize the fast path of certain operations. For example, equality Z.equal x y could be

   if is_long(x) || is_long(y) then x == y else (* slow path *)

since a small Z.t and a big Z.t would never be equal, and == returns false when comparing their value representations. Z.compare can also be improved along the same lines.

Opinions?

Overflow in Big_int_Z.power_int_positive_int

When given a ridiculously large number, Big_int_Z.power_int_positive_int aborts with the message:

gmp: overflow in mpz type

In some cases, it would be better to be able to capture the error or to terminate in a less abrupt way.

For instance, the following program triggers this behavior:

let () =
  let _ = Big_int_Z.power_int_positive_int 5 999999999999999 in
  ()

It seems the issue is in function ml_z_pow, in caml_z.c, when calling mpz_pow_ui(mbase, mbase, e);

The real issue seems to be upstream in gmp (e.g. https://stackoverflow.com/questions/3558684, https://stackoverflow.com/questions/13328409), but I wonder if something could be done in zarith to raise an OCaml exception instead.

(approximate) conversion to float

Q is missing a to_float : t -> float function that converts the rational q to the floating point number to_float q that best approximates q.

Windows MSVC ABI compatible build

Hello,
I've been trying to get a Windows build compatible with MSVC ABI (to load a .dll in a MSVC compiled binary).
Has anyone managed to compile gmp/zarith in a setup like this ?

Problem with compilation - Unbound module Z, error during linking

Hi there,

I've been trying to get compilation with Zarith to work, but I'm having some trouble.

I have installed Zarith with the "opam install zarith" command. I also have everything from the Requirements section installed. I'm on Linux Mint 18.

Opam version is 1.2.2 and Ocaml version is 4.02.3.

The commands "opam list" and "ocamlfind list" do have zarith listed as an installed package.

I've tried to compile the code in different ways to no avail. Let's say I have a single line "let x = Z.of_int 4" in a test.ml file.

If I do compilation with "ocamlopt -I +zarith test.ml" I get:
Error: Unbound module Z

With "ocamlfind ocamlopt -package zarith test.ml":
test.o: In function camlTest__entry': test.ml:(.text+0xc): undefined reference to ml_z_of_int'
collect2: error: ld returned 1 exit status
File "caml_startup", line 1:
Error: Error during linking

I also tried "ocamlopt zarith.cmxa test.ml", which gives me:
Error: Cannot find file zarith.cmxa

However, in the OCaml TopLevel, if I call:
#require "zarith";;
#load "zarith.cma";;

I can use the module just fine, inside the TopLevel.

How could I fix this problem with the compilation? Thank you in advance.

ZArith's assembly file caml_z_x86_64_mingw64 is rejected due to non-executable stack statement

Building ZArith with assembly instructions for the fast path on Cygwin64/mingw-w64 fails
due to the instructions for making the stack non-executable that have been introduced by 96a8242.

The GCC version used is x86_64-w64-mingw32-gcc (GCC) 6.4.0, the error message reads:

caml_z_x86_64_mingw64.S: Assembler messages:
caml_z_x86_64_mingw64.S:24: Error: junk at end of line, first unrecognized character is `-'

Reverting the commit solves the issue (but leaves the stack executable).
Just replacing @progbits by %progbits (as proposed in #14) does not solve the issue on Cygwin/mingw-w64.

Given the other bug report #14 that concerns 96a8242, the change appears to be rather non-portable.
Is there a better solution available?

Sign on result of GCD is unpredictable

When numbers are small, the result of a call to gcd is positive when one parameter is zero, and the other parameter is negative.

However, when the negative value is "large", it returns a negative number.

At first glance, it appears that the "normalization" in the small-case happens here:
https://github.com/ocaml/Zarith/blob/master/caml_z.c#L1743

  let gcd_helper a b = gcd (Z.of_string a) (Z.of_string b) |> Z.print

  let%expect_test "" =
    gcd_helper "0" "-350854590609916240021621339209265605473999635689";
    [%expect "-350854590609916240021621339209265605473999635689"]
  ;;

  let%expect_test "" =
    gcd_helper "0" "-55";
    [%expect "55"]
  ;;

Q.to_float is not correct for denormal results

Consider the following example submitted by @mbarbin in 5463dbc#commitcomment-27324931:

(* q = 7.56181796669062E-309 *)
let q = Q.make (Z.of_string "756181796669062") (Z.pow (Z.of_int 10) (309+14));;

Printf.printf "%h\n" (Q.to_float q);;
(* 0x0.570020d1942p-1022 *)

Printf.printf "%h\n" 7.56181796669062E-309;;
(* 0x0.570020d1941ffp-1022 *)

The result of Q.to_float is not the FP number closest to the exact value.

@pascal-cuoq notes that the "round to odd" technique used in Q.to_float is incorrectly used in this particular case involving denormal FP numbers as the result.

`Q.compare` handles NaN surprisingly

Hi all,

I noticed that Q.compare has the following semantics for comparing with NaN:

let nan = Q.(zero / zero);;

Q.compare nan Q.(neg inf);;
(* -1 *)

Q.compare nan nan;;
(* 0 *)

This was a little surprising to me, as these comparisons imply that NaN is "smaller" than all other bignums, including negative infinity. More specifically, I was expecting a behaviour similar to IEEE 754 floating point, where all inequalities involving NaN return false, and NaN <> any value.

Looking at the code, it seems to me like this behaviour was deliberately chosen:
https://github.com/ocaml/Zarith/blob/cda0bb6/q.ml#L146
Could someone explain the rationale behind having NaN compare in this way?

Thanks in advance!
Cheng

Cannot enable executable stack on Ubuntu on Windows

Hi,

For « fun » I decided to try to build Prose (the collaborative text editor) on Windows/Ubuntu through its recent Linux subsystem. Well, for fun and to find out whether this subsystem could handle non-trivial workloads which include builds and packaging.

Build worked but ocsigenserver failed at runtime with the following error message:

Error: Error on dynamically loaded library: /home/prose/.opam/4.04.2/lib/stublibs/dllzarith.so: /home/prose/.opam/4.04.2/lib/stublibs/dllzarith.so: cannot enable executable stack as shared object requires: Invalid argument\n

I don't know if the requirement on an executable stack comes from Zarith or from GMP so maybe I'm filling this issue report in the wrong project.

Consider adding a mutable API

I tried implementing finite field arithmetic for GF2^n (here and here) but it performs horribly for large integers (e.g. several thousand bits long) due to the need to copy these around rather than mutating the values directly.

It would be nice if there were a mutable API for this purpose, e.g. inside a child module Z.Mutable or something.

Please make a new release

Hello!

It would really nice if you could cut a new release.

@antoinemine recently added this commit 96a8242 which fixes an important security issue that caused various memory mappings in programs using zarith to be both executable and writable at the same time, which makes it much easier for hackers to exploit vulnerabilities. Thanks to @antoinemine for spotting and fixing this, appreciate it a lot!

Since Zarith is used in security-critical libraries like https://github.com/mirleft/ocaml-nocrypto that are used to protect network-facing services, the inherited protection flags transitionally weakens the security of every ocaml library and program that use the current zarith releases. I ran into this problem while trying to figure out why my own library suddenly had executable stack.

I tested the patch by pinning the master branch of zarith, and confirmed that it correctly fixes the protection flags. A new release would enable nocrypto to update its dependency on zarith and mitigate the problem.

Polymorphic comparison over `Q.t` values

Is there a fundamental impediment to supporting OCaml's polymorphic comparison operators over Q.t values? Could it be done similarly to how it's done for Z.t values (e.g., via something like ml_z_custom_compare)?

If there's no fundamental issue making this not possible, we could perhaps try to do this.

Many thanks.

The functions Q.lt and '<' work differently.

This simple program prints res1=1 and res2=0, which is wrong. The second result should be 1 as well. Or am I missing something?

open Q

let by_function a b =
  if Q.lt a b then
    0
  else
    1

let by_infix a b =
  if a < b then
    0
  else
    1

let main () =
  let a = Q.of_float 100.0 in
  let b = of_float 0.001 in
  let res1 = by_function a b in
  let res2 = by_infix a b in
  let _ = Printf.printf "res1=%d\n" res1 in
  let _ = Printf.printf "res2=%d\n" res2 in
  0

let _ = main ()

The ocaml version is 4.02.3
The zarith library is 1.7, installed by opam:

$ opam show zarith
             package: zarith
             version: 1.7
          repository: default
        upstream-url: https://github.com/ocaml/Zarith/archive/release-1.7.tar.gz
       upstream-kind: http
   upstream-checksum: 80944e2755ebb848451a77dc2ad0651b
            homepage: https://github.com/ocaml/Zarith
         bug-reports: https://github.com/ocaml/Zarith/issues
            dev-repo: https://github.com/ocaml/Zarith.git
              author: Antoine Miné, Xavier Leroy, Pascal Cuoq
             depends: ocamlfind & conf-gmp & conf-perl
   installed-version: 1.7 [system]
  available-versions: 1.1, 1.2, 1.3, 1.4, 1.4.1, 1.5, 1.6, 1.7
         description: Implements arithmetic and logical operations over arbitrary-precision integers
The Zarith library implements arithmetic and logical operations over
arbitrary-precision integers. It uses GMP to efficiently implement
arithmetic over big integers. Small integers are represented as Caml
unboxed integers, for speed and space economy.

Add a decimal arithmetics

Decimal floating-point (DFP) arithmetic refers to both a representation and operations on decimal floating-point numbers. Working directly with decimal (base-10) fractions can avoid the rounding errors that otherwise typically occur when converting between decimal fractions (common in human-entered data, such as measurements or financial information) and binary (base-2) fractions.

The advantage of decimal floating-point representation over decimal fixed-point and integer representation is that it supports a much wider range of values. For example, while a fixed-point representation that allocates 8 decimal digits and 2 decimal places can represent the numbers 123456.78, 8765.43, 123.00, and so on, a floating-point representation with 8 decimal digits could also represent 1.2345678, 1234567.8, 0.000012345678, 12345678000000000, and so on. This wider range can dramatically slow the accumulation of rounding errors during successive calculations; for example, the Kahan summation algorithm can be used in floating point to add many numbers with no asymptotic accumulation of rounding error.
Fixed-length decimal point numbers are popular in various business applications, the most notorious example is COBOL written applications.

The Rust community for example, has three crates for dealing with decimal numbers: decimal, rust-decimal, and bigdecimal.

There seems some demand for this type of arithmetic in OCaml world too:

Aside "classic" decimal numbers there are also so called posits (unums) in OCaml - see examples in other languages. There are no benefits of using them while there is no hardware available, nevertheless it might be interesting to play with the software implementation for evaluation reasons.

See also Decimal Point Algorithms for Computers and Software Implementation of DecimalFloating-Point papers.

Make a release?

The latest release is quite old and trigger an OCaml warning on recent compilers because .cmx files are not shipped with the library.

Installation issue on Debian Jessie since version 1.6

unfortunately since this code update I'm not able anymore to install Zarith on Raspberry Debian Jessie :(

this is the error I get, after the command 'make':

pi@raspberrypi:~/.opam/system/build/zarith.1.6 $ make
gcc -DZ_OCAML_HASH -DZ_OCAML_COMPARE_EXT -DHAS_GMP     -c -o caml_z_arm.o caml_z_arm.S
caml_z_arm.S: Assembler messages:
caml_z_arm.S:25: Error: junk at end of line, first unrecognized character is `,'
<eingebaut>: die Regel für Ziel „caml_z_arm.o“ scheiterte
make: *** [caml_z_arm.o] Fehler 1

with earlier versions installation has been working without issues - and after commenting-out this line of code the problem vanishes as well...

do we really need this addition - or can we fix it in order to not break the installation on Debian Jessie?

Thanks for any hints / updates!
best regards.


[edited 11.10.2017 15:55]:
is related to #13

make install lacks DESTDIR support for findlib

There is appearantly no concept of DESTDIR. One can use --installdir to concat DESTDIR+$prefix, but ocamlfind does not cope with it:

[    4s] + make install DESTDIR=/home/abuild/rpmbuild/BUILDROOT/ocaml-zarith-1.9.1-190925162731.0.x86_64
[    4s] ocamlfind install -destdir "/home/abuild/rpmbuild/BUILDROOT/ocaml-zarith-1.9.1-190925162731.0.x86_64/usr/lib64/ocaml" zarith META zarith.h zarith.cma libzarith.a z.mli q.mli big_int_Z.mli z.cmi q.cmi big_int_Z.cmi zarith_top.cma zarith.a zarith.cmxa z.cmx q.cmx big_int_Z.cmx zarith.cmxs z.cmti q.cmti big_int_Z.cmti -optional dllzarith.so
[    4s] ocamlfind: Bad configuration: Cannot mkdir /home/abuild/rpmbuild/BUILDROOT/ocaml-zarith-1.9.1-190925162731.0.x86_64/usr/lib64/ocaml/zarith because a path component does not exist or is not a directory

Apparently the install -d command must also be used the findlib case.

win10 make failure - wait-process.c:298: undefined reference to `waitpid'

Hi guys,

When I tried to build and install Zarith, after configure it, it showed me below error.
I'm using windows 10, cygwin + OPAM (which provided by OCaml 64bit windows installation).

Could you give me some suggestions on it? Thank you very much!

The error:

Steve@DESKTOP-HI9GPS4 /cygdrive/d/zarith
$ make
make all-recursive
make[1]: Entering directory '/cygdrive/d/zarith'
Making all in .
make[2]: Entering directory '/cygdrive/d/zarith'
make[2]: Nothing to be done for 'all-am'.
make[2]: Leaving directory '/cygdrive/d/zarith'
Making all in examples
make[2]: Entering directory '/cygdrive/d/zarith/examples'
make[2]: Nothing to be done for 'all'.
make[2]: Leaving directory '/cygdrive/d/zarith/examples'
Making all in lib
make[2]: Entering directory '/cygdrive/d/zarith/lib'
make all-am
make[3]: Entering directory '/cygdrive/d/zarith/lib'
make[3]: Leaving directory '/cygdrive/d/zarith/lib'
make[2]: Leaving directory '/cygdrive/d/zarith/lib'
Making all in src
make[2]: Entering directory '/cygdrive/d/zarith/src'
x86_64-w64-mingw32-gcc.exe -g -O2 -o m4.exe m4.o builtin.o debug.o eval.o format.o freeze.o input.o macro.o output.o path.o symtab.o ../lib/libm4.a
../lib/libm4.a(wait-process.o): In function wait_subprocess': /cygdrive/d/m4/lib/wait-process.c:298: undefined reference to waitpid'
collect2: error: ld returned 1 exit status
make[2]: *** [Makefile:1491: m4.exe] Error 1
make[2]: Leaving directory '/cygdrive/d/zarith/src'
make[1]: *** [Makefile:1506: all-recursive] Error 1
make[1]: Leaving directory '/cygdrive/d/zarith'
make: *** [Makefile:1461:all] Error 2

Cheers,
Steve

ZArith's built-in test suite reports errors on 64bit Windows (both native and on Cygwin)

While working on #23, it occurred to me that ZArith's own test suite consistently reports errors on Windows 64 bit builds. I attached the outputs of the zq. exe test binary here:
zarith_test_failures.tar.gz

All tests have been conducted with OCaml 4.06.0 and the latest ZArith on github.

It seems that some floating-point precision is lost on both Windows ports.
Even more disturbing, the results also differ between the Cygwin and the native built.
Platform-specific assembly code does not seem to influence the outcomes.

gmp.h not found when compiling with `4.11.1+musl+static+flambda`

On ubuntu-20.04 (x86_64) with the 4.11.1+musl+static+flambda zarith fails to build: caml_z.c:32:10: fatal error: gmp.h: No such file or directory. (libgmp-dev is installed and vanilla 4.11.1 works fine)

#=== ERROR while compiling zarith.1.10 ========================================#
# context              2.0.7 | linux/x86_64 | ocaml-variants.4.11.1+musl+static+flambda | git+https://github.com/ocaml/opam-repository.git
# path                 ~/.opam/4.11.1+musl+static+flambda/.opam-switch/build/zarith.1.10
# command              ~/.opam/opam-init/hooks/sandbox.sh build make
# exit-code            2
# env-file             ~/.opam/log/zarith-14525-ab7083.env
# output-file          ~/.opam/log/zarith-14525-ab7083.out
### output ###
# [...]
# ocamlc -I +compiler-libs -bin-annot  -c q.mli
# ocamlc -I +compiler-libs -bin-annot  -c q.ml
# ocamlc -I +compiler-libs -bin-annot  -c big_int_Z.mli
# ocamlc -I +compiler-libs -bin-annot  -c big_int_Z.ml
# ocamlmklib -failsafe -o zarith z.cmo q.cmo big_int_Z.cmo -lgmp
# gcc -DZ_OCAML_HASH -DZ_OCAML_COMPARE_EXT -DHAS_GMP -DZ_ELF -DZ_DOT_LABEL_PREFIX     -c -o caml_z_x86_64.o caml_z_x86_64.S
# ocamlc -ccopt "-I/home/runner/.opam/4.11.1+musl+static+flambda/lib/ocaml  -DZ_OCAML_HASH -DZ_OCAML_COMPARE_EXT -DHAS_GMP -DZ_ELF -DZ_DOT_LABEL_PREFIX  -O3 -Wall -Wextra " -c caml_z.c
# caml_z.c:32:10: fatal error: gmp.h: No such file or directory
#    32 | #include <gmp.h>
#       |          ^~~~~~~
# compilation terminated.
# make: *** [project.mak:142: caml_z.o] Error 2

Failed linking when trying to use zarith.h

I'm trying to convert between Z.t and the mpz_ptr C type reified in OCaml by Ctypes, following following my own feature request. My plan was to use zarith's C interface zarith.h since, at the ocaml level, Z.t is abstract.
I'm failing to link

+ ocamlfind ocamlopt -linkpkg -g -package ctypes -package ctypes.foreign -package yices2_bindings -package sexplib -package containers -package ppx_deriving.std -cclib -lyices -ccopt -L/Users/e29546/.opam/4.10.0+flambda/lib/zarith/ -ccopt -I/Users/e29546/.opam/4.10.0+flambda/lib/zarith/ -cclib -lunix -cclib -lasmrun -cclib -lcamlrun -I src_tests src_tests/context_test.cmx src_tests/error_test.cmx src_tests/yices_runtime.cmx -o src_tests/yices_runtime.native
Undefined symbols for architecture x86_64:
  "_ml_z_from_mpz_ml", referenced from:
      _camlYices_runtime__entry in yices_runtime.o
      _camlYices2_high__x_26 in yices2_bindings.a(yices2_high.o)
      _camlZbindings__anon_fn$5bzbindings$2eml$3a9$2c0$2d$2d66$5d_24 in yices2_bindings.a(zbindings.o)
      _camlZbindings in yices2_bindings.a(zbindings.o)
  "_ml_z_mpz_init_set_z_ml", referenced from:
      _camlYices_runtime__entry in yices_runtime.o
      _camlYices2_high__x_26 in yices2_bindings.a(yices2_high.o)
      _camlZbindings__anon_fn$5bzbindings$2eml$3a6$2c0$2d$2d85$5d_17 in yices2_bindings.a(zbindings.o)
      _camlZbindings in yices2_bindings.a(zbindings.o)
  "_ml_z_mpz_set_z_ml", referenced from:
      _camlZbindings__anon_fn$5bzbindings$2eml$3a3$2c0$2d$2d75$5d_10 in yices2_bindings.a(zbindings.o)
      _camlZbindings in yices2_bindings.a(zbindings.o)

My understanding is that the implementation of the three functions offered in zarith.h is not found and, when I see the content of findlib's zarith directory, indeed I see zarith.h and only OCaml's compiled files, so I'm not sure how to link C code with them. As you can see in the command, I've tried many combinations of the C options I gathered from here and there.

Is this related to issue #8? I do not have a dllzarith.* file anywhere...

`to_bits` and `of_bits` for big endian ordering

Hello,

I see that to_bits and of_bits return or read from little endian ordering. Would it be possible to also add functions for big-endian ordering?

I see that to_bits and of_bits are implemented in the C functions ml_z_to_bits and ml_z_of_bits. I assume adding corresponding big endian functions would entail implementing corresponding C functions?

Could there be another way (without much C) of getting the big endian representation? It seems like GMP uses a big endian representation internally: https://gmplib.org/manual/Raw-Output-Internals.

I am interested in big endian representation for implementing CBOR (RFC8949) in OCaml. In particular to support Bignums.

Thanks!

ld: illegal text-relocation ...

Trying to build zarith on OS X 10.11.6

$ clang --version
Apple LLVM version 8.0.0 (clang-800.0.42.1)
Target: x86_64-apple-darwin15.6.0
Thread model: posix
InstalledDir: /Applications/Xcode.app/Contents/Developer/Toolchains/XcodeDefault.xctoolchain/usr/bin

$ ./configure
binary ocaml: found in /Users/davidlaxer/.opam/default/bin
binary ocamlc: found in /opt/local/bin
binary ocamldep: found in /opt/local/bin
binary ocamlmklib: found in /opt/local/bin
binary ocamldoc: found in /opt/local/bin
binary ar: found in /usr/bin
binary perl: found in /usr/bin
binary gcc: found in /usr/bin
binary ocamlopt: found in /opt/local/bin
checking compilation with gcc -O3 -Wall -Wextra : working
include caml/mlvalues.h: found
library dynlink.cmxa: found
binary ocamlfind: found in /Users/davidlaxer/.opam/default/bin
OCaml's word size is 64
binary uname: found in /usr/bin
checking compilation with gcc -arch x86_64 -O3 -Wall -Wextra : working
include gmp.h: found
library gmp: found
OCaml extended comparison supported
OCaml new hash functions available
OCaml supports -bin-annot to produce documentation

detected configuration:

  native-code:          yes
  dynamic linking:      yes
  asm path:             x86_64
  defines:              -DZ_OCAML_HASH -DZ_OCAML_COMPARE_EXT -DHAS_GMP -DZ_UNDERSCORE_PREFIX -DZ_MACOS 
  libraries:             -lgmp
  C options:            -arch x86_64 -O3 -Wall -Wextra 
  asm options           -arch x86_64 
  installation path:    /Users/davidlaxer/.opam/default/lib
  installation method   findlib

configuration successful!
now type "make" to build
then type "make install" or "sudo make install" to install
(ai) MacBook-Pro:zarith davidlaxer$ make
project.mak:151: depend: No such file or directory
./z_pp.pl x86_64
Name "main::extra" used only once: possible typo at ./z_pp.pl line 29.
found assembly file caml_z_x86_64.S
  found abs
  found add
  found div
  found divexact
  found logand
  found lognot
  found logor
  found logxor
  found mul
  found neg
  found pred
  found rem
  found shift_left
  found shift_right
  found sub
  found succ
ocamldep -native  z.ml q.ml big_int_Z.ml z.mli q.mli big_int_Z.mli > depend
ocamlc -I +compiler-libs -bin-annot  -c z.mli
ocamlc -I +compiler-libs -bin-annot  -c z.ml
ocamlc -I +compiler-libs -bin-annot  -c q.mli
ocamlc -I +compiler-libs -bin-annot  -c q.ml
ocamlc -I +compiler-libs -bin-annot  -c big_int_Z.mli
ocamlc -I +compiler-libs -bin-annot  -c big_int_Z.ml
ocamlmklib -failsafe -o zarith z.cmo q.cmo big_int_Z.cmo -lgmp
gcc -DZ_OCAML_HASH -DZ_OCAML_COMPARE_EXT -DHAS_GMP -DZ_UNDERSCORE_PREFIX -DZ_MACOS  -arch x86_64    -c -o caml_z_x86_64.o caml_z_x86_64.S
ocamlc -ccopt "-I/opt/local/lib/ocaml  -DZ_OCAML_HASH -DZ_OCAML_COMPARE_EXT -DHAS_GMP -DZ_UNDERSCORE_PREFIX -DZ_MACOS  -arch x86_64 -O3 -Wall -Wextra " -c caml_z.c
caml_z.c:2987:3: warning: implicit declaration of function 'mpz_2fac_ui' is
      invalid in C99 [-Wimplicit-function-declaration]
  mpz_2fac_ui(mr, ma);
  ^
caml_z.c:3002:3: warning: implicit declaration of function 'mpz_mfac_uiui' is
      invalid in C99 [-Wimplicit-function-declaration]
  mpz_mfac_uiui(mr, ma, mb);
  ^
caml_z.c:3017:3: warning: implicit declaration of function 'mpz_primorial_ui' is
      invalid in C99 [-Wimplicit-function-declaration]
  mpz_primorial_ui(mr, ma);
  ^
3 warnings generated.
ocamlmklib -failsafe -o zarith caml_z_x86_64.o caml_z.o -lgmp
ld: illegal text-relocation to '___gmp_binvert_limb_table' in /usr/local/lib/libgmp.a(mp_minv_tab.o) from '___gmpn_divexact_1' in /usr/local/lib/libgmp.a(dive_1.o) for architecture x86_64
clang: error: linker command failed with exit code 1 (use -v to see invocation)
ocamlc -I +compiler-libs -bin-annot  -c zarith_top.ml
ocamlc -o zarith_top.cma -a zarith_top.cmo
ocamlopt -I +compiler-libs  -c z.ml
ocamlopt -I +compiler-libs  -c q.ml
ocamlopt -I +compiler-libs  -c big_int_Z.ml
ocamlmklib -failsafe -o zarith z.cmx q.cmx big_int_Z.cmx -lgmp
ocamlopt -shared -o zarith.cmxs -I . zarith.cmxa -linkall
ld: illegal text-relocation to '___gmp_binvert_limb_table' in /usr/local/lib/libgmp.a(mp_minv_tab.o) from '___gmpn_divexact_1' in /usr/local/lib/libgmp.a(dive_1.o) for architecture x86_64
clang: error: linker command failed with exit code 1 (use -v to see invocation)
File "caml_startup", line 1:
Error: Error during linking
make: *** [zarith.cmxs] Error 2
(ai) MacBook-Pro:zarith davidlaxer$ 

Recommend Projects

  • React photo React

    A declarative, efficient, and flexible JavaScript library for building user interfaces.

  • Vue.js photo Vue.js

    🖖 Vue.js is a progressive, incrementally-adoptable JavaScript framework for building UI on the web.

  • Typescript photo Typescript

    TypeScript is a superset of JavaScript that compiles to clean JavaScript output.

  • TensorFlow photo TensorFlow

    An Open Source Machine Learning Framework for Everyone

  • Django photo Django

    The Web framework for perfectionists with deadlines.

  • D3 photo D3

    Bring data to life with SVG, Canvas and HTML. 📊📈🎉

Recommend Topics

  • javascript

    JavaScript (JS) is a lightweight interpreted programming language with first-class functions.

  • web

    Some thing interesting about web. New door for the world.

  • server

    A server is a program made to process requests and deliver data to clients.

  • Machine learning

    Machine learning is a way of modeling and interpreting data that allows a piece of software to respond intelligently.

  • Game

    Some thing interesting about game, make everyone happy.

Recommend Org

  • Facebook photo Facebook

    We are working to build community through open source technology. NB: members must have two-factor auth.

  • Microsoft photo Microsoft

    Open source projects and samples from Microsoft.

  • Google photo Google

    Google ❤️ Open Source for everyone.

  • D3 photo D3

    Data-Driven Documents codes.