summaryrefslogtreecommitdiffstats
diff options
context:
space:
mode:
authorPierre Weis <Pierre.Weis@inria.fr>2010-06-04 16:44:08 +0000
committerPierre Weis <Pierre.Weis@inria.fr>2010-06-04 16:44:08 +0000
commitf5c2201cc0d73efee1497bf90896ce64c7f28b7e (patch)
tree0639386905fe89b27eebb9ab56e369ad3fa4654f
parentef6ed63a782beb38a1be9fc4b5a1e904de93b741 (diff)
PR#5062
git-svn-id: http://caml.inria.fr/svn/ocaml/trunk@10498 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02
-rw-r--r--VERSION2
-rwxr-xr-xboot/ocamlcbin1086691 -> 1094083 bytes
-rwxr-xr-xboot/ocamldepbin306290 -> 306689 bytes
-rwxr-xr-xboot/ocamllexbin166022 -> 169501 bytes
-rw-r--r--parsing/parser.mly11
-rw-r--r--stdlib/pervasives.ml2
-rw-r--r--stdlib/pervasives.mli16
7 files changed, 22 insertions, 9 deletions
diff --git a/VERSION b/VERSION
index 3fbafe2df..738426160 100644
--- a/VERSION
+++ b/VERSION
@@ -1,4 +1,4 @@
-3.12.0+dev25 (2010-05-20)
+3.12.0+dev26 (2010-06-04)
# The version string is the first line of this file.
# It must be in the format described in stdlib/sys.mli
diff --git a/boot/ocamlc b/boot/ocamlc
index 38b6bb9a7..e2a7ed90b 100755
--- a/boot/ocamlc
+++ b/boot/ocamlc
Binary files differ
diff --git a/boot/ocamldep b/boot/ocamldep
index 14034fbf2..ec792d394 100755
--- a/boot/ocamldep
+++ b/boot/ocamldep
Binary files differ
diff --git a/boot/ocamllex b/boot/ocamllex
index d60895f3e..7cc08b38f 100755
--- a/boot/ocamllex
+++ b/boot/ocamllex
Binary files differ
diff --git a/parsing/parser.mly b/parsing/parser.mly
index 87a565961..4f9bcc58b 100644
--- a/parsing/parser.mly
+++ b/parsing/parser.mly
@@ -93,14 +93,19 @@ let mkuminus name arg =
mkexp(Pexp_constant(Const_int64(Int64.neg n)))
| "-", Pexp_constant(Const_nativeint n) ->
mkexp(Pexp_constant(Const_nativeint(Nativeint.neg n)))
- | _, Pexp_constant(Const_float f) ->
+ | ("-" | "-."), Pexp_constant(Const_float f) ->
mkexp(Pexp_constant(Const_float(neg_float_string f)))
| _ ->
mkexp(Pexp_apply(mkoperator ("~" ^ name) 1, ["", arg]))
let mkuplus name arg =
- match name, arg.pexp_desc with
- | "+", desc -> mkexp desc
+ let desc = arg.pexp_desc in
+ match name, desc with
+ | "+", Pexp_constant(Const_int _)
+ | "+", Pexp_constant(Const_int32 _)
+ | "+", Pexp_constant(Const_int64 _)
+ | "+", Pexp_constant(Const_nativeint _)
+ | ("+" | "+."), Pexp_constant(Const_float _) -> mkexp desc
| _ ->
mkexp(Pexp_apply(mkoperator ("~" ^ name) 1, ["", arg]))
diff --git a/stdlib/pervasives.ml b/stdlib/pervasives.ml
index c4f0bcfd8..22dfa8fc2 100644
--- a/stdlib/pervasives.ml
+++ b/stdlib/pervasives.ml
@@ -51,6 +51,7 @@ external (||) : bool -> bool -> bool = "%sequor"
(* Integer operations *)
external (~-) : int -> int = "%negint"
+external (~+) : int -> int = "%identity"
external succ : int -> int = "%succint"
external pred : int -> int = "%predint"
external (+) : int -> int -> int = "%addint"
@@ -77,6 +78,7 @@ let max_int = min_int - 1
(* Floating-point operations *)
external (~-.) : float -> float = "%negfloat"
+external (~+.) : float -> float = "%identity"
external (+.) : float -> float -> float = "%addfloat"
external (-.) : float -> float -> float = "%subfloat"
external ( *. ) : float -> float -> float = "%mulfloat"
diff --git a/stdlib/pervasives.mli b/stdlib/pervasives.mli
index d77b44249..da5a5aa49 100644
--- a/stdlib/pervasives.mli
+++ b/stdlib/pervasives.mli
@@ -145,13 +145,16 @@ external ( or ) : bool -> bool -> bool = "%sequor"
They do not fail on overflow. *)
external ( ~- ) : int -> int = "%negint"
-(** Unary negation. You can also write [-e] instead of [~-e]. *)
+(** Unary negation. You can also write [- e] instead of [~- e]. *)
+
+external ( ~+ ) : int -> int = "%identity"
+(** Unary addition. You can also write [+ e] instead of [~+ e]. *)
external succ : int -> int = "%succint"
-(** [succ x] is [x+1]. *)
+(** [succ x] is [x + 1]. *)
external pred : int -> int = "%predint"
-(** [pred x] is [x-1]. *)
+(** [pred x] is [x - 1]. *)
external ( + ) : int -> int -> int = "%addint"
(** Integer addition. *)
@@ -168,7 +171,7 @@ external ( / ) : int -> int -> int = "%divint"
Integer division rounds the real quotient of its arguments towards zero.
More precisely, if [x >= 0] and [y > 0], [x / y] is the greatest integer
less than or equal to the real quotient of [x] by [y]. Moreover,
- [(-x) / y = x / (-y) = -(x / y)]. *)
+ [(- x) / y = x / (-y) = - (x / y)]. *)
external ( mod ) : int -> int -> int = "%modint"
(** Integer remainder. If [y] is not zero, the result
@@ -237,7 +240,10 @@ external ( asr ) : int -> int -> int = "%asrint"
*)
external ( ~-. ) : float -> float = "%negfloat"
-(** Unary negation. You can also write [-.e] instead of [~-.e]. *)
+(** Unary negation. You can also write [-. e] instead of [~-. e]. *)
+
+external ( ~+. ) : float -> float = "%identity"
+(** Unary addition. You can also write [+. e] instead of [~+. e]. *)
external ( +. ) : float -> float -> float = "%addfloat"
(** Floating-point addition *)