summaryrefslogtreecommitdiffstats
path: root/stdlib
diff options
context:
space:
mode:
authorJérôme Vouillon <Jerome.Vouillon@pps.jussieu.fr>1996-08-13 15:10:35 +0000
committerJérôme Vouillon <Jerome.Vouillon@pps.jussieu.fr>1996-08-13 15:10:35 +0000
commit65f5150ea5e329bada8a5afb0acedea6c65bb9ca (patch)
treeadedfbb9723b9a1828d7cbe5689de59d85d7518f /stdlib
parent872ef330f4562652a42091dd0c13c136a22ddebb (diff)
Classes recursives compilees correctement.
git-svn-id: http://caml.inria.fr/svn/ocaml/trunk@946 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02
Diffstat (limited to 'stdlib')
-rw-r--r--stdlib/oo.ml15
-rw-r--r--stdlib/oo.mli2
2 files changed, 9 insertions, 8 deletions
diff --git a/stdlib/oo.ml b/stdlib/oo.ml
index 303980745..c4181e5dc 100644
--- a/stdlib/oo.ml
+++ b/stdlib/oo.ml
@@ -262,9 +262,9 @@ let put array label element =
type t
type class_info =
- {obj_init: t -> t;
- class_init: table -> unit;
- table: table}
+ {mutable obj_init: t -> t;
+ mutable class_init: table -> unit;
+ mutable table: table}
let set_initializer table init =
match table.init with
@@ -363,19 +363,20 @@ let new_object table =
obj.(0) <- (magic table.buckets : t);
obj
-let create_class class_init =
+let create_class class_info class_init =
let table = new_table () in
class_init table;
method_count := !method_count + List.length table.methods;
if !compact_table then
compact_buckets table.buckets;
inst_var_count := !inst_var_count + table.size - 1;
- { class_init = class_init; table = table;
- obj_init =
+ class_info.class_init <- class_init;
+ class_info.table <- table;
+ class_info.obj_init <-
(function x ->
let obj = Array.create table.size (magic () : t) in
obj.(0) <- (magic table.buckets : t);
- (magic (List.hd (List.hd table.init))) obj x) }
+ (magic (List.hd (List.hd table.init))) obj x)
(**** Objects ****)
diff --git a/stdlib/oo.mli b/stdlib/oo.mli
index 56f550225..d2fc1ff97 100644
--- a/stdlib/oo.mli
+++ b/stdlib/oo.mli
@@ -37,7 +37,7 @@ val set_method: table -> label -> item -> unit
val get_variable: table -> string -> int
val hide_variable: table -> string -> unit
val get_private_variable: table -> string -> int
-val create_class: (table -> unit) -> class_info
+val create_class: class_info -> (table -> unit) -> unit
(* Objects *)
type t