Module CamlinternalOO

module CamlinternalOO: sig .. end
Run-time support for objects and classes. All functions in this module are for system use only, not for the casual user.


Classes

 
type tag
 
type label
 
type table
 
type meth
 
type t
 
type obj
 
type closure
 
val public_method_label : string -> tag
 
val new_method : table -> label
 
val new_variable : table -> string -> int
 
val new_methods_variables : table ->
string array -> string array -> label array
 
val get_variable : table -> string -> int
 
val get_variables : table -> string array -> int array
 
val get_method_label : table -> string -> label
 
val get_method_labels : table -> string array -> label array
 
val get_method : table -> label -> meth
 
val set_method : table -> label -> meth -> unit
 
val set_methods : table -> label array -> unit
 
val narrow : table -> string array -> string array -> string array -> unit
 
val widen : table -> unit
 
val add_initializer : table -> (obj -> unit) -> unit
 
val dummy_table : table
 
val create_table : string array -> table
 
val init_class : table -> unit
 
val inherits : table ->
string array ->
string array ->
string array ->
t * (table -> obj -> Obj.t) *
t * obj -> bool -> Obj.t array
 
val make_class : string array ->
(table -> Obj.t -> t) ->
t * (table -> Obj.t -> t) *
(Obj.t -> t) * Obj.t
 
type init_table
 
val make_class_store : string array ->
(table -> t) ->
init_table -> unit
 
val dummy_class : string * int * int ->
t * (table -> Obj.t -> t) *
(Obj.t -> t) * Obj.t
 

Objects

 
val copy : (< .. > as 'a) -> 'a
 
val create_object : table -> obj
 
val create_object_opt : obj -> table -> obj
 
val run_initializers : obj -> table -> unit
 
val run_initializers_opt : obj ->
obj -> table -> obj
 
val create_object_and_run_initializers : obj -> table -> obj
 
val send : obj -> tag -> t
 
val sendcache : obj ->
tag -> t -> int -> t
 
val sendself : obj -> label -> t
 
val get_public_method : obj -> tag -> closure
 

Table cache

 
type tables
 
val lookup_tables : tables ->
closure array -> tables
 

Builtins to reduce code size

 
type impl =
|  GetConst
|  GetVar
|  GetEnv
|  GetMeth
|  SetVar
|  AppConst
|  AppVar
|  AppEnv
|  AppMeth
|  AppConstConst
|  AppConstVar
|  AppConstEnv
|  AppConstMeth
|  AppVarConst
|  AppEnvConst
|  AppMethConst
|  MethAppConst
|  MethAppVar
|  MethAppEnv
|  MethAppMeth
|  SendConst
|  SendVar
|  SendEnv
|  SendMeth
|  Closure of closure
 

Parameters

 
type params = {
   mutable compact_table : bool;
   mutable copy_parent : bool;
   mutable clean_when_copying : bool;
   mutable retry_count : int;
   mutable bucket_small_size : int;
}
 
val params : params
 

Statistics

 
type stats = {
   classes : int;
   methods : int;
   inst_vars : int;
}
 
val stats : unit -> stats