Flambda
type apply = {
func : Variable.t;
args : Variable.t list;
kind : call_kind;
dbg : Debuginfo.t;
inline : Lambda.inline_attribute;
specialise : Lambda.specialise_attribute;
}
type send = {
kind : Lambda.meth_kind;
meth : Variable.t;
obj : Variable.t;
args : Variable.t list;
dbg : Debuginfo.t;
}
type project_closure = Projection.project_closure
type move_within_set_of_closures = Projection.move_within_set_of_closures
type project_var = Projection.project_var
type t =
| Var of Variable.t
| Let of let_expr
| Let_mutable of let_mutable
| Let_rec of (Variable.t * named) list * t
| Apply of apply
| Send of send
| Assign of assign
| If_then_else of Variable.t * t * t
| Switch of Variable.t * switch
| String_switch of Variable.t * (string * t) list * t option
| Static_raise of Static_exception.t * Variable.t list
| Static_catch of Static_exception.t * Variable.t list * t * t
| Try_with of t * Variable.t * t
| While of t * t
| For of for_loop
| Proved_unreachable
and named =
| Symbol of Symbol.t
| Const of const
| Allocated_const of Allocated_const.t
| Read_mutable of Mutable_variable.t
| Read_symbol_field of Symbol.t * int
| Set_of_closures of set_of_closures
| Project_closure of project_closure
| Move_within_set_of_closures of move_within_set_of_closures
| Project_var of project_var
| Prim of Clambda_primitives.primitive * Variable.t list * Debuginfo.t
| Expr of t
and let_expr = private {
var : Variable.t;
defining_expr : named;
body : t;
free_vars_of_defining_expr : Variable.Set.t;
free_vars_of_body : Variable.Set.t;
}
and let_mutable = {
var : Mutable_variable.t;
initial_value : Variable.t;
contents_kind : Lambda.value_kind;
body : t;
}
and set_of_closures = private {
function_decls : function_declarations;
free_vars : specialised_to Variable.Map.t;
specialised_args : specialised_to Variable.Map.t;
direct_call_surrogates : Variable.t Variable.Map.t;
}
and 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_declaration = private {
closure_origin : Closure_origin.t;
params : Parameter.t list;
body : t;
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;
poll : Lambda.poll_attribute;
}
and switch = {
numconsts : Numbers.Int.Set.t;
consts : (int * t) list;
numblocks : Numbers.Int.Set.t;
blocks : (int * t) list;
failaction : t option;
}
and for_loop = {
bound_var : Variable.t;
from_value : Variable.t;
to_value : Variable.t;
direction : Asttypes.direction_flag;
body : t;
}
and constant_defining_value =
| Allocated_const of Allocated_const.t
| Block of Tag.t * constant_defining_value_block_field list
| Set_of_closures of set_of_closures
| Project_closure of Symbol.t * Closure_id.t
module Constant_defining_value : sig ... end
type expr = t
type program_body =
| Let_symbol of Symbol.t * constant_defining_value * program_body
| Let_rec_symbol of (Symbol.t * constant_defining_value) list * program_body
| Initialize_symbol of Symbol.t * Tag.t * t list * program_body
| Effect of t * program_body
| End of Symbol.t
val free_variables :
?ignore_uses_as_callee:unit ->
?ignore_uses_as_argument:unit ->
?ignore_uses_in_project_var:unit ->
t ->
Variable.Set.t
val free_variables_named :
?ignore_uses_in_project_var:unit ->
named ->
Variable.Set.t
val used_variables :
?ignore_uses_as_callee:unit ->
?ignore_uses_as_argument:unit ->
?ignore_uses_in_project_var:unit ->
t ->
Variable.Set.t
val used_variables_named :
?ignore_uses_in_project_var:unit ->
named ->
Variable.Set.t
val free_symbols : expr -> Symbol.Set.t
val free_symbols_named : named -> Symbol.Set.t
val free_symbols_program : program -> Symbol.Set.t
val fold_lets_option :
t ->
init:'a ->
for_defining_expr:('a -> Variable.t -> named -> 'a * Variable.t * named) ->
for_last_body:('a -> t -> t * 'b) ->
filter_defining_expr:
('b ->
Variable.t ->
named ->
Variable.Set.t ->
'b * Variable.t * named option) ->
t * 'b
val iter_lets :
t ->
for_defining_expr:(Variable.t -> named -> unit) ->
for_last_body:(t -> unit) ->
for_each_let:(t -> unit) ->
unit
val create_let : Variable.t -> named -> t -> t
module With_free_variables : sig ... end
val create_function_declaration :
params:Parameter.t list ->
body:t ->
stub:bool ->
dbg:Debuginfo.t ->
inline:Lambda.inline_attribute ->
specialise:Lambda.specialise_attribute ->
is_a_functor:bool ->
closure_origin:Closure_origin.t ->
poll:Lambda.poll_attribute ->
function_declaration
val update_function_declaration :
function_declaration ->
params:Parameter.t list ->
body:t ->
function_declaration
val create_function_declarations :
is_classic_mode:bool ->
funs:function_declaration Variable.Map.t ->
function_declarations
val create_function_declarations_with_origin :
is_classic_mode:bool ->
funs:function_declaration Variable.Map.t ->
set_of_closures_origin:Set_of_closures_origin.t ->
function_declarations
val update_body_of_function_declaration :
function_declaration ->
body:expr ->
function_declaration
val update_function_decl's_params_and_body :
function_declaration ->
params:Parameter.t list ->
body:expr ->
function_declaration
val update_function_declarations :
function_declarations ->
funs:function_declaration Variable.Map.t ->
function_declarations
val create_function_declarations_with_closures_origin :
is_classic_mode:bool ->
funs:function_declaration Variable.Map.t ->
set_of_closures_origin:Set_of_closures_origin.t ->
function_declarations
val 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_declarations
val create_set_of_closures :
function_decls:function_declarations ->
free_vars:specialised_to Variable.Map.t ->
specialised_args:specialised_to Variable.Map.t ->
direct_call_surrogates:Variable.t Variable.Map.t ->
set_of_closures
val used_params : function_declaration -> Variable.Set.t
val iter_general :
toplevel:bool ->
(t -> unit) ->
(named -> unit) ->
maybe_named ->
unit
val print : Format.formatter -> t -> unit
val print_named : Format.formatter -> named -> unit
val print_program : Format.formatter -> program -> unit
val print_const : Format.formatter -> const -> unit
val print_constant_defining_value :
Format.formatter ->
constant_defining_value ->
unit
val print_function_declaration :
Format.formatter ->
(Variable.t * function_declaration) ->
unit
val print_function_declarations :
Format.formatter ->
function_declarations ->
unit
val print_project_closure : Format.formatter -> project_closure -> unit
val print_move_within_set_of_closures :
Format.formatter ->
move_within_set_of_closures ->
unit
val print_project_var : Format.formatter -> project_var -> unit
val print_set_of_closures : Format.formatter -> set_of_closures -> unit
val print_specialised_to : Format.formatter -> specialised_to -> unit
val equal_specialised_to : specialised_to -> specialised_to -> bool
val compare_project_var : project_var -> project_var -> int
val compare_move_within_set_of_closures :
move_within_set_of_closures ->
move_within_set_of_closures ->
int
val compare_project_closure : project_closure -> project_closure -> int