summaryrefslogtreecommitdiffstats
path: root/stdlib/oo.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/oo.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/oo.ml')
-rw-r--r--stdlib/oo.ml6
1 files changed, 3 insertions, 3 deletions
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