Flambda
Intermediate language used for tree-based analysis and optimization.
Whether the callee in a function application is known at compile time.
Simple constants. ("Structured constants" are rewritten to invocations of Pmakeblock
so that they easily take part in optimizations.)
type apply = {
func : Variable.t; | |
args : Variable.t list; | |
kind : call_kind; | |
dbg : Debuginfo.t; | |
inline : Lambda.inline_attribute; | (* Instructions from the source code as to whether the callee should be inlined. *) |
specialise : Lambda.specialise_attribute; | (* Instructions from the source code as to whether the callee should be specialised. *) |
}
The application of a function to a list of arguments.
The update of a mutable variable. Mutable variables are distinct from immutable variables in Flambda.
type send = {
kind : Lambda.meth_kind; |
meth : Variable.t; |
obj : Variable.t; |
args : Variable.t list; |
dbg : Debuginfo.t; |
}
The invocation of a method.
type project_closure = Projection.project_closure
For details on these types, see projection.mli.
type move_within_set_of_closures = Projection.move_within_set_of_closures
type project_var = Projection.project_var
type specialised_to = {
var : Variable.t; | (* The "outer variable". *) |
projection : Projection.t option; | (* The |
}
See free_vars
and specialised_args
, below.
type t =
| Var of Variable.t | |
| Let of let_expr | |
| Let_mutable of let_mutable | |
| Let_rec of (Variable.t * named) list * t | (* CR-someday lwhite: give Let_rec the same fields as Let. *) |
| 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 | (* Restrictions on |
| 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 |
Flambda terms are partitioned in a pseudo-ANF manner; many terms are required to be let
-bound. This in particular ensures there is always a variable name for an expression that may be lifted out (for example if it is found to be constant). Note: All bound variables in Flambda terms must be distinct. Flambda_invariants
verifies this.
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 | (* During the lifting of |
| 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 | (* ANF escape hatch. *) |
Values of type named
will always be let
-bound to a Variable.t
.
and let_expr = private {
var : Variable.t; | |
defining_expr : named; | |
body : t; | |
free_vars_of_defining_expr : Variable.Set.t; | (* A cache of the free variables in the defining expression of the |
free_vars_of_body : Variable.Set.t; | (* A cache of the free variables of the body of the |
}
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; | (* Mapping from all variables free in the body of the |
specialised_args : specialised_to Variable.Map.t; | (* Parameters whose corresponding arguments are known to always alias a particular value. These are the only parameters that may, during An argument may only be specialised to a variable in the scope of the corresponding set of closures declaration. Usually, that variable itself also appears in the position of the specialised argument at all call sites of the function. However it may also be the case (for example in code generated as a result of As an example, supposing all call sites of f are represented here: This information is used for optimization purposes, if such a binding is known, it is possible to specialise the body of the function according to its parameter. This is usually introduced when specialising a recursive function, for instance. Specialised argument information for arguments that are used must never be erased. This ensures that specialised arguments whose approximations describe closures maintain those approximations, which is essential to transport the closure freshening information to the point of use (e.g. a |
direct_call_surrogates : Variable.t Variable.Map.t; | (* If |
}
The representation of a set of function declarations (possibly mutually recursive). Such a set encapsulates the declarations themselves, information about their defining environment, and information used specifically for optimization. Before a function can be applied it must be "projected" from a set of closures to yield a "closure". This is done using Project_closure
(see above). Given a closure, not only can it be applied, but information about its defining environment can be retrieved (using Project_var
, see above). At runtime, a set_of_closures
corresponds to an OCaml value with tag Closure_tag
(possibly with inline Infix_tag
(s)). As an optimization, an operation (Move_within_set_of_closures
) is provided (see above) which enables one closure within a set to be located given another closure in the same set. This avoids keeping a pointer to the whole set of closures alive when compiling, for example, mutually-recursive functions.
and function_declarations = private {
is_classic_mode : bool; | (* Indicates whether this |
set_of_closures_id : Set_of_closures_id.t; | (* An identifier (unique across all Flambda trees currently in memory) of the set of closures associated with this set of function declarations. *) |
set_of_closures_origin : Set_of_closures_origin.t; | (* An identifier of the original set of closures on which this set of function declarations is based. Used to prevent different specialisations of the same functions from being inlined/specialised within each other. *) |
funs : function_declaration Variable.Map.t; | (* The function(s) defined by the set of function declarations. The keys of this map are often referred to in the code as "fun_var"s. *) |
}
and function_declaration = private {
closure_origin : Closure_origin.t; | |
params : Parameter.t list; | |
body : t; | |
free_variables : Variable.Set.t; | (* All variables free in the *body* of the function. For example, a variable that is bound as one of the function's parameters will still be included in this set. This field is present as an optimization. *) |
free_symbols : Symbol.Set.t; | (* All symbols that occur in the function's body. (Symbols can never be bound in a function's body; the only thing that binds symbols is the |
stub : bool; | (* A stub function is a generated function used to prepare arguments or return values to allow indirect calls to functions with a special calling convention. For instance indirect calls to tuplified functions must go through a stub. Stubs will be unconditionally inlined. *) |
dbg : Debuginfo.t; | (* Debug info for the function declaration. *) |
inline : Lambda.inline_attribute; | (* Inlining requirements from the source code. *) |
specialise : Lambda.specialise_attribute; | (* Specialising requirements from the source code. *) |
is_a_functor : bool; | (* Whether the function is known definitively to be a functor. *) |
}
and switch = {
numconsts : Numbers.Int.Set.t; | (* Integer cases *) |
consts : (int * t) list; | (* Integer cases *) |
numblocks : Numbers.Int.Set.t; | (* Number of tag block cases *) |
blocks : (int * t) list; | (* Tag block cases *) |
failaction : t option; | (* Action to take if none matched *) |
}
Equivalent to the similar type in Lambda
.
and for_loop = {
bound_var : Variable.t; |
from_value : Variable.t; |
to_value : Variable.t; |
direction : Asttypes.direction_flag; |
body : t; |
}
Equivalent to the similar type in Lambda
.
and constant_defining_value =
| Allocated_const of Allocated_const.t | (* A single constant. These are never "simple constants" (type |
| Block of Tag.t * constant_defining_value_block_field list | (* A pre-allocated block full of constants (either simple constants or references to other constants, see below). *) |
| Set_of_closures of set_of_closures | (* A closed (and thus constant) set of closures. (That is to say, |
| Project_closure of Symbol.t * Closure_id.t | (* Selection of one closure from a constant set of closures. Analogous to the equivalent operation on expressions. *) |
Like a subset of Flambda.named
, except that instead of Variable.t
s we have Symbol.t
s, and everything is a constant (i.e. with a fixed value known at compile time). Values of this type describe constants that will be directly assigned to symbols in the object file (see below).
module Constant_defining_value : Identifiable.S with type t = constant_defining_value
type expr = t
type program_body =
| Let_symbol of Symbol.t * constant_defining_value * program_body | (* Define the given symbol to have the given constant value. *) |
| Let_rec_symbol of (Symbol.t * constant_defining_value) list * program_body | (* As for let rec f x = f x After lifting this produces (in pseudo-Flambda): Let_rec_symbol set_of_closures_symbol = (Set_of_closures Use of |
| Initialize_symbol of Symbol.t * Tag.t * t list * program_body | (* Define the given symbol as a constant block of the given size and tag; but with a possibly non-constant initializer. The initializer will be executed at most once (from the entry point of the compilation unit). *) |
| Effect of t * program_body | (* Cause the given expression, which may have a side effect, to be executed. The resulting value is discarded. |
| End of Symbol.t | (*
|
A "program" is the contents of one compilation unit. It describes the various values that are assigned to symbols (and in some cases fields of such symbols) in the object file. As such, it is closely related to the compilation of toplevel modules.
val free_variables : ?ignore_uses_as_callee:unit ->
?ignore_uses_as_argument:unit -> ?ignore_uses_in_project_var:unit -> t -> Variable.Set.t
Compute the free variables of a term. (This is O(1) for Let
s). If ignore_uses_as_callee
, all free variables inside Apply
expressions are ignored. Likewise ignore_uses_in_project_var
for Project_var
expressions.
val free_variables_named : ?ignore_uses_in_project_var:unit -> named -> Variable.Set.t
Compute the free variables of a named expression.
val used_variables : ?ignore_uses_as_callee:unit ->
?ignore_uses_as_argument:unit -> ?ignore_uses_in_project_var:unit -> t -> Variable.Set.t
Compute _all_ variables occurring inside an expression.
val used_variables_named : ?ignore_uses_in_project_var:unit -> named -> Variable.Set.t
Compute _all_ variables occurring inside a named expression.
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
Used to avoid exceeding the stack limit when handling expressions with multiple consecutive nested Let
-expressions. This saves rewriting large simplification functions in CPS. This function provides for the rewriting or elimination of expressions during the fold.
val map_lets : t -> for_defining_expr:(Variable.t -> named -> named) -> for_last_body:(t -> t) ->
after_rebuild:(t -> t) -> t
Like fold_lets_option
, but just a map.
val iter_lets : t -> for_defining_expr:(Variable.t -> named -> unit) -> for_last_body:(t -> unit) ->
for_each_let:(t -> unit) -> unit
Like map_lets
, but just an iterator.
val create_let : Variable.t -> named -> t -> t
Creates a Let
expression. (This computes the free variables of the defining expression and the body.)
Apply the specified function f
to the defining expression of the given Let
-expression, returning a new Let
.
module With_free_variables : sig ... end
A module for the manipulation of terms where the recomputation of free variable sets is to be kept to a minimum.
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 -> function_declaration
Create a function declaration. This calculates the free variables and symbols occurring in the specified body
.
val update_function_declaration : function_declaration -> params:Parameter.t list -> body:t -> function_declaration
Create a function declaration based on another function declaration
val create_function_declarations : is_classic_mode:bool -> funs:function_declaration Variable.Map.t -> function_declarations
Create a set of function declarations given the individual 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
Create a set of function declarations with a given set of closures origin.
val update_body_of_function_declaration : function_declaration -> body:expr -> function_declaration
Change only the code of a function declaration.
val update_function_decl's_params_and_body : function_declaration -> params:Parameter.t list -> body:expr -> function_declaration
Change only the code and parameters of a function declaration.
val update_function_declarations : function_declarations -> funs:function_declaration Variable.Map.t -> function_declarations
Create a set of function declarations based on another set of 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
Create a set of closures. Checks are made to ensure that free_vars
and specialised_args
are reasonable.
val used_params : function_declaration -> Variable.Set.t
Given a function declaration, find which of its parameters (if any) are used in the body.
val iter_general : toplevel:bool -> (t -> unit) -> (named -> unit) -> maybe_named -> unit
This function is designed for the internal use of Flambda_iterators
. See that module for iterators to be used over Flambda terms.
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