summaryrefslogtreecommitdiffstats
path: root/stdlib
diff options
context:
space:
mode:
Diffstat (limited to 'stdlib')
-rw-r--r--stdlib/gc.ml20
-rw-r--r--stdlib/gc.mli18
-rw-r--r--stdlib/hashtbl.ml2
-rw-r--r--stdlib/hashtbl.mli2
-rw-r--r--stdlib/moreLabels.mli2
-rw-r--r--stdlib/pervasives.ml48
-rw-r--r--stdlib/pervasives.mli46
-rw-r--r--stdlib/printf.ml2
-rw-r--r--stdlib/sys.ml2
9 files changed, 71 insertions, 71 deletions
diff --git a/stdlib/gc.ml b/stdlib/gc.ml
index 86bf86da8..6e0436279 100644
--- a/stdlib/gc.ml
+++ b/stdlib/gc.ml
@@ -40,15 +40,15 @@ type control = {
mutable stack_limit : int;
};;
-external stat : unit -> stat = "gc_stat";;
-external counters : unit -> (float * float * float) = "gc_counters";;
-external get : unit -> control = "gc_get";;
-external set : control -> unit = "gc_set";;
-external minor : unit -> unit = "gc_minor";;
-external major_slice : int -> int = "gc_major_slice";;
-external major : unit -> unit = "gc_major";;
-external full_major : unit -> unit = "gc_full_major";;
-external compact : unit -> unit = "gc_compaction";;
+external stat : unit -> stat = "caml_gc_stat";;
+external counters : unit -> (float * float * float) = "caml_gc_counters";;
+external get : unit -> control = "caml_gc_get";;
+external set : control -> unit = "caml_gc_set";;
+external minor : unit -> unit = "caml_gc_minor";;
+external major_slice : int -> int = "caml_gc_major_slice";;
+external major : unit -> unit = "caml_gc_major";;
+external full_major : unit -> unit = "caml_gc_full_major";;
+external compact : unit -> unit = "caml_gc_compaction";;
open Printf;;
@@ -76,7 +76,7 @@ let allocated_bytes () =
(mi +. ma -. pro) *. float_of_int (Sys.word_size / 8)
;;
-external finalise : ('a -> unit) -> 'a -> unit = "final_register";;
+external finalise : ('a -> unit) -> 'a -> unit = "caml_final_register";;
type alarm = bool ref;;
diff --git a/stdlib/gc.mli b/stdlib/gc.mli
index 3a824c375..bfc8cf6d1 100644
--- a/stdlib/gc.mli
+++ b/stdlib/gc.mli
@@ -129,38 +129,38 @@ type control =
}
(** The GC parameters are given as a [control] record. *)
-external stat : unit -> stat = "gc_stat"
+external stat : unit -> stat = "caml_gc_stat"
(** Return the current values of the memory management counters in a
[stat] record. *)
-external counters : unit -> float * float * float = "gc_counters"
+external counters : unit -> float * float * float = "caml_gc_counters"
(** Return [(minor_words, promoted_words, major_words)]. Much faster
than [stat]. *)
-external get : unit -> control = "gc_get"
+external get : unit -> control = "caml_gc_get"
(** Return the current values of the GC parameters in a [control] record. *)
-external set : control -> unit = "gc_set"
+external set : control -> unit = "caml_gc_set"
(** [set r] changes the GC parameters according to the [control] record [r].
The normal usage is: [Gc.set { (Gc.get()) with Gc.verbose = 0x00d }] *)
-external minor : unit -> unit = "gc_minor"
+external minor : unit -> unit = "caml_gc_minor"
(** Trigger a minor collection. *)
-external major_slice : int -> int = "gc_major_slice";;
+external major_slice : int -> int = "caml_gc_major_slice";;
(** Do a minor collection and a slice of major collection. The argument
is the size of the slice, 0 to use the automatically-computed
slice size. In all cases, the result is the computed slice size. *)
-external major : unit -> unit = "gc_major"
+external major : unit -> unit = "caml_gc_major"
(** Do a minor collection and finish the current major collection cycle. *)
-external full_major : unit -> unit = "gc_full_major"
+external full_major : unit -> unit = "caml_gc_full_major"
(** Do a minor collection, finish the current major collection cycle,
and perform a complete new cycle. This will collect all currently
unreachable blocks. *)
-external compact : unit -> unit = "gc_compaction"
+external compact : unit -> unit = "caml_gc_compaction"
(** Perform a full major collection and compact the heap. Note that heap
compaction is a lengthy operation. *)
diff --git a/stdlib/hashtbl.ml b/stdlib/hashtbl.ml
index 872cf2a0f..0169f747a 100644
--- a/stdlib/hashtbl.ml
+++ b/stdlib/hashtbl.ml
@@ -15,7 +15,7 @@
(* Hash tables *)
-external hash_param : int -> int -> 'a -> int = "hash_univ_param" "noalloc"
+external hash_param : int -> int -> 'a -> int = "caml_hash_univ_param" "noalloc"
let hash x = hash_param 10 100 x
diff --git a/stdlib/hashtbl.mli b/stdlib/hashtbl.mli
index 3a6b13401..fcb296a7c 100644
--- a/stdlib/hashtbl.mli
+++ b/stdlib/hashtbl.mli
@@ -154,7 +154,7 @@ val hash : 'a -> int
Moreover, [hash] always terminates, even on cyclic
structures. *)
-external hash_param : int -> int -> 'a -> int = "hash_univ_param" "noalloc"
+external hash_param : int -> int -> 'a -> int = "caml_hash_univ_param" "noalloc"
(** [Hashtbl.hash_param n m x] computes a hash value for [x], with the
same properties as for [hash]. The two extra parameters [n] and
[m] give more precise control over hashing. Hashing performs a
diff --git a/stdlib/moreLabels.mli b/stdlib/moreLabels.mli
index 977893aec..6a690470c 100644
--- a/stdlib/moreLabels.mli
+++ b/stdlib/moreLabels.mli
@@ -60,7 +60,7 @@ module Hashtbl : sig
module Make : functor (H : HashedType) -> S with type key = H.t
val hash : 'a -> int
external hash_param : int -> int -> 'a -> int
- = "hash_univ_param" "noalloc"
+ = "caml_hash_univ_param" "noalloc"
end
module Map : sig
diff --git a/stdlib/pervasives.ml b/stdlib/pervasives.ml
index 0c6a26888..514adeee7 100644
--- a/stdlib/pervasives.ml
+++ b/stdlib/pervasives.ml
@@ -81,28 +81,28 @@ external (+.) : float -> float -> float = "%addfloat"
external (-.) : float -> float -> float = "%subfloat"
external ( *. ) : float -> float -> float = "%mulfloat"
external (/.) : float -> float -> float = "%divfloat"
-external ( ** ) : float -> float -> float = "power_float" "pow" "float"
-external exp : float -> float = "exp_float" "exp" "float"
-external acos : float -> float = "acos_float" "acos" "float"
-external asin : float -> float = "asin_float" "asin" "float"
-external atan : float -> float = "atan_float" "atan" "float"
-external atan2 : float -> float -> float = "atan2_float" "atan2" "float"
-external cos : float -> float = "cos_float" "cos" "float"
-external cosh : float -> float = "cosh_float" "cosh" "float"
-external log : float -> float = "log_float" "log" "float"
-external log10 : float -> float = "log10_float" "log10" "float"
-external sin : float -> float = "sin_float" "sin" "float"
-external sinh : float -> float = "sinh_float" "sinh" "float"
-external sqrt : float -> float = "sqrt_float" "sqrt" "float"
-external tan : float -> float = "tan_float" "tan" "float"
-external tanh : float -> float = "tanh_float" "tanh" "float"
-external ceil : float -> float = "ceil_float" "ceil" "float"
-external floor : float -> float = "floor_float" "floor" "float"
+external ( ** ) : float -> float -> float = "caml_power_float" "pow" "float"
+external exp : float -> float = "caml_exp_float" "exp" "float"
+external acos : float -> float = "caml_acos_float" "acos" "float"
+external asin : float -> float = "caml_asin_float" "asin" "float"
+external atan : float -> float = "caml_atan_float" "atan" "float"
+external atan2 : float -> float -> float = "caml_atan2_float" "atan2" "float"
+external cos : float -> float = "caml_cos_float" "cos" "float"
+external cosh : float -> float = "caml_cosh_float" "cosh" "float"
+external log : float -> float = "caml_log_float" "log" "float"
+external log10 : float -> float = "caml_log10_float" "log10" "float"
+external sin : float -> float = "caml_sin_float" "sin" "float"
+external sinh : float -> float = "caml_sinh_float" "sinh" "float"
+external sqrt : float -> float = "caml_sqrt_float" "sqrt" "float"
+external tan : float -> float = "caml_tan_float" "tan" "float"
+external tanh : float -> float = "caml_tanh_float" "tanh" "float"
+external ceil : float -> float = "caml_ceil_float" "ceil" "float"
+external floor : float -> float = "caml_floor_float" "floor" "float"
external abs_float : float -> float = "%absfloat"
-external mod_float : float -> float -> float = "fmod_float" "fmod" "float"
-external frexp : float -> float * int = "frexp_float"
-external ldexp : float -> int -> float = "ldexp_float"
-external modf : float -> float * float = "modf_float"
+external mod_float : float -> float -> float = "caml_fmod_float" "fmod" "float"
+external frexp : float -> float * int = "caml_frexp_float"
+external ldexp : float -> int -> float = "caml_ldexp_float"
+external modf : float -> float * float = "caml_modf_float"
external float : int -> float = "%floatofint"
external float_of_int : int -> float = "%floatofint"
external truncate : float -> int = "%intoffloat"
@@ -127,7 +127,7 @@ type fpclass =
| FP_zero
| FP_infinite
| FP_nan
-external classify_float: float -> fpclass = "classify_float"
+external classify_float: float -> fpclass = "caml_classify_float"
(* String operations -- more in module String *)
@@ -162,7 +162,7 @@ external snd : 'a * 'b -> 'b = "%field1"
(* String conversion functions *)
external format_int: string -> int -> string = "caml_format_int"
-external format_float: string -> float -> string = "format_float"
+external format_float: string -> float -> string = "caml_format_float"
let string_of_bool b =
if b then "true" else "false"
@@ -193,7 +193,7 @@ let valid_float_lexem s =
let string_of_float f = valid_float_lexem (format_float "%.12g" f);;
-external float_of_string : string -> float = "float_of_string"
+external float_of_string : string -> float = "caml_float_of_string"
(* List operations -- more in module List *)
diff --git a/stdlib/pervasives.mli b/stdlib/pervasives.mli
index 3788cd440..2561cc4ca 100644
--- a/stdlib/pervasives.mli
+++ b/stdlib/pervasives.mli
@@ -247,55 +247,55 @@ external ( *. ) : float -> float -> float = "%mulfloat"
external ( /. ) : float -> float -> float = "%divfloat"
(** Floating-point division. *)
-external ( ** ) : float -> float -> float = "power_float" "pow" "float"
+external ( ** ) : float -> float -> float = "caml_power_float" "pow" "float"
(** Exponentiation *)
-external sqrt : float -> float = "sqrt_float" "sqrt" "float"
+external sqrt : float -> float = "caml_sqrt_float" "sqrt" "float"
(** Square root *)
-external exp : float -> float = "exp_float" "exp" "float"
+external exp : float -> float = "caml_exp_float" "exp" "float"
(** Exponential. *)
-external log : float -> float = "log_float" "log" "float"
+external log : float -> float = "caml_log_float" "log" "float"
(** Natural logarithm. *)
-external log10 : float -> float = "log10_float" "log10" "float"
+external log10 : float -> float = "caml_log10_float" "log10" "float"
(** Base 10 logarithm. *)
-external cos : float -> float = "cos_float" "cos" "float"
+external cos : float -> float = "caml_cos_float" "cos" "float"
(** See {!Pervasives.atan2}. *)
-external sin : float -> float = "sin_float" "sin" "float"
+external sin : float -> float = "caml_sin_float" "sin" "float"
(** See {!Pervasives.atan2}. *)
-external tan : float -> float = "tan_float" "tan" "float"
+external tan : float -> float = "caml_tan_float" "tan" "float"
(** See {!Pervasives.atan2}. *)
-external acos : float -> float = "acos_float" "acos" "float"
+external acos : float -> float = "caml_acos_float" "acos" "float"
(** See {!Pervasives.atan2}. *)
-external asin : float -> float = "asin_float" "asin" "float"
+external asin : float -> float = "caml_asin_float" "asin" "float"
(** See {!Pervasives.atan2}. *)
-external atan : float -> float = "atan_float" "atan" "float"
+external atan : float -> float = "caml_atan_float" "atan" "float"
(** See {!Pervasives.atan2}. *)
-external atan2 : float -> float -> float = "atan2_float" "atan2" "float"
+external atan2 : float -> float -> float = "caml_atan2_float" "atan2" "float"
(** The usual trigonometric functions. *)
-external cosh : float -> float = "cosh_float" "cosh" "float"
+external cosh : float -> float = "caml_cosh_float" "cosh" "float"
(** See {!Pervasives.tanh}. *)
-external sinh : float -> float = "sinh_float" "sinh" "float"
+external sinh : float -> float = "caml_sinh_float" "sinh" "float"
(** See {!Pervasives.tanh}. *)
-external tanh : float -> float = "tanh_float" "tanh" "float"
+external tanh : float -> float = "caml_tanh_float" "tanh" "float"
(** The usual hyperbolic trigonometric functions. *)
-external ceil : float -> float = "ceil_float" "ceil" "float"
+external ceil : float -> float = "caml_ceil_float" "ceil" "float"
(** See {!Pervasives.floor}. *)
-external floor : float -> float = "floor_float" "floor" "float"
+external floor : float -> float = "caml_floor_float" "floor" "float"
(** Round the given float to an integer value.
[floor f] returns the greatest integer value less than or
equal to [f].
@@ -305,22 +305,22 @@ external floor : float -> float = "floor_float" "floor" "float"
external abs_float : float -> float = "%absfloat"
(** Return the absolute value of the argument. *)
-external mod_float : float -> float -> float = "fmod_float" "fmod" "float"
+external mod_float : float -> float -> float = "caml_fmod_float" "fmod" "float"
(** [mod_float a b] returns the remainder of [a] with respect to
[b]. The returned value is [a -. n *. b], where [n]
is the quotient [a /. b] rounded towards zero to an integer. *)
-external frexp : float -> float * int = "frexp_float"
+external frexp : float -> float * int = "caml_frexp_float"
(** [frexp f] returns the pair of the significant
and the exponent of [f]. When [f] is zero, the
significant [x] and the exponent [n] of [f] are equal to
zero. When [f] is non-zero, they are defined by
[f = x *. 2 ** n] and [0.5 <= x < 1.0]. *)
-external ldexp : float -> int -> float = "ldexp_float"
+external ldexp : float -> int -> float = "caml_ldexp_float"
(** [ldexp x n] returns [x *. 2 ** n]. *)
-external modf : float -> float * float = "modf_float"
+external modf : float -> float * float = "caml_modf_float"
(** [modf f] returns the pair of the fractional and integral
part of [f]. *)
@@ -370,7 +370,7 @@ type fpclass =
(** The five classes of floating-point numbers, as determined by
the {!Pervasives.classify_float} function. *)
-external classify_float : float -> fpclass = "classify_float"
+external classify_float : float -> fpclass = "caml_classify_float"
(** Return the class of the given floating-point number:
normal, subnormal, zero, infinite, or not a number. *)
@@ -434,7 +434,7 @@ external int_of_string : string -> int = "caml_int_of_string"
val string_of_float : float -> string
(** Return the string representation of a floating-point number. *)
-external float_of_string : string -> float = "float_of_string"
+external float_of_string : string -> float = "caml_float_of_string"
(** Convert the given string to a float. Raise [Failure "float_of_string"]
if the given string is not a valid representation of a float. *)
diff --git a/stdlib/printf.ml b/stdlib/printf.ml
index ff893e053..f29d2b431 100644
--- a/stdlib/printf.ml
+++ b/stdlib/printf.ml
@@ -18,7 +18,7 @@ external format_int32: string -> int32 -> string = "caml_int32_format"
external format_nativeint: string -> nativeint -> string
= "caml_nativeint_format"
external format_int64: string -> int64 -> string = "caml_int64_format"
-external format_float: string -> float -> string = "format_float"
+external format_float: string -> float -> string = "caml_format_float"
let bad_format fmt pos =
invalid_arg
diff --git a/stdlib/sys.ml b/stdlib/sys.ml
index 117205176..f3f9333fa 100644
--- a/stdlib/sys.ml
+++ b/stdlib/sys.ml
@@ -78,4 +78,4 @@ let catch_break on =
(* OCaml version string, must be in the format described in sys.mli. *)
-let ocaml_version = "3.07+10 (2004-01-01)";;
+let ocaml_version = "3.07+11 (2004-01-02)";;