Module Export_info

Exported information (that is to say, information written into a .cmx file) about a compilation unit.

type value_string_contents =
| Contents of string
| Unknown_or_mutable
type value_string = {
contents : value_string_contents;
size : int;
}
type value_float_array_contents =
| Contents of float option array
| Unknown_or_mutable
type value_float_array = {
contents : value_float_array_contents;
size : int;
}
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_closure = {
closure_id : Closure_id.t;
set_of_closures : value_set_of_closures;
}
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;
}
and approx =
| Value_unknown
| Value_id of Export_id.t
| Value_symbol of Symbol.t
type t = private {
sets_of_closures : A.function_declarations Set_of_closures_id.Map.t;(*

Code of exported functions indexed by set of closures IDs.

*)
values : descr Export_id.Map.t Compilation_unit.Map.t;(*

Structure of exported values.

*)
symbol_id : Export_id.t Symbol.Map.t;(*

Associates symbols and values.

*)
offset_fun : int Closure_id.Map.t;(*

Positions of function pointers in their closures.

*)
offset_fv : int Var_within_closure.Map.t;(*

Positions of value pointers in their closures.

*)
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;
}

A structure that describes what a single compilation unit exports.

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

Export information for a compilation unit that exports nothing.

val opaque_transient : compilation_unit:Compilation_unit.t -> root_symbol:Symbol.t -> transient

Create a new export information structure.

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

Record information about the layout of closures and which sets of closures are constant. These are all worked out during the Flambda_to_clambda pass.

val merge : t -> t -> t

Union of export information. Verifies that there are no identifier clashes.

val find_description : t -> Export_id.t -> descr

Look up the description of an exported value given its export ID.

Partition a mapping from export IDs by compilation unit.