summaryrefslogtreecommitdiffstats
path: root/stdlib/sys.ml
diff options
context:
space:
mode:
authorXavier Leroy <xavier.leroy@inria.fr>1996-11-07 11:00:19 +0000
committerXavier Leroy <xavier.leroy@inria.fr>1996-11-07 11:00:19 +0000
commitdfb5710a14e4c37945ab67c9ed24452a89f7c946 (patch)
tree42e05f8a8715299806f4fbf95bed702b27fcad97 /stdlib/sys.ml
parente5ea3418a8e064e6dbd30889b4c00f7fb1cfc0c2 (diff)
Utilisation de Sys.os_type. Nettoyages exceptions (failwith -> invalid_arg)
git-svn-id: http://caml.inria.fr/svn/ocaml/trunk@1170 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02
Diffstat (limited to 'stdlib/sys.ml')
-rw-r--r--stdlib/sys.ml5
1 files changed, 2 insertions, 3 deletions
diff --git a/stdlib/sys.ml b/stdlib/sys.ml
index b58473816..0a117bc40 100644
--- a/stdlib/sys.ml
+++ b/stdlib/sys.ml
@@ -13,12 +13,11 @@
(* System interface *)
-type config = { os_type : string; word_size : int };;
-external get_config: unit -> config = "sys_get_config"
-
+external get_config: unit -> string * int = "sys_get_config"
external get_argv: unit -> string array = "sys_get_argv"
let argv = get_argv()
+let (os_type, word_size) = get_config()
external file_exists: string -> bool = "sys_file_exists"
external remove: string -> unit = "sys_remove"