Sys.Signals module for a Variant type of signals (and a set_signal function that...
[ocaml.git] / stdlib / camlinternalOO.mli
blobd2aeea319b41639010a092cd2b382af055216f74
1 (***********************************************************************)
2 (* *)
3 (* Objective Caml *)
4 (* *)
5 (* Jerome Vouillon, projet Cristal, INRIA Rocquencourt *)
6 (* *)
7 (* Copyright 1996 Institut National de Recherche en Informatique et *)
8 (* en Automatique. All rights reserved. This file is distributed *)
9 (* under the terms of the GNU Library General Public License, with *)
10 (* the special exception on linking described in file ../LICENSE. *)
11 (* *)
12 (***********************************************************************)
14 (* $Id$ *)
16 (** Run-time support for objects and classes.
17 All functions in this module are for system use only, not for the
18 casual user. *)
20 (** {6 Classes} *)
22 type tag
23 type label
24 type table
25 type meth
26 type t
27 type obj
28 type closure
29 val public_method_label : string -> tag
30 val new_method : table -> label
31 val new_variable : table -> string -> int
32 val new_methods_variables :
33 table -> string array -> string array -> label array
34 val get_variable : table -> string -> int
35 val get_variables : table -> string array -> int array
36 val get_method_label : table -> string -> label
37 val get_method_labels : table -> string array -> label array
38 val get_method : table -> label -> meth
39 val set_method : table -> label -> meth -> unit
40 val set_methods : table -> label array -> unit
41 val narrow : table -> string array -> string array -> string array -> unit
42 val widen : table -> unit
43 val add_initializer : table -> (obj -> unit) -> unit
44 val dummy_table : table
45 val create_table : string array -> table
46 val init_class : table -> unit
47 val inherits :
48 table -> string array -> string array -> string array ->
49 (t * (table -> obj -> Obj.t) * t * obj) -> bool -> Obj.t array
50 val make_class :
51 string array -> (table -> Obj.t -> t) ->
52 (t * (table -> Obj.t -> t) * (Obj.t -> t) * Obj.t)
53 type init_table
54 val make_class_store :
55 string array -> (table -> t) -> init_table -> unit
56 val dummy_class :
57 string * int * int ->
58 (t * (table -> Obj.t -> t) * (Obj.t -> t) * Obj.t)
60 (** {6 Objects} *)
62 val copy : (< .. > as 'a) -> 'a
63 val create_object : table -> obj
64 val create_object_opt : obj -> table -> obj
65 val run_initializers : obj -> table -> unit
66 val run_initializers_opt : obj -> obj -> table -> obj
67 val create_object_and_run_initializers : obj -> table -> obj
68 external send : obj -> tag -> t = "%send"
69 external sendcache : obj -> tag -> t -> int -> t = "%sendcache"
70 external sendself : obj -> label -> t = "%sendself"
71 external get_public_method : obj -> tag -> closure
72 = "caml_get_public_method" "noalloc"
74 (** {6 Table cache} *)
76 type tables
77 val lookup_tables : tables -> closure array -> tables
79 (** {6 Builtins to reduce code size} *)
82 val get_const : t -> closure
83 val get_var : int -> closure
84 val get_env : int -> int -> closure
85 val get_meth : label -> closure
86 val set_var : int -> closure
87 val app_const : (t -> t) -> t -> closure
88 val app_var : (t -> t) -> int -> closure
89 val app_env : (t -> t) -> int -> int -> closure
90 val app_meth : (t -> t) -> label -> closure
91 val app_const_const : (t -> t -> t) -> t -> t -> closure
92 val app_const_var : (t -> t -> t) -> t -> int -> closure
93 val app_const_env : (t -> t -> t) -> t -> int -> int -> closure
94 val app_const_meth : (t -> t -> t) -> t -> label -> closure
95 val app_var_const : (t -> t -> t) -> int -> t -> closure
96 val app_env_const : (t -> t -> t) -> int -> int -> t -> closure
97 val app_meth_const : (t -> t -> t) -> label -> t -> closure
98 val meth_app_const : label -> t -> closure
99 val meth_app_var : label -> int -> closure
100 val meth_app_env : label -> int -> int -> closure
101 val meth_app_meth : label -> label -> closure
102 val send_const : tag -> obj -> int -> closure
103 val send_var : tag -> int -> int -> closure
104 val send_env : tag -> int -> int -> int -> closure
105 val send_meth : tag -> label -> int -> closure
108 type impl =
109 GetConst
110 | GetVar
111 | GetEnv
112 | GetMeth
113 | SetVar
114 | AppConst
115 | AppVar
116 | AppEnv
117 | AppMeth
118 | AppConstConst
119 | AppConstVar
120 | AppConstEnv
121 | AppConstMeth
122 | AppVarConst
123 | AppEnvConst
124 | AppMethConst
125 | MethAppConst
126 | MethAppVar
127 | MethAppEnv
128 | MethAppMeth
129 | SendConst
130 | SendVar
131 | SendEnv
132 | SendMeth
133 | Closure of closure
135 (** {6 Parameters} *)
137 (* currently disabled *)
138 type params =
139 { mutable compact_table : bool;
140 mutable copy_parent : bool;
141 mutable clean_when_copying : bool;
142 mutable retry_count : int;
143 mutable bucket_small_size : int }
145 val params : params
147 (** {6 Statistics} *)
149 type stats =
150 { classes : int;
151 methods : int;
152 inst_vars : int }
153 val stats : unit -> stats