summaryrefslogtreecommitdiffstats
path: root/stdlib
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
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')
-rw-r--r--stdlib/filename.ml30
-rw-r--r--stdlib/oo.ml6
-rw-r--r--stdlib/stream.ml4
-rw-r--r--stdlib/sys.ml5
-rw-r--r--stdlib/sys.mli15
5 files changed, 28 insertions, 32 deletions
diff --git a/stdlib/filename.ml b/stdlib/filename.ml
index 378263cbd..611c4f6a3 100644
--- a/stdlib/filename.ml
+++ b/stdlib/filename.ml
@@ -11,14 +11,12 @@
(* $Id$ *)
-let systype = (Sys.get_config()).Sys.os_type
-
let current_dir_name =
- match systype with
+ match Sys.os_type with
| "Unix" -> "."
| "Win32" -> "."
| "MacOS" -> ":"
- | _ -> failwith "Filename.current_dir_name: unknown system"
+ | _ -> invalid_arg "Filename.current_dir_name: unknown system"
let unix_concat dirname filename =
let l = String.length dirname in
@@ -39,11 +37,11 @@ let mac_concat dirname filename =
else dirname ^ ":" ^ filename
let concat =
- match systype with
+ match Sys.os_type with
| "Unix" -> unix_concat
| "Win32" -> wnt_concat
| "MacOS" -> mac_concat
- | _ -> failwith "Filename.concat: unknown system"
+ | _ -> invalid_arg "Filename.concat: unknown system"
let unix_is_absolute n =
(String.length n >= 1 && String.sub n 0 1 = "/")
@@ -68,11 +66,11 @@ let mac_is_absolute n =
with Exit -> true
let is_absolute =
- match systype with
+ match Sys.os_type with
| "Unix" -> unix_is_absolute
| "Win32" -> wnt_is_absolute
| "MacOS" -> mac_is_absolute
- | _ -> failwith "Filename.is_absolute: unknown system"
+ | _ -> invalid_arg "Filename.is_absolute: unknown system"
let unix_check_suffix name suff =
String.length name >= String.length suff &&
@@ -88,11 +86,11 @@ let wnt_check_suffix name suff =
let mac_check_suffix = unix_check_suffix
let check_suffix =
- match systype with
+ match Sys.os_type with
| "Unix" -> unix_check_suffix
| "Win32" -> wnt_check_suffix
| "MacOS" -> mac_check_suffix
- | _ -> failwith "Filename.check_suffix: unknown system"
+ | _ -> invalid_arg "Filename.check_suffix: unknown system"
let chop_suffix name suff =
let n = String.length name - String.length suff in
@@ -161,25 +159,25 @@ let mac_dirname name =
with Not_found -> ":"
let basename =
- match systype with
+ match Sys.os_type with
| "Unix" -> unix_basename
| "Win32" -> wnt_basename
| "MacOS" -> mac_basename
- | _ -> failwith "Filename.basename: unknown system"
+ | _ -> invalid_arg "Filename.basename: unknown system"
let dirname =
- match systype with
+ match Sys.os_type with
| "Unix" -> unix_dirname
| "Win32" -> wnt_dirname
| "MacOS" -> mac_dirname
- | _ -> failwith "Filename.dirname: unknown system"
+ | _ -> invalid_arg "Filename.dirname: unknown system"
let temporary_directory =
- match systype with
+ match Sys.os_type with
| "Unix" -> (try Sys.getenv "TMPDIR" with Not_found -> "/tmp")
| "Win32" -> (try Sys.getenv "TEMP" with Not_found -> "C:\\temp")
| "MacOS" -> (try Sys.getenv "TempFolder" with Not_found -> ":")
- | _ -> failwith "Filename.temporary_directory: unknown system"
+ | _ -> invalid_arg "Filename.temporary_directory: unknown system"
external open_desc: string -> open_flag list -> int -> int = "sys_open"
external close_desc: int -> unit = "sys_close"
diff --git a/stdlib/oo.ml b/stdlib/oo.ml
index 27fc08eb5..bfdb189fe 100644
--- a/stdlib/oo.ml
+++ b/stdlib/oo.ml
@@ -25,7 +25,7 @@ let bucket_small_size = ref 16
(**** Parameters ****)
-let step = (Sys.get_config()).Sys.word_size / 16
+let step = Sys.word_size / 16
let first_label = 0
@@ -276,7 +276,7 @@ let set_initializer table init =
in
table.init <- (i::l')::l''
| _ ->
- failwith "Fatal error in Oo.set_initializer."
+ invalid_arg "Fatal error in Oo.set_initializer."
let inheritance table cl vars =
if
@@ -342,7 +342,7 @@ let hide_variable table name =
let rec list_remove name =
function
[] ->
- failwith "Fatal error in Oo.get_private_variable"
+ invalid_arg "Fatal error in Oo.get_private_variable"
| (n, _) as a::l ->
if name = n then l
else a::list_remove name l
diff --git a/stdlib/stream.ml b/stdlib/stream.ml
index 91d280f7f..ebb10f181 100644
--- a/stdlib/stream.ml
+++ b/stdlib/stream.ml
@@ -46,7 +46,7 @@ let rec get_data =
| None -> get_data d2
end
| Slazy f -> get_data (f ())
- | _ -> failwith "illegal stream concatenation"
+ | _ -> invalid_arg "illegal stream concatenation"
let rec peek s =
match s.data with
@@ -63,7 +63,7 @@ let rec peek s =
end
| Slazy f ->
begin match f () with
- Sgen _ | Sbuffio _ -> failwith "illegal stream concatenation"
+ Sgen _ | Sbuffio _ -> invalid_arg "illegal stream concatenation"
| x -> Obj.set_field (Obj.repr s) 1 (Obj.repr x); peek s
end
| Sgen {curr = Some a} -> a
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"
diff --git a/stdlib/sys.mli b/stdlib/sys.mli
index bcf582103..3d6099899 100644
--- a/stdlib/sys.mli
+++ b/stdlib/sys.mli
@@ -13,14 +13,6 @@
(* Module [Sys]: system interface *)
-type config = { os_type : string; word_size : int };;
- (* Configuration information:
-- [os_type] is one of Unix, Win32, MacOS.
-- [word_size] is the size of one word, in bits: 32 or 64
- *)
-external get_config: unit -> config = "sys_get_config"
- (* Return the current run-time configuration. *)
-
val argv: string array
(* The command line arguments given to the process.
The first element is the command name used to invoke the program.
@@ -45,6 +37,13 @@ val interactive: bool ref
(* This reference is initially set to [false] in standalone
programs and to [true] if the code is being executed under
the interactive toplevel [csltop]. *)
+val os_type: string
+ (* Operating system currently executing the Caml program.
+ One of ["Unix"], ["Win32"], or ["MacOS"]. *)
+val word_size: int
+ (* Size of one word on the machine currently executing the Caml
+ program, in bits: 32 or 64. *)
+
(*** Signal handling *)
type signal_behavior =