Export_info
module A = Simple_value_approx
type descr =
| Value_block of Tag.t * approx array
| Value_mutable_block of Tag.t * int
| Value_int of int
| Value_char of char
| Value_float of float
| Value_float_array of value_float_array
| Value_boxed_int : 'a A.boxed_int * 'a -> descr
| Value_string of value_string
| Value_closure of value_closure
| Value_set_of_closures of value_set_of_closures
| Value_unknown_descr
and value_set_of_closures = {
set_of_closures_id : Set_of_closures_id.t;
bound_vars : approx Var_within_closure.Map.t;
free_vars : Flambda.specialised_to Variable.Map.t;
results : approx Closure_id.Map.t;
aliased_symbol : Symbol.t option;
}
type t = private {
sets_of_closures : A.function_declarations Set_of_closures_id.Map.t;
values : descr Export_id.Map.t Compilation_unit.Map.t;
symbol_id : Export_id.t Symbol.Map.t;
offset_fun : int Closure_id.Map.t;
offset_fv : int Var_within_closure.Map.t;
constant_closures : Closure_id.Set.t;
invariant_params : Variable.Set.t Variable.Map.t Set_of_closures_id.Map.t;
recursive : Variable.Set.t Set_of_closures_id.Map.t;
}
type transient = private {
sets_of_closures : A.function_declarations Set_of_closures_id.Map.t;
values : descr Export_id.Map.t Compilation_unit.Map.t;
symbol_id : Export_id.t Symbol.Map.t;
invariant_params : Variable.Set.t Variable.Map.t Set_of_closures_id.Map.t;
recursive : Variable.Set.t Set_of_closures_id.Map.t;
relevant_local_closure_ids : Closure_id.Set.t;
relevant_imported_closure_ids : Closure_id.Set.t;
relevant_local_vars_within_closure : Var_within_closure.Set.t;
relevant_imported_vars_within_closure : Var_within_closure.Set.t;
}
val empty : t
val opaque_transient :
compilation_unit:Compilation_unit.t ->
root_symbol:Symbol.t ->
transient
val create :
sets_of_closures:A.function_declarations Set_of_closures_id.Map.t ->
values:descr Export_id.Map.t Compilation_unit.Map.t ->
symbol_id:Export_id.t Symbol.Map.t ->
offset_fun:int Closure_id.Map.t ->
offset_fv:int Var_within_closure.Map.t ->
constant_closures:Closure_id.Set.t ->
invariant_params:Variable.Set.t Variable.Map.t Set_of_closures_id.Map.t ->
recursive:Variable.Set.t Set_of_closures_id.Map.t ->
t
val create_transient :
sets_of_closures:A.function_declarations Set_of_closures_id.Map.t ->
values:descr Export_id.Map.t Compilation_unit.Map.t ->
symbol_id:Export_id.t Symbol.Map.t ->
invariant_params:Variable.Set.t Variable.Map.t Set_of_closures_id.Map.t ->
recursive:Variable.Set.t Set_of_closures_id.Map.t ->
relevant_local_closure_ids:Closure_id.Set.t ->
relevant_imported_closure_ids:Closure_id.Set.t ->
relevant_local_vars_within_closure:Var_within_closure.Set.t ->
relevant_imported_vars_within_closure:Var_within_closure.Set.t ->
transient
val t_of_transient :
transient ->
program:Flambda.program ->
local_offset_fun:int Closure_id.Map.t ->
local_offset_fv:int Var_within_closure.Map.t ->
imported_offset_fun:int Closure_id.Map.t ->
imported_offset_fv:int Var_within_closure.Map.t ->
constant_closures:Closure_id.Set.t ->
t
val find_description : t -> Export_id.t -> descr
val nest_eid_map :
'a Export_id.Map.t ->
'a Export_id.Map.t Compilation_unit.Map.t
val print_approx_components :
Format.formatter ->
symbol_id:Export_id.t Symbol.Map.t ->
values:descr Export_id.Map.t Compilation_unit.Map.t ->
Symbol.t list ->
unit
val print_approx : Format.formatter -> (t * Symbol.t list) -> unit
val print_functions : Format.formatter -> t -> unit
val print_offsets : Format.formatter -> t -> unit
val print_all : Format.formatter -> (t * Symbol.t list) -> unit
val print_raw_approx : Format.formatter -> approx -> unit
val print_raw_descr : Format.formatter -> descr -> unit