summaryrefslogtreecommitdiffstats
path: root/stdlib/pervasives.ml
diff options
context:
space:
mode:
authorGabriel Scherer <gabriel.scherer@gmail.com>2014-03-20 16:09:33 +0000
committerGabriel Scherer <gabriel.scherer@gmail.com>2014-03-20 16:09:33 +0000
commiteeae918f35cacae1c6f13126199ef49eae89d971 (patch)
treea7c863c8670e1d4e81999a27b714718e6d678a34 /stdlib/pervasives.ml
parent5c90eefd882b270ec5e83b015cbdfd61e9d46c98 (diff)
Pervasives: define [min_int] and [max_int] without assuming that integers are either 31 or 63 bits.
(Patch by Jérôme Vouillon) Js_of_ocaml has 32 bit integers. Currently, it patches the bytecode, just to get the correct values for [min_int] and [max_int]. It would be simpler if this was not necessary. git-svn-id: http://caml.inria.fr/svn/ocaml/trunk@14477 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02
Diffstat (limited to 'stdlib/pervasives.ml')
-rw-r--r--stdlib/pervasives.ml4
1 files changed, 2 insertions, 2 deletions
diff --git a/stdlib/pervasives.ml b/stdlib/pervasives.ml
index 43e23cc52..e4a07c3de 100644
--- a/stdlib/pervasives.ml
+++ b/stdlib/pervasives.ml
@@ -85,8 +85,8 @@ external ( lsl ) : int -> int -> int = "%lslint"
external ( lsr ) : int -> int -> int = "%lsrint"
external ( asr ) : int -> int -> int = "%asrint"
-let min_int = 1 lsl (if 1 lsl 31 = 0 then 30 else 62)
-let max_int = min_int - 1
+let max_int = (-1) lsr 1
+let min_int = max_int + 1
(* Floating-point operations *)