Simple_value_approxand descr = private | Value_block of Tag.t * t array| Value_int of int| Value_char of char| Value_float of float option| Value_boxed_int : 'a boxed_int * 'a -> descr| Value_set_of_closures of value_set_of_closures| Value_closure of value_closure| Value_string of value_string| Value_float_array of value_float_array| Value_unknown of unknown_because_of| Value_bottom| Value_extern of Export_id.t| Value_symbol of Symbol.t| Value_unresolved of unresolved_valueand function_declarations = private {is_classic_mode : bool;set_of_closures_id : Set_of_closures_id.t;set_of_closures_origin : Set_of_closures_origin.t;funs : function_declaration Variable.Map.t;}and function_body = private {free_variables : Variable.Set.t;free_symbols : Symbol.Set.t;stub : bool;dbg : Debuginfo.t;inline : Lambda.inline_attribute;specialise : Lambda.specialise_attribute;is_a_functor : bool;body : Flambda.t;poll : Lambda.poll_attribute;}and function_declaration = private {closure_origin : Closure_origin.t;params : Parameter.t list;function_body : function_body option;}and value_set_of_closures = private {function_decls : function_declarations;bound_vars : t Var_within_closure.Map.t;free_vars : Flambda.specialised_to Variable.Map.t;invariant_params : Variable.Set.t Variable.Map.t Lazy.t;recursive : Variable.Set.t Lazy.t;size : int option Variable.Map.t Lazy.t;specialised_args : Flambda.specialised_to Variable.Map.t;freshening : Freshening.Project_var.t;direct_call_surrogates : Closure_id.t Closure_id.Map.t;}val print : Format.formatter -> t -> unitval print_descr : Format.formatter -> descr -> unitval print_value_set_of_closures :
Format.formatter ->
value_set_of_closures ->
unitval print_function_declarations :
Format.formatter ->
function_declarations ->
unitval function_declarations_approx :
keep_body:(Variable.t -> Flambda.function_declaration -> bool) ->
Flambda.function_declarations ->
function_declarationsval create_value_set_of_closures :
function_decls:function_declarations ->
bound_vars:t Var_within_closure.Map.t ->
free_vars:Flambda.specialised_to Variable.Map.t ->
invariant_params:Variable.Set.t Variable.Map.t lazy_t ->
recursive:Variable.Set.t Lazy.t ->
specialised_args:Flambda.specialised_to Variable.Map.t ->
freshening:Freshening.Project_var.t ->
direct_call_surrogates:Closure_id.t Closure_id.Map.t ->
value_set_of_closuresval update_freshening_of_value_set_of_closures :
value_set_of_closures ->
freshening:Freshening.Project_var.t ->
value_set_of_closuresval value_unknown : unknown_because_of -> tval value_int : int -> tval value_char : char -> tval value_float : float -> tval value_any_float : tval value_mutable_float_array : size:int -> tval value_string : int -> string option -> tval value_extern : Export_id.t -> tval value_bottom : tval value_unresolved : unresolved_value -> tval value_closure :
?closure_var:Variable.t ->
?set_of_closures_var:Variable.t ->
?set_of_closures_symbol:Symbol.t ->
value_set_of_closures ->
Closure_id.t ->
tval value_set_of_closures :
?set_of_closures_var:Variable.t ->
value_set_of_closures ->
tval make_const_int_named : int -> Flambda.named * tval make_const_char_named : char -> Flambda.named * tval make_const_bool_named : bool -> Flambda.named * tval make_const_float_named : float -> Flambda.named * tval make_const_boxed_int_named : 'i boxed_int -> 'i -> Flambda.named * tval augment_with_variable : t -> Variable.t -> tval augment_with_kind : t -> Lambda.value_kind -> tval augment_kind_with_approx : t -> Lambda.value_kind -> Lambda.value_kindval known : t -> boolval useful : t -> boolval all_not_useful : t list -> boolval warn_on_mutation : t -> booltype simplification_result = Flambda.t * simplification_summary * ttype simplification_result_named = Flambda.named * simplification_summary * tval simplify : t -> Flambda.t -> simplification_resultval simplify_using_env :
t ->
is_present_in_env:(Variable.t -> bool) ->
Flambda.t ->
simplification_resultval simplify_named : t -> Flambda.named -> simplification_result_namedval simplify_named_using_env :
t ->
is_present_in_env:(Variable.t -> bool) ->
Flambda.named ->
simplification_result_namedval simplify_var_to_var_using_env :
t ->
is_present_in_env:(Variable.t -> bool) ->
Variable.t optionval simplify_var : t -> (Flambda.named * t) optionval get_field : t -> field_index:int -> get_field_resultval check_approx_for_block : t -> checked_approx_for_blockval approx_for_bound_var : value_set_of_closures -> Var_within_closure.t -> tval freshen_and_check_closure_id :
value_set_of_closures ->
Closure_id.t ->
Closure_id.ttype strict_checked_approx_for_set_of_closures = | Wrong| Ok of Variable.t option * value_set_of_closuresval strict_check_approx_for_set_of_closures :
t ->
strict_checked_approx_for_set_of_closurestype checked_approx_for_set_of_closures = | Wrong| Unresolved of unresolved_value| Unknown| Unknown_because_of_unresolved_value of unresolved_value| Ok of Variable.t option * value_set_of_closuresval check_approx_for_set_of_closures : t -> checked_approx_for_set_of_closurestype checked_approx_for_closure = | Wrong| Ok of value_closure
* Variable.t option
* Symbol.t option
* value_set_of_closuresval check_approx_for_closure : t -> checked_approx_for_closuretype checked_approx_for_closure_allowing_unresolved = | Wrong| Unresolved of unresolved_value| Unknown| Unknown_because_of_unresolved_value of unresolved_value| Ok of value_closure
* Variable.t option
* Symbol.t option
* value_set_of_closuresval check_approx_for_closure_allowing_unresolved :
t ->
checked_approx_for_closure_allowing_unresolvedval check_approx_for_float : t -> float optionval float_array_as_constant : value_float_array -> float list optionval check_approx_for_string : t -> string optionval potentially_taken_const_switch_branch : t -> int -> switch_branch_selectionval potentially_taken_block_switch_branch : t -> int -> switch_branch_selectionval function_arity : function_declaration -> intval update_function_declarations :
function_declarations ->
funs:function_declaration Variable.Map.t ->
function_declarationsval import_function_declarations_for_pack :
function_declarations ->
(Set_of_closures_id.t -> Set_of_closures_id.t) ->
(Set_of_closures_origin.t -> Set_of_closures_origin.t) ->
function_declarationsval update_function_declaration_body :
function_declaration ->
(Flambda.t -> Flambda.t) ->
function_declarationval make_closure_map :
function_declarations Set_of_closures_id.Map.t ->
function_declarations Closure_id.Map.tval clear_function_bodies : function_declarations -> function_declarations