git-svn-id: http://caml.inria.fr/svn/ocaml/trunk@10498 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02
master
Pierre Weis 2010-06-04 16:44:08 +00:00
parent ef6ed63a78
commit f5c2201cc0
7 changed files with 22 additions and 9 deletions

View File

@ -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

Binary file not shown.

Binary file not shown.

Binary file not shown.

View File

@ -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]))

View File

@ -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"

View File

@ -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 *)