summaryrefslogtreecommitdiffstats
path: root/stdlib/pervasives.ml
diff options
context:
space:
mode:
authorPierre Weis <Pierre.Weis@inria.fr>1998-12-02 10:40:33 +0000
committerPierre Weis <Pierre.Weis@inria.fr>1998-12-02 10:40:33 +0000
commit73e446d376ef844f45deab1071b79fd048b0cd2d (patch)
tree19cca209a0ddaefe12237784a21ef10367b27ce3 /stdlib/pervasives.ml
parentb83b27899119824923f754caf251f17bc02bae3f (diff)
Ajout des fonctions int_of_float, float_of_int, char_of_int,
int_of_char, bool_of_string. git-svn-id: http://caml.inria.fr/svn/ocaml/trunk@2211 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02
Diffstat (limited to 'stdlib/pervasives.ml')
-rw-r--r--stdlib/pervasives.ml6
1 files changed, 6 insertions, 0 deletions
diff --git a/stdlib/pervasives.ml b/stdlib/pervasives.ml
index 83b591c07..9819c1c5c 100644
--- a/stdlib/pervasives.ml
+++ b/stdlib/pervasives.ml
@@ -103,7 +103,9 @@ external frexp : float -> float * int = "frexp_float"
external ldexp : float -> int -> float = "ldexp_float"
external modf : float -> float * float = "modf_float" "modf"
external float : int -> float = "%floatofint"
+external float_of_int : int -> float = "%floatofint"
external truncate : float -> int = "%intoffloat"
+external int_of_float : float -> int = "%intoffloat"
(* String operations -- more in module String *)
@@ -131,6 +133,10 @@ external format_float: string -> float -> string = "format_float"
let string_of_bool b =
if b then "true" else "false"
+let bool_of_string = function
+ | "true" -> true
+ | "false" -> false
+ | _ -> invalid_arg "string_of_bool"
let string_of_int n =
format_int "%d" n