moonpool/dev/ocaml/Flambda/index.html

120 lines
No EOL
79 KiB
HTML
Raw Blame History

This file contains ambiguous Unicode characters

This file contains Unicode characters that might be confused with other characters. If you think that this is intentional, you can safely ignore this warning. Use the Escape button to reveal them.

<!DOCTYPE html>
<html xmlns="http://www.w3.org/1999/xhtml"><head><title>Flambda (ocaml.Flambda)</title><link rel="stylesheet" href="../../_odoc-theme/odoc.css"/><meta charset="utf-8"/><meta name="generator" content="odoc 2.2.1"/><meta name="viewport" content="width=device-width,initial-scale=1.0"/><script src="../../highlight.pack.js"></script><script>hljs.initHighlightingOnLoad();</script></head><body class="odoc"><nav class="odoc-nav"><a href="../index.html">Up</a> <a href="../index.html">ocaml</a> &#x00BB; Flambda</nav><header class="odoc-preamble"><h1>Module <code><span>Flambda</span></code></h1><p>Intermediate language used for tree-based analysis and optimization.</p></header><div class="odoc-content"><div class="odoc-spec"><div class="spec type anchored" id="type-call_kind"><a href="#type-call_kind" class="anchor"></a><code><span><span class="keyword">type</span> call_kind</span><span> = </span></code><ol><li id="type-call_kind.Indirect" class="def variant constructor anchored"><a href="#type-call_kind.Indirect" class="anchor"></a><code><span>| </span><span><span class="constructor">Indirect</span></span></code></li><li id="type-call_kind.Direct" class="def variant constructor anchored"><a href="#type-call_kind.Direct" class="anchor"></a><code><span>| </span><span><span class="constructor">Direct</span> <span class="keyword">of</span> <a href="../Closure_id/index.html#type-t">Closure_id.t</a></span></code></li></ol></div><div class="spec-doc"><p>Whether the callee in a function application is known at compile time.</p></div></div><div class="odoc-spec"><div class="spec type anchored" id="type-const"><a href="#type-const" class="anchor"></a><code><span><span class="keyword">type</span> const</span><span> = </span></code><ol><li id="type-const.Int" class="def variant constructor anchored"><a href="#type-const.Int" class="anchor"></a><code><span>| </span><span><span class="constructor">Int</span> <span class="keyword">of</span> int</span></code></li><li id="type-const.Char" class="def variant constructor anchored"><a href="#type-const.Char" class="anchor"></a><code><span>| </span><span><span class="constructor">Char</span> <span class="keyword">of</span> char</span></code><div class="def-doc"><span class="comment-delim">(*</span><p><code>Char</code> is kept separate from <code>Int</code> to improve printing</p><span class="comment-delim">*)</span></div></li></ol></div><div class="spec-doc"><p>Simple constants. (&quot;Structured constants&quot; are rewritten to invocations of <code>Pmakeblock</code> so that they easily take part in optimizations.)</p></div></div><div class="odoc-spec"><div class="spec type anchored" id="type-apply"><a href="#type-apply" class="anchor"></a><code><span><span class="keyword">type</span> apply</span><span> = </span><span>{</span></code><ol><li id="type-apply.func" class="def record field anchored"><a href="#type-apply.func" class="anchor"></a><code><span>func : <a href="../Variable/index.html#type-t">Variable.t</a>;</span></code></li><li id="type-apply.args" class="def record field anchored"><a href="#type-apply.args" class="anchor"></a><code><span>args : <span><a href="../Variable/index.html#type-t">Variable.t</a> list</span>;</span></code></li><li id="type-apply.kind" class="def record field anchored"><a href="#type-apply.kind" class="anchor"></a><code><span>kind : <a href="#type-call_kind">call_kind</a>;</span></code></li><li id="type-apply.dbg" class="def record field anchored"><a href="#type-apply.dbg" class="anchor"></a><code><span>dbg : <a href="../Debuginfo/index.html#type-t">Debuginfo.t</a>;</span></code></li><li id="type-apply.inline" class="def record field anchored"><a href="#type-apply.inline" class="anchor"></a><code><span>inline : <a href="../Lambda/index.html#type-inline_attribute">Lambda.inline_attribute</a>;</span></code><div class="def-doc"><span class="comment-delim">(*</span><p>Instructions from the source code as to whether the callee should be inlined.</p><span class="comment-delim">*)</span></div></li><li id="type-apply.specialise" class="def record field anchored"><a href="#type-apply.specialise" class="anchor"></a><code><span>specialise : <a href="../Lambda/index.html#type-specialise_attribute">Lambda.specialise_attribute</a>;</span></code><div class="def-doc"><span class="comment-delim">(*</span><p>Instructions from the source code as to whether the callee should be specialised.</p><span class="comment-delim">*)</span></div></li></ol><code><span>}</span></code></div><div class="spec-doc"><p>The application of a function to a list of arguments.</p></div></div><div class="odoc-spec"><div class="spec type anchored" id="type-assign"><a href="#type-assign" class="anchor"></a><code><span><span class="keyword">type</span> assign</span><span> = </span><span>{</span></code><ol><li id="type-assign.being_assigned" class="def record field anchored"><a href="#type-assign.being_assigned" class="anchor"></a><code><span>being_assigned : <a href="../Mutable_variable/index.html#type-t">Mutable_variable.t</a>;</span></code></li><li id="type-assign.new_value" class="def record field anchored"><a href="#type-assign.new_value" class="anchor"></a><code><span>new_value : <a href="../Variable/index.html#type-t">Variable.t</a>;</span></code></li></ol><code><span>}</span></code></div><div class="spec-doc"><p>The update of a mutable variable. Mutable variables are distinct from immutable variables in Flambda.</p></div></div><div class="odoc-spec"><div class="spec type anchored" id="type-send"><a href="#type-send" class="anchor"></a><code><span><span class="keyword">type</span> send</span><span> = </span><span>{</span></code><ol><li id="type-send.kind" class="def record field anchored"><a href="#type-send.kind" class="anchor"></a><code><span>kind : <a href="../Lambda/index.html#type-meth_kind">Lambda.meth_kind</a>;</span></code></li><li id="type-send.meth" class="def record field anchored"><a href="#type-send.meth" class="anchor"></a><code><span>meth : <a href="../Variable/index.html#type-t">Variable.t</a>;</span></code></li><li id="type-send.obj" class="def record field anchored"><a href="#type-send.obj" class="anchor"></a><code><span>obj : <a href="../Variable/index.html#type-t">Variable.t</a>;</span></code></li><li id="type-send.args" class="def record field anchored"><a href="#type-send.args" class="anchor"></a><code><span>args : <span><a href="../Variable/index.html#type-t">Variable.t</a> list</span>;</span></code></li><li id="type-send.dbg" class="def record field anchored"><a href="#type-send.dbg" class="anchor"></a><code><span>dbg : <a href="../Debuginfo/index.html#type-t">Debuginfo.t</a>;</span></code></li></ol><code><span>}</span></code></div><div class="spec-doc"><p>The invocation of a method.</p></div></div><div class="odoc-spec"><div class="spec type anchored" id="type-project_closure"><a href="#type-project_closure" class="anchor"></a><code><span><span class="keyword">type</span> project_closure</span><span> = <a href="../Projection/index.html#type-project_closure">Projection.project_closure</a></span></code></div><div class="spec-doc"><p>For details on these types, see projection.mli.</p></div></div><div class="odoc-spec"><div class="spec type anchored" id="type-move_within_set_of_closures"><a href="#type-move_within_set_of_closures" class="anchor"></a><code><span><span class="keyword">type</span> move_within_set_of_closures</span><span> = <a href="../Projection/index.html#type-move_within_set_of_closures">Projection.move_within_set_of_closures</a></span></code></div></div><div class="odoc-spec"><div class="spec type anchored" id="type-project_var"><a href="#type-project_var" class="anchor"></a><code><span><span class="keyword">type</span> project_var</span><span> = <a href="../Projection/index.html#type-project_var">Projection.project_var</a></span></code></div></div><div class="odoc-spec"><div class="spec type anchored" id="type-specialised_to"><a href="#type-specialised_to" class="anchor"></a><code><span><span class="keyword">type</span> specialised_to</span><span> = </span><span>{</span></code><ol><li id="type-specialised_to.var" class="def record field anchored"><a href="#type-specialised_to.var" class="anchor"></a><code><span>var : <a href="../Variable/index.html#type-t">Variable.t</a>;</span></code><div class="def-doc"><span class="comment-delim">(*</span><p>The &quot;outer variable&quot;.</p><span class="comment-delim">*)</span></div></li><li id="type-specialised_to.projection" class="def record field anchored"><a href="#type-specialised_to.projection" class="anchor"></a><code><span>projection : <span><a href="../Projection/index.html#type-t">Projection.t</a> option</span>;</span></code><div class="def-doc"><span class="comment-delim">(*</span><p>The <code>projecting_from</code> value (see projection.mli) of any <code>projection</code> must be another free variable or specialised argument (depending on whether this record type is involved in <code>free_vars</code> or <code>specialised_args</code> respectively) in the same set of closures. As such, this field describes a relation of projections between either the <code>free_vars</code> or the <code>specialised_args</code>.</p><span class="comment-delim">*)</span></div></li></ol><code><span>}</span></code></div><div class="spec-doc"><p>See <code>free_vars</code> and <code>specialised_args</code>, below.</p></div></div><div class="odoc-spec"><div class="spec type anchored" id="type-t"><a href="#type-t" class="anchor"></a><code><span><span class="keyword">type</span> t</span><span> = </span></code><ol><li id="type-t.Var" class="def variant constructor anchored"><a href="#type-t.Var" class="anchor"></a><code><span>| </span><span><span class="constructor">Var</span> <span class="keyword">of</span> <a href="../Variable/index.html#type-t">Variable.t</a></span></code></li><li id="type-t.Let" class="def variant constructor anchored"><a href="#type-t.Let" class="anchor"></a><code><span>| </span><span><span class="constructor">Let</span> <span class="keyword">of</span> <a href="#type-let_expr">let_expr</a></span></code></li><li id="type-t.Let_mutable" class="def variant constructor anchored"><a href="#type-t.Let_mutable" class="anchor"></a><code><span>| </span><span><span class="constructor">Let_mutable</span> <span class="keyword">of</span> <a href="#type-let_mutable">let_mutable</a></span></code></li><li id="type-t.Let_rec" class="def variant constructor anchored"><a href="#type-t.Let_rec" class="anchor"></a><code><span>| </span><span><span class="constructor">Let_rec</span> <span class="keyword">of</span> <span><span>(<a href="../Variable/index.html#type-t">Variable.t</a> * <a href="#type-named">named</a>)</span> list</span> * <a href="#type-t">t</a></span></code><div class="def-doc"><span class="comment-delim">(*</span><p>CR-someday lwhite: give Let_rec the same fields as Let.</p><span class="comment-delim">*)</span></div></li><li id="type-t.Apply" class="def variant constructor anchored"><a href="#type-t.Apply" class="anchor"></a><code><span>| </span><span><span class="constructor">Apply</span> <span class="keyword">of</span> <a href="#type-apply">apply</a></span></code></li><li id="type-t.Send" class="def variant constructor anchored"><a href="#type-t.Send" class="anchor"></a><code><span>| </span><span><span class="constructor">Send</span> <span class="keyword">of</span> <a href="#type-send">send</a></span></code></li><li id="type-t.Assign" class="def variant constructor anchored"><a href="#type-t.Assign" class="anchor"></a><code><span>| </span><span><span class="constructor">Assign</span> <span class="keyword">of</span> <a href="#type-assign">assign</a></span></code></li><li id="type-t.If_then_else" class="def variant constructor anchored"><a href="#type-t.If_then_else" class="anchor"></a><code><span>| </span><span><span class="constructor">If_then_else</span> <span class="keyword">of</span> <a href="../Variable/index.html#type-t">Variable.t</a> * <a href="#type-t">t</a> * <a href="#type-t">t</a></span></code></li><li id="type-t.Switch" class="def variant constructor anchored"><a href="#type-t.Switch" class="anchor"></a><code><span>| </span><span><span class="constructor">Switch</span> <span class="keyword">of</span> <a href="../Variable/index.html#type-t">Variable.t</a> * <a href="#type-switch">switch</a></span></code></li><li id="type-t.String_switch" class="def variant constructor anchored"><a href="#type-t.String_switch" class="anchor"></a><code><span>| </span><span><span class="constructor">String_switch</span> <span class="keyword">of</span> <a href="../Variable/index.html#type-t">Variable.t</a> * <span><span>(string * <a href="#type-t">t</a>)</span> list</span> * <span><a href="#type-t">t</a> option</span></span></code><div class="def-doc"><span class="comment-delim">(*</span><p>Restrictions on <code>Lambda.Lstringswitch</code> also apply to <code>String_switch</code>.</p><span class="comment-delim">*)</span></div></li><li id="type-t.Static_raise" class="def variant constructor anchored"><a href="#type-t.Static_raise" class="anchor"></a><code><span>| </span><span><span class="constructor">Static_raise</span> <span class="keyword">of</span> <a href="../Static_exception/index.html#type-t">Static_exception.t</a> * <span><a href="../Variable/index.html#type-t">Variable.t</a> list</span></span></code></li><li id="type-t.Static_catch" class="def variant constructor anchored"><a href="#type-t.Static_catch" class="anchor"></a><code><span>| </span><span><span class="constructor">Static_catch</span> <span class="keyword">of</span> <a href="../Static_exception/index.html#type-t">Static_exception.t</a> * <span><a href="../Variable/index.html#type-t">Variable.t</a> list</span> * <a href="#type-t">t</a> * <a href="#type-t">t</a></span></code></li><li id="type-t.Try_with" class="def variant constructor anchored"><a href="#type-t.Try_with" class="anchor"></a><code><span>| </span><span><span class="constructor">Try_with</span> <span class="keyword">of</span> <a href="#type-t">t</a> * <a href="../Variable/index.html#type-t">Variable.t</a> * <a href="#type-t">t</a></span></code></li><li id="type-t.While" class="def variant constructor anchored"><a href="#type-t.While" class="anchor"></a><code><span>| </span><span><span class="constructor">While</span> <span class="keyword">of</span> <a href="#type-t">t</a> * <a href="#type-t">t</a></span></code></li><li id="type-t.For" class="def variant constructor anchored"><a href="#type-t.For" class="anchor"></a><code><span>| </span><span><span class="constructor">For</span> <span class="keyword">of</span> <a href="#type-for_loop">for_loop</a></span></code></li><li id="type-t.Proved_unreachable" class="def variant constructor anchored"><a href="#type-t.Proved_unreachable" class="anchor"></a><code><span>| </span><span><span class="constructor">Proved_unreachable</span></span></code></li></ol></div><div class="spec-doc"><p>Flambda terms are partitioned in a pseudo-ANF manner; many terms are required to be <code>let</code>-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. <code>Flambda_invariants</code> verifies this.</p></div></div><div class="odoc-spec"><div class="spec type anchored" id="type-named"><a href="#type-named" class="anchor"></a><code><span><span class="keyword">and</span> named</span><span> = </span></code><ol><li id="type-named.Symbol" class="def variant constructor anchored"><a href="#type-named.Symbol" class="anchor"></a><code><span>| </span><span><span class="constructor">Symbol</span> <span class="keyword">of</span> <a href="../Symbol/index.html#type-t">Symbol.t</a></span></code></li><li id="type-named.Const" class="def variant constructor anchored"><a href="#type-named.Const" class="anchor"></a><code><span>| </span><span><span class="constructor">Const</span> <span class="keyword">of</span> <a href="#type-const">const</a></span></code></li><li id="type-named.Allocated_const" class="def variant constructor anchored"><a href="#type-named.Allocated_const" class="anchor"></a><code><span>| </span><span><span class="constructor">Allocated_const</span> <span class="keyword">of</span> <a href="../Allocated_const/index.html#type-t">Allocated_const.t</a></span></code></li><li id="type-named.Read_mutable" class="def variant constructor anchored"><a href="#type-named.Read_mutable" class="anchor"></a><code><span>| </span><span><span class="constructor">Read_mutable</span> <span class="keyword">of</span> <a href="../Mutable_variable/index.html#type-t">Mutable_variable.t</a></span></code></li><li id="type-named.Read_symbol_field" class="def variant constructor anchored"><a href="#type-named.Read_symbol_field" class="anchor"></a><code><span>| </span><span><span class="constructor">Read_symbol_field</span> <span class="keyword">of</span> <a href="../Symbol/index.html#type-t">Symbol.t</a> * int</span></code><div class="def-doc"><span class="comment-delim">(*</span><p>During the lifting of <code>let</code> bindings to <code>program</code> constructions after closure conversion, we generate symbols and their corresponding definitions (which may or may not be constant), together with field accesses to such symbols. We would like it to be the case that such field accesses are simplified to the relevant component of the symbol concerned. (The rationale is to generate efficient code and share constants as expected: see e.g. tests/asmcomp/staticalloc.ml.) The components of the symbol would be identified by other symbols. This sort of access pattern is feasible because the top-level structure of symbols is statically allocated and fixed at compile time. It may seem that <code>Prim (Pfield, ...)</code> expressions could be used to perform the field accesses. However for simplicity, to avoid having to keep track of properties of individual fields of blocks, <code>Inconstant_idents</code> never deems a <code>Prim (Pfield, ...)</code> expression to be constant. This would in general prevent field accesses to symbols from being simplified in the way we would like, since <code>Lift_constants</code> would not assign new symbols (i.e. the things we would like to simplify to) to the various projections from the symbols in question. To circumvent this problem we use <code>Read_symbol_field</code> when generating projections from the top level of symbols. Owing to the properties of symbols described above, such expressions may be eligible for declaration as constant by <code>Inconstant_idents</code> (and thus themselves lifted to another symbol), without any further complication. <code>Read_symbol_field</code> may only be used when the definition of the symbol is in scope in the <code>program</code>. For external unresolved symbols, <code>Pfield</code> may still be used; it will be changed to <code>Read_symbol_field</code> by <code>Inline_and_simplify</code> when (and if) the symbol is imported.</p><span class="comment-delim">*)</span></div></li><li id="type-named.Set_of_closures" class="def variant constructor anchored"><a href="#type-named.Set_of_closures" class="anchor"></a><code><span>| </span><span><span class="constructor">Set_of_closures</span> <span class="keyword">of</span> <a href="#type-set_of_closures">set_of_closures</a></span></code></li><li id="type-named.Project_closure" class="def variant constructor anchored"><a href="#type-named.Project_closure" class="anchor"></a><code><span>| </span><span><span class="constructor">Project_closure</span> <span class="keyword">of</span> <a href="#type-project_closure">project_closure</a></span></code></li><li id="type-named.Move_within_set_of_closures" class="def variant constructor anchored"><a href="#type-named.Move_within_set_of_closures" class="anchor"></a><code><span>| </span><span><span class="constructor">Move_within_set_of_closures</span> <span class="keyword">of</span> <a href="#type-move_within_set_of_closures">move_within_set_of_closures</a></span></code></li><li id="type-named.Project_var" class="def variant constructor anchored"><a href="#type-named.Project_var" class="anchor"></a><code><span>| </span><span><span class="constructor">Project_var</span> <span class="keyword">of</span> <a href="#type-project_var">project_var</a></span></code></li><li id="type-named.Prim" class="def variant constructor anchored"><a href="#type-named.Prim" class="anchor"></a><code><span>| </span><span><span class="constructor">Prim</span> <span class="keyword">of</span> <a href="../Clambda_primitives/index.html#type-primitive">Clambda_primitives.primitive</a> * <span><a href="../Variable/index.html#type-t">Variable.t</a> list</span> * <a href="../Debuginfo/index.html#type-t">Debuginfo.t</a></span></code></li><li id="type-named.Expr" class="def variant constructor anchored"><a href="#type-named.Expr" class="anchor"></a><code><span>| </span><span><span class="constructor">Expr</span> <span class="keyword">of</span> <a href="#type-t">t</a></span></code><div class="def-doc"><span class="comment-delim">(*</span><p>ANF escape hatch.</p><span class="comment-delim">*)</span></div></li></ol></div><div class="spec-doc"><p>Values of type <code>named</code> will always be <code>let</code>-bound to a <code>Variable.t</code>.</p></div></div><div class="odoc-spec"><div class="spec type anchored" id="type-let_expr"><a href="#type-let_expr" class="anchor"></a><code><span><span class="keyword">and</span> let_expr</span><span> = <span class="keyword">private</span> </span><span>{</span></code><ol><li id="type-let_expr.var" class="def record field anchored"><a href="#type-let_expr.var" class="anchor"></a><code><span>var : <a href="../Variable/index.html#type-t">Variable.t</a>;</span></code></li><li id="type-let_expr.defining_expr" class="def record field anchored"><a href="#type-let_expr.defining_expr" class="anchor"></a><code><span>defining_expr : <a href="#type-named">named</a>;</span></code></li><li id="type-let_expr.body" class="def record field anchored"><a href="#type-let_expr.body" class="anchor"></a><code><span>body : <a href="#type-t">t</a>;</span></code></li><li id="type-let_expr.free_vars_of_defining_expr" class="def record field anchored"><a href="#type-let_expr.free_vars_of_defining_expr" class="anchor"></a><code><span>free_vars_of_defining_expr : <a href="../Variable/Set/index.html#type-t">Variable.Set.t</a>;</span></code><div class="def-doc"><span class="comment-delim">(*</span><p>A cache of the free variables in the defining expression of the <code>let</code>.</p><span class="comment-delim">*)</span></div></li><li id="type-let_expr.free_vars_of_body" class="def record field anchored"><a href="#type-let_expr.free_vars_of_body" class="anchor"></a><code><span>free_vars_of_body : <a href="../Variable/Set/index.html#type-t">Variable.Set.t</a>;</span></code><div class="def-doc"><span class="comment-delim">(*</span><p>A cache of the free variables of the body of the <code>let</code>. This is an important optimization.</p><span class="comment-delim">*)</span></div></li></ol><code><span>}</span></code></div></div><div class="odoc-spec"><div class="spec type anchored" id="type-let_mutable"><a href="#type-let_mutable" class="anchor"></a><code><span><span class="keyword">and</span> let_mutable</span><span> = </span><span>{</span></code><ol><li id="type-let_mutable.var" class="def record field anchored"><a href="#type-let_mutable.var" class="anchor"></a><code><span>var : <a href="../Mutable_variable/index.html#type-t">Mutable_variable.t</a>;</span></code></li><li id="type-let_mutable.initial_value" class="def record field anchored"><a href="#type-let_mutable.initial_value" class="anchor"></a><code><span>initial_value : <a href="../Variable/index.html#type-t">Variable.t</a>;</span></code></li><li id="type-let_mutable.contents_kind" class="def record field anchored"><a href="#type-let_mutable.contents_kind" class="anchor"></a><code><span>contents_kind : <a href="../Lambda/index.html#type-value_kind">Lambda.value_kind</a>;</span></code></li><li id="type-let_mutable.body" class="def record field anchored"><a href="#type-let_mutable.body" class="anchor"></a><code><span>body : <a href="#type-t">t</a>;</span></code></li></ol><code><span>}</span></code></div></div><div class="odoc-spec"><div class="spec type anchored" id="type-set_of_closures"><a href="#type-set_of_closures" class="anchor"></a><code><span><span class="keyword">and</span> set_of_closures</span><span> = <span class="keyword">private</span> </span><span>{</span></code><ol><li id="type-set_of_closures.function_decls" class="def record field anchored"><a href="#type-set_of_closures.function_decls" class="anchor"></a><code><span>function_decls : <a href="#type-function_declarations">function_declarations</a>;</span></code></li><li id="type-set_of_closures.free_vars" class="def record field anchored"><a href="#type-set_of_closures.free_vars" class="anchor"></a><code><span>free_vars : <span><a href="#type-specialised_to">specialised_to</a> <a href="../Variable/Map/index.html#type-t">Variable.Map.t</a></span>;</span></code><div class="def-doc"><span class="comment-delim">(*</span><p>Mapping from all variables free in the body of the <code>function_decls</code> to variables in scope at the definition point of the <code>set_of_closures</code>. The domain of this map is sometimes known as the &quot;variables bound by the closure&quot;.</p><span class="comment-delim">*)</span></div></li><li id="type-set_of_closures.specialised_args" class="def record field anchored"><a href="#type-set_of_closures.specialised_args" class="anchor"></a><code><span>specialised_args : <span><a href="#type-specialised_to">specialised_to</a> <a href="../Variable/Map/index.html#type-t">Variable.Map.t</a></span>;</span></code><div class="def-doc"><span class="comment-delim">(*</span><p>Parameters whose corresponding arguments are known to always alias a particular value. These are the only parameters that may, during <code>Inline_and_simplify</code>, have non-unknown approximations.</p><p>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 <code>Augment_specialised_args</code>) that the various call sites of such a function have differing variables in the position of the specialised argument. This is permissible *so long as it is certain they all alias the same value*. Great care must be taken in transformations that result in this situation since there are no invariant checks for correctness.</p><p>As an example, supposing all call sites of f are represented here: <code>let x = ... in
let f a b c = ... in
let y = ... in
f x y 1;
f x y 1</code> the specialised arguments of f can (but does not necessarily) contain the association <code>a</code> -&gt; <code>x</code>, but cannot contain <code>b</code> -&gt; <code>y</code> because <code>f</code> is not in the scope of <code>y</code>. If f were the recursive function <code>let rec f a b c = f a 1 2 in</code>, <code>a</code> -&gt; <code>x</code> would still be a valid specialised argument because all recursive calls maintain the invariant.</p><p>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. <code>let rec map f = function
| [] -&gt; []
| h :: t -&gt; f h :: map f t
let map_succ l =
let succ x = x + 1 in
map succ l</code> <code>map</code> can be duplicated in <code>map_succ</code> to be specialised for the argument <code>f</code>. This will result in <code>let map_succ l =
let succ x = x + 1 in
let rec map f = function
| [] -&gt; []
| h :: t -&gt; f h :: map f t in
map succ l</code> with map having <code>f</code> -&gt; <code>succ</code> in its <code>specialised_args</code> field.</p><p>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 <code>Project_var</code> from such an argument).</p><span class="comment-delim">*)</span></div></li><li id="type-set_of_closures.direct_call_surrogates" class="def record field anchored"><a href="#type-set_of_closures.direct_call_surrogates" class="anchor"></a><code><span>direct_call_surrogates : <span><a href="../Variable/index.html#type-t">Variable.t</a> <a href="../Variable/Map/index.html#type-t">Variable.Map.t</a></span>;</span></code><div class="def-doc"><span class="comment-delim">(*</span><p>If <code>direct_call_surrogates</code> maps <code>fun_var1</code> to <code>fun_var2</code> then direct calls to <code>fun_var1</code> should be redirected to <code>fun_var2</code>. This is used to reduce the overhead of transformations that introduce wrapper functions (which will be inlined at direct call sites, but will penalise indirect call sites). <code>direct_call_surrogates</code> may not be transitively closed.</p><span class="comment-delim">*)</span></div></li></ol><code><span>}</span></code></div><div class="spec-doc"><p>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 &quot;projected&quot; from a set of closures to yield a &quot;closure&quot;. This is done using <code>Project_closure</code> (see above). Given a closure, not only can it be applied, but information about its defining environment can be retrieved (using <code>Project_var</code>, see above). At runtime, a <code>set_of_closures</code> corresponds to an OCaml value with tag <code>Closure_tag</code> (possibly with inline <code>Infix_tag</code>(s)). As an optimization, an operation (<code>Move_within_set_of_closures</code>) 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.</p></div></div><div class="odoc-spec"><div class="spec type anchored" id="type-function_declarations"><a href="#type-function_declarations" class="anchor"></a><code><span><span class="keyword">and</span> function_declarations</span><span> = <span class="keyword">private</span> </span><span>{</span></code><ol><li id="type-function_declarations.is_classic_mode" class="def record field anchored"><a href="#type-function_declarations.is_classic_mode" class="anchor"></a><code><span>is_classic_mode : bool;</span></code><div class="def-doc"><span class="comment-delim">(*</span><p>Indicates whether this <code>function_declarations</code> was compiled with -Oclassic.</p><span class="comment-delim">*)</span></div></li><li id="type-function_declarations.set_of_closures_id" class="def record field anchored"><a href="#type-function_declarations.set_of_closures_id" class="anchor"></a><code><span>set_of_closures_id : <a href="../Set_of_closures_id/index.html#type-t">Set_of_closures_id.t</a>;</span></code><div class="def-doc"><span class="comment-delim">(*</span><p>An identifier (unique across all Flambda trees currently in memory) of the set of closures associated with this set of function declarations.</p><span class="comment-delim">*)</span></div></li><li id="type-function_declarations.set_of_closures_origin" class="def record field anchored"><a href="#type-function_declarations.set_of_closures_origin" class="anchor"></a><code><span>set_of_closures_origin : <a href="../Set_of_closures_origin/index.html#type-t">Set_of_closures_origin.t</a>;</span></code><div class="def-doc"><span class="comment-delim">(*</span><p>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.</p><span class="comment-delim">*)</span></div></li><li id="type-function_declarations.funs" class="def record field anchored"><a href="#type-function_declarations.funs" class="anchor"></a><code><span>funs : <span><a href="#type-function_declaration">function_declaration</a> <a href="../Variable/Map/index.html#type-t">Variable.Map.t</a></span>;</span></code><div class="def-doc"><span class="comment-delim">(*</span><p>The function(s) defined by the set of function declarations. The keys of this map are often referred to in the code as &quot;fun_var&quot;s.</p><span class="comment-delim">*)</span></div></li></ol><code><span>}</span></code></div></div><div class="odoc-spec"><div class="spec type anchored" id="type-function_declaration"><a href="#type-function_declaration" class="anchor"></a><code><span><span class="keyword">and</span> function_declaration</span><span> = <span class="keyword">private</span> </span><span>{</span></code><ol><li id="type-function_declaration.closure_origin" class="def record field anchored"><a href="#type-function_declaration.closure_origin" class="anchor"></a><code><span>closure_origin : <a href="../Closure_origin/index.html#type-t">Closure_origin.t</a>;</span></code></li><li id="type-function_declaration.params" class="def record field anchored"><a href="#type-function_declaration.params" class="anchor"></a><code><span>params : <span><a href="../Parameter/index.html#type-t">Parameter.t</a> list</span>;</span></code></li><li id="type-function_declaration.body" class="def record field anchored"><a href="#type-function_declaration.body" class="anchor"></a><code><span>body : <a href="#type-t">t</a>;</span></code></li><li id="type-function_declaration.free_variables" class="def record field anchored"><a href="#type-function_declaration.free_variables" class="anchor"></a><code><span>free_variables : <a href="../Variable/Set/index.html#type-t">Variable.Set.t</a>;</span></code><div class="def-doc"><span class="comment-delim">(*</span><p>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.</p><span class="comment-delim">*)</span></div></li><li id="type-function_declaration.free_symbols" class="def record field anchored"><a href="#type-function_declaration.free_symbols" class="anchor"></a><code><span>free_symbols : <a href="../Symbol/Set/index.html#type-t">Symbol.Set.t</a>;</span></code><div class="def-doc"><span class="comment-delim">(*</span><p>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 <code>program</code> constructions below.)</p><span class="comment-delim">*)</span></div></li><li id="type-function_declaration.stub" class="def record field anchored"><a href="#type-function_declaration.stub" class="anchor"></a><code><span>stub : bool;</span></code><div class="def-doc"><span class="comment-delim">(*</span><p>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.</p><span class="comment-delim">*)</span></div></li><li id="type-function_declaration.dbg" class="def record field anchored"><a href="#type-function_declaration.dbg" class="anchor"></a><code><span>dbg : <a href="../Debuginfo/index.html#type-t">Debuginfo.t</a>;</span></code><div class="def-doc"><span class="comment-delim">(*</span><p>Debug info for the function declaration.</p><span class="comment-delim">*)</span></div></li><li id="type-function_declaration.inline" class="def record field anchored"><a href="#type-function_declaration.inline" class="anchor"></a><code><span>inline : <a href="../Lambda/index.html#type-inline_attribute">Lambda.inline_attribute</a>;</span></code><div class="def-doc"><span class="comment-delim">(*</span><p>Inlining requirements from the source code.</p><span class="comment-delim">*)</span></div></li><li id="type-function_declaration.specialise" class="def record field anchored"><a href="#type-function_declaration.specialise" class="anchor"></a><code><span>specialise : <a href="../Lambda/index.html#type-specialise_attribute">Lambda.specialise_attribute</a>;</span></code><div class="def-doc"><span class="comment-delim">(*</span><p>Specialising requirements from the source code.</p><span class="comment-delim">*)</span></div></li><li id="type-function_declaration.is_a_functor" class="def record field anchored"><a href="#type-function_declaration.is_a_functor" class="anchor"></a><code><span>is_a_functor : bool;</span></code><div class="def-doc"><span class="comment-delim">(*</span><p>Whether the function is known definitively to be a functor.</p><span class="comment-delim">*)</span></div></li><li id="type-function_declaration.poll" class="def record field anchored"><a href="#type-function_declaration.poll" class="anchor"></a><code><span>poll : <a href="../Lambda/index.html#type-poll_attribute">Lambda.poll_attribute</a>;</span></code><div class="def-doc"><span class="comment-delim">(*</span><p>Behaviour for polls</p><span class="comment-delim">*)</span></div></li></ol><code><span>}</span></code></div></div><div class="odoc-spec"><div class="spec type anchored" id="type-switch"><a href="#type-switch" class="anchor"></a><code><span><span class="keyword">and</span> switch</span><span> = </span><span>{</span></code><ol><li id="type-switch.numconsts" class="def record field anchored"><a href="#type-switch.numconsts" class="anchor"></a><code><span>numconsts : <a href="../Numbers/Int/Set/index.html#type-t">Numbers.Int.Set.t</a>;</span></code><div class="def-doc"><span class="comment-delim">(*</span><p>Integer cases</p><span class="comment-delim">*)</span></div></li><li id="type-switch.consts" class="def record field anchored"><a href="#type-switch.consts" class="anchor"></a><code><span>consts : <span><span>(int * <a href="#type-t">t</a>)</span> list</span>;</span></code><div class="def-doc"><span class="comment-delim">(*</span><p>Integer cases</p><span class="comment-delim">*)</span></div></li><li id="type-switch.numblocks" class="def record field anchored"><a href="#type-switch.numblocks" class="anchor"></a><code><span>numblocks : <a href="../Numbers/Int/Set/index.html#type-t">Numbers.Int.Set.t</a>;</span></code><div class="def-doc"><span class="comment-delim">(*</span><p>Number of tag block cases</p><span class="comment-delim">*)</span></div></li><li id="type-switch.blocks" class="def record field anchored"><a href="#type-switch.blocks" class="anchor"></a><code><span>blocks : <span><span>(int * <a href="#type-t">t</a>)</span> list</span>;</span></code><div class="def-doc"><span class="comment-delim">(*</span><p>Tag block cases</p><span class="comment-delim">*)</span></div></li><li id="type-switch.failaction" class="def record field anchored"><a href="#type-switch.failaction" class="anchor"></a><code><span>failaction : <span><a href="#type-t">t</a> option</span>;</span></code><div class="def-doc"><span class="comment-delim">(*</span><p>Action to take if none matched</p><span class="comment-delim">*)</span></div></li></ol><code><span>}</span></code></div><div class="spec-doc"><p>Equivalent to the similar type in <code>Lambda</code>.</p></div></div><div class="odoc-spec"><div class="spec type anchored" id="type-for_loop"><a href="#type-for_loop" class="anchor"></a><code><span><span class="keyword">and</span> for_loop</span><span> = </span><span>{</span></code><ol><li id="type-for_loop.bound_var" class="def record field anchored"><a href="#type-for_loop.bound_var" class="anchor"></a><code><span>bound_var : <a href="../Variable/index.html#type-t">Variable.t</a>;</span></code></li><li id="type-for_loop.from_value" class="def record field anchored"><a href="#type-for_loop.from_value" class="anchor"></a><code><span>from_value : <a href="../Variable/index.html#type-t">Variable.t</a>;</span></code></li><li id="type-for_loop.to_value" class="def record field anchored"><a href="#type-for_loop.to_value" class="anchor"></a><code><span>to_value : <a href="../Variable/index.html#type-t">Variable.t</a>;</span></code></li><li id="type-for_loop.direction" class="def record field anchored"><a href="#type-for_loop.direction" class="anchor"></a><code><span>direction : <a href="../Asttypes/index.html#type-direction_flag">Asttypes.direction_flag</a>;</span></code></li><li id="type-for_loop.body" class="def record field anchored"><a href="#type-for_loop.body" class="anchor"></a><code><span>body : <a href="#type-t">t</a>;</span></code></li></ol><code><span>}</span></code></div><div class="spec-doc"><p>Equivalent to the similar type in <code>Lambda</code>.</p></div></div><div class="odoc-spec"><div class="spec type anchored" id="type-constant_defining_value"><a href="#type-constant_defining_value" class="anchor"></a><code><span><span class="keyword">and</span> constant_defining_value</span><span> = </span></code><ol><li id="type-constant_defining_value.Allocated_const" class="def variant constructor anchored"><a href="#type-constant_defining_value.Allocated_const" class="anchor"></a><code><span>| </span><span><span class="constructor">Allocated_const</span> <span class="keyword">of</span> <a href="../Allocated_const/index.html#type-t">Allocated_const.t</a></span></code><div class="def-doc"><span class="comment-delim">(*</span><p>A single constant. These are never &quot;simple constants&quot; (type <code>const</code>) but instead more complicated constructions.</p><span class="comment-delim">*)</span></div></li><li id="type-constant_defining_value.Block" class="def variant constructor anchored"><a href="#type-constant_defining_value.Block" class="anchor"></a><code><span>| </span><span><span class="constructor">Block</span> <span class="keyword">of</span> <a href="../Tag/index.html#type-t">Tag.t</a> * <span><a href="#type-constant_defining_value_block_field">constant_defining_value_block_field</a> list</span></span></code><div class="def-doc"><span class="comment-delim">(*</span><p>A pre-allocated block full of constants (either simple constants or references to other constants, see below).</p><span class="comment-delim">*)</span></div></li><li id="type-constant_defining_value.Set_of_closures" class="def variant constructor anchored"><a href="#type-constant_defining_value.Set_of_closures" class="anchor"></a><code><span>| </span><span><span class="constructor">Set_of_closures</span> <span class="keyword">of</span> <a href="#type-set_of_closures">set_of_closures</a></span></code><div class="def-doc"><span class="comment-delim">(*</span><p>A closed (and thus constant) set of closures. (That is to say, <code>free_vars</code> must be empty.)</p><span class="comment-delim">*)</span></div></li><li id="type-constant_defining_value.Project_closure" class="def variant constructor anchored"><a href="#type-constant_defining_value.Project_closure" class="anchor"></a><code><span>| </span><span><span class="constructor">Project_closure</span> <span class="keyword">of</span> <a href="../Symbol/index.html#type-t">Symbol.t</a> * <a href="../Closure_id/index.html#type-t">Closure_id.t</a></span></code><div class="def-doc"><span class="comment-delim">(*</span><p>Selection of one closure from a constant set of closures. Analogous to the equivalent operation on expressions.</p><span class="comment-delim">*)</span></div></li></ol></div><div class="spec-doc"><p>Like a subset of <code>Flambda.named</code>, except that instead of <code>Variable.t</code>s we have <code>Symbol.t</code>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).</p></div></div><div class="odoc-spec"><div class="spec type anchored" id="type-constant_defining_value_block_field"><a href="#type-constant_defining_value_block_field" class="anchor"></a><code><span><span class="keyword">and</span> constant_defining_value_block_field</span><span> = </span></code><ol><li id="type-constant_defining_value_block_field.Symbol" class="def variant constructor anchored"><a href="#type-constant_defining_value_block_field.Symbol" class="anchor"></a><code><span>| </span><span><span class="constructor">Symbol</span> <span class="keyword">of</span> <a href="../Symbol/index.html#type-t">Symbol.t</a></span></code></li><li id="type-constant_defining_value_block_field.Const" class="def variant constructor anchored"><a href="#type-constant_defining_value_block_field.Const" class="anchor"></a><code><span>| </span><span><span class="constructor">Const</span> <span class="keyword">of</span> <a href="#type-const">const</a></span></code></li></ol></div></div><div class="odoc-spec"><div class="spec module anchored" id="module-Constant_defining_value"><a href="#module-Constant_defining_value" class="anchor"></a><code><span><span class="keyword">module</span> <a href="Constant_defining_value/index.html">Constant_defining_value</a></span><span> :
<a href="../Identifiable/module-type-S/index.html">Identifiable.S</a> <span class="keyword">with</span> <span><span class="keyword">type</span> <a href="../Identifiable/module-type-S/index.html#type-t">t</a> = <a href="#type-constant_defining_value">constant_defining_value</a></span></span></code></div></div><div class="odoc-spec"><div class="spec type anchored" id="type-expr"><a href="#type-expr" class="anchor"></a><code><span><span class="keyword">type</span> expr</span><span> = <a href="#type-t">t</a></span></code></div></div><div class="odoc-spec"><div class="spec type anchored" id="type-program_body"><a href="#type-program_body" class="anchor"></a><code><span><span class="keyword">type</span> program_body</span><span> = </span></code><ol><li id="type-program_body.Let_symbol" class="def variant constructor anchored"><a href="#type-program_body.Let_symbol" class="anchor"></a><code><span>| </span><span><span class="constructor">Let_symbol</span> <span class="keyword">of</span> <a href="../Symbol/index.html#type-t">Symbol.t</a> * <a href="#type-constant_defining_value">constant_defining_value</a> * <a href="#type-program_body">program_body</a></span></code><div class="def-doc"><span class="comment-delim">(*</span><p>Define the given symbol to have the given constant value.</p><span class="comment-delim">*)</span></div></li><li id="type-program_body.Let_rec_symbol" class="def variant constructor anchored"><a href="#type-program_body.Let_rec_symbol" class="anchor"></a><code><span>| </span><span><span class="constructor">Let_rec_symbol</span> <span class="keyword">of</span> <span><span>(<a href="../Symbol/index.html#type-t">Symbol.t</a> * <a href="#type-constant_defining_value">constant_defining_value</a>)</span> list</span> * <a href="#type-program_body">program_body</a></span></code><div class="def-doc"><span class="comment-delim">(*</span><p>As for <code>Let_symbol</code>, but recursive. This is needed to treat examples like this, where a constant set of closures is lifted to toplevel:</p><p>let rec f x = f x</p><p>After lifting this produces (in pseudo-Flambda):</p><p>Let_rec_symbol set_of_closures_symbol = (Set_of_closures <code> f x -&gt;
let applied_function = Symbol f_closure in
Apply (applied_function, x) </code>) and f_closure = Project_closure (set_of_closures_symbol, f)</p><p>Use of <code>Let_rec_symbol</code>, by virtue of the special handling in <code>Inline_and_simplify.define_let_rec_symbol_approx</code>, enables the approximation of the set of closures to be present in order to correctly simplify the <code>Project_closure</code> construction. (See <code>Inline_and_simplify.simplify_project_closure</code> for that part.)</p><span class="comment-delim">*)</span></div></li><li id="type-program_body.Initialize_symbol" class="def variant constructor anchored"><a href="#type-program_body.Initialize_symbol" class="anchor"></a><code><span>| </span><span><span class="constructor">Initialize_symbol</span> <span class="keyword">of</span> <a href="../Symbol/index.html#type-t">Symbol.t</a> * <a href="../Tag/index.html#type-t">Tag.t</a> * <span><a href="#type-t">t</a> list</span> * <a href="#type-program_body">program_body</a></span></code><div class="def-doc"><span class="comment-delim">(*</span><p>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).</p><span class="comment-delim">*)</span></div></li><li id="type-program_body.Effect" class="def variant constructor anchored"><a href="#type-program_body.Effect" class="anchor"></a><code><span>| </span><span><span class="constructor">Effect</span> <span class="keyword">of</span> <a href="#type-t">t</a> * <a href="#type-program_body">program_body</a></span></code><div class="def-doc"><span class="comment-delim">(*</span><p>Cause the given expression, which may have a side effect, to be executed. The resulting value is discarded. <code>Effect</code> constructions are never re-ordered.</p><span class="comment-delim">*)</span></div></li><li id="type-program_body.End" class="def variant constructor anchored"><a href="#type-program_body.End" class="anchor"></a><code><span>| </span><span><span class="constructor">End</span> <span class="keyword">of</span> <a href="../Symbol/index.html#type-t">Symbol.t</a></span></code><div class="def-doc"><span class="comment-delim">(*</span><p><code>End</code> accepts the root symbol: the only symbol that can never be eliminated.</p><span class="comment-delim">*)</span></div></li></ol></div><div class="spec-doc"><p>A &quot;program&quot; 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.</p></div></div><div class="odoc-spec"><div class="spec type anchored" id="type-program"><a href="#type-program" class="anchor"></a><code><span><span class="keyword">type</span> program</span><span> = </span><span>{</span></code><ol><li id="type-program.imported_symbols" class="def record field anchored"><a href="#type-program.imported_symbols" class="anchor"></a><code><span>imported_symbols : <a href="../Symbol/Set/index.html#type-t">Symbol.Set.t</a>;</span></code></li><li id="type-program.program_body" class="def record field anchored"><a href="#type-program.program_body" class="anchor"></a><code><span>program_body : <a href="#type-program_body">program_body</a>;</span></code></li></ol><code><span>}</span></code></div></div><div class="odoc-spec"><div class="spec value anchored" id="val-free_variables"><a href="#val-free_variables" class="anchor"></a><code><span><span class="keyword">val</span> free_variables :
<span>?ignore_uses_as_callee:unit <span class="arrow">&#45;&gt;</span></span>
<span>?ignore_uses_as_argument:unit <span class="arrow">&#45;&gt;</span></span>
<span>?ignore_uses_in_project_var:unit <span class="arrow">&#45;&gt;</span></span>
<span><a href="#type-t">t</a> <span class="arrow">&#45;&gt;</span></span>
<a href="../Variable/Set/index.html#type-t">Variable.Set.t</a></span></code></div><div class="spec-doc"><p>Compute the free variables of a term. (This is O(1) for <code>Let</code>s). If <code>ignore_uses_as_callee</code>, all free variables inside <code>Apply</code> expressions are ignored. Likewise <code>ignore_uses_in_project_var</code> for <code>Project_var</code> expressions.</p></div></div><div class="odoc-spec"><div class="spec value anchored" id="val-free_variables_named"><a href="#val-free_variables_named" class="anchor"></a><code><span><span class="keyword">val</span> free_variables_named :
<span>?ignore_uses_in_project_var:unit <span class="arrow">&#45;&gt;</span></span>
<span><a href="#type-named">named</a> <span class="arrow">&#45;&gt;</span></span>
<a href="../Variable/Set/index.html#type-t">Variable.Set.t</a></span></code></div><div class="spec-doc"><p>Compute the free variables of a named expression.</p></div></div><div class="odoc-spec"><div class="spec value anchored" id="val-used_variables"><a href="#val-used_variables" class="anchor"></a><code><span><span class="keyword">val</span> used_variables :
<span>?ignore_uses_as_callee:unit <span class="arrow">&#45;&gt;</span></span>
<span>?ignore_uses_as_argument:unit <span class="arrow">&#45;&gt;</span></span>
<span>?ignore_uses_in_project_var:unit <span class="arrow">&#45;&gt;</span></span>
<span><a href="#type-t">t</a> <span class="arrow">&#45;&gt;</span></span>
<a href="../Variable/Set/index.html#type-t">Variable.Set.t</a></span></code></div><div class="spec-doc"><p>Compute _all_ variables occurring inside an expression.</p></div></div><div class="odoc-spec"><div class="spec value anchored" id="val-used_variables_named"><a href="#val-used_variables_named" class="anchor"></a><code><span><span class="keyword">val</span> used_variables_named :
<span>?ignore_uses_in_project_var:unit <span class="arrow">&#45;&gt;</span></span>
<span><a href="#type-named">named</a> <span class="arrow">&#45;&gt;</span></span>
<a href="../Variable/Set/index.html#type-t">Variable.Set.t</a></span></code></div><div class="spec-doc"><p>Compute _all_ variables occurring inside a named expression.</p></div></div><div class="odoc-spec"><div class="spec value anchored" id="val-free_symbols"><a href="#val-free_symbols" class="anchor"></a><code><span><span class="keyword">val</span> free_symbols : <span><a href="#type-expr">expr</a> <span class="arrow">&#45;&gt;</span></span> <a href="../Symbol/Set/index.html#type-t">Symbol.Set.t</a></span></code></div></div><div class="odoc-spec"><div class="spec value anchored" id="val-free_symbols_named"><a href="#val-free_symbols_named" class="anchor"></a><code><span><span class="keyword">val</span> free_symbols_named : <span><a href="#type-named">named</a> <span class="arrow">&#45;&gt;</span></span> <a href="../Symbol/Set/index.html#type-t">Symbol.Set.t</a></span></code></div></div><div class="odoc-spec"><div class="spec value anchored" id="val-free_symbols_program"><a href="#val-free_symbols_program" class="anchor"></a><code><span><span class="keyword">val</span> free_symbols_program : <span><a href="#type-program">program</a> <span class="arrow">&#45;&gt;</span></span> <a href="../Symbol/Set/index.html#type-t">Symbol.Set.t</a></span></code></div></div><div class="odoc-spec"><div class="spec value anchored" id="val-fold_lets_option"><a href="#val-fold_lets_option" class="anchor"></a><code><span><span class="keyword">val</span> fold_lets_option :
<span><a href="#type-t">t</a> <span class="arrow">&#45;&gt;</span></span>
<span>init:<span class="type-var">'a</span> <span class="arrow">&#45;&gt;</span></span>
<span>for_defining_expr:<span>(<span><span class="type-var">'a</span> <span class="arrow">&#45;&gt;</span></span> <span><a href="../Variable/index.html#type-t">Variable.t</a> <span class="arrow">&#45;&gt;</span></span> <span><a href="#type-named">named</a> <span class="arrow">&#45;&gt;</span></span> <span class="type-var">'a</span> * <a href="../Variable/index.html#type-t">Variable.t</a> * <a href="#type-named">named</a>)</span> <span class="arrow">&#45;&gt;</span></span>
<span>for_last_body:<span>(<span><span class="type-var">'a</span> <span class="arrow">&#45;&gt;</span></span> <span><a href="#type-t">t</a> <span class="arrow">&#45;&gt;</span></span> <a href="#type-t">t</a> * <span class="type-var">'b</span>)</span> <span class="arrow">&#45;&gt;</span></span>
<span>filter_defining_expr:
<span>(<span><span class="type-var">'b</span> <span class="arrow">&#45;&gt;</span></span>
<span><a href="../Variable/index.html#type-t">Variable.t</a> <span class="arrow">&#45;&gt;</span></span>
<span><a href="#type-named">named</a> <span class="arrow">&#45;&gt;</span></span>
<span><a href="../Variable/Set/index.html#type-t">Variable.Set.t</a> <span class="arrow">&#45;&gt;</span></span>
<span class="type-var">'b</span> * <a href="../Variable/index.html#type-t">Variable.t</a> * <span><a href="#type-named">named</a> option</span>)</span> <span class="arrow">&#45;&gt;</span></span>
<a href="#type-t">t</a> * <span class="type-var">'b</span></span></code></div><div class="spec-doc"><p>Used to avoid exceeding the stack limit when handling expressions with multiple consecutive nested <code>Let</code>-expressions. This saves rewriting large simplification functions in CPS. This function provides for the rewriting or elimination of expressions during the fold.</p></div></div><div class="odoc-spec"><div class="spec value anchored" id="val-map_lets"><a href="#val-map_lets" class="anchor"></a><code><span><span class="keyword">val</span> map_lets :
<span><a href="#type-t">t</a> <span class="arrow">&#45;&gt;</span></span>
<span>for_defining_expr:<span>(<span><a href="../Variable/index.html#type-t">Variable.t</a> <span class="arrow">&#45;&gt;</span></span> <span><a href="#type-named">named</a> <span class="arrow">&#45;&gt;</span></span> <a href="#type-named">named</a>)</span> <span class="arrow">&#45;&gt;</span></span>
<span>for_last_body:<span>(<span><a href="#type-t">t</a> <span class="arrow">&#45;&gt;</span></span> <a href="#type-t">t</a>)</span> <span class="arrow">&#45;&gt;</span></span>
<span>after_rebuild:<span>(<span><a href="#type-t">t</a> <span class="arrow">&#45;&gt;</span></span> <a href="#type-t">t</a>)</span> <span class="arrow">&#45;&gt;</span></span>
<a href="#type-t">t</a></span></code></div><div class="spec-doc"><p>Like <code>fold_lets_option</code>, but just a map.</p></div></div><div class="odoc-spec"><div class="spec value anchored" id="val-iter_lets"><a href="#val-iter_lets" class="anchor"></a><code><span><span class="keyword">val</span> iter_lets :
<span><a href="#type-t">t</a> <span class="arrow">&#45;&gt;</span></span>
<span>for_defining_expr:<span>(<span><a href="../Variable/index.html#type-t">Variable.t</a> <span class="arrow">&#45;&gt;</span></span> <span><a href="#type-named">named</a> <span class="arrow">&#45;&gt;</span></span> unit)</span> <span class="arrow">&#45;&gt;</span></span>
<span>for_last_body:<span>(<span><a href="#type-t">t</a> <span class="arrow">&#45;&gt;</span></span> unit)</span> <span class="arrow">&#45;&gt;</span></span>
<span>for_each_let:<span>(<span><a href="#type-t">t</a> <span class="arrow">&#45;&gt;</span></span> unit)</span> <span class="arrow">&#45;&gt;</span></span>
unit</span></code></div><div class="spec-doc"><p>Like <code>map_lets</code>, but just an iterator.</p></div></div><div class="odoc-spec"><div class="spec value anchored" id="val-create_let"><a href="#val-create_let" class="anchor"></a><code><span><span class="keyword">val</span> create_let : <span><a href="../Variable/index.html#type-t">Variable.t</a> <span class="arrow">&#45;&gt;</span></span> <span><a href="#type-named">named</a> <span class="arrow">&#45;&gt;</span></span> <span><a href="#type-t">t</a> <span class="arrow">&#45;&gt;</span></span> <a href="#type-t">t</a></span></code></div><div class="spec-doc"><p>Creates a <code>Let</code> expression. (This computes the free variables of the defining expression and the body.)</p></div></div><div class="odoc-spec"><div class="spec value anchored" id="val-map_defining_expr_of_let"><a href="#val-map_defining_expr_of_let" class="anchor"></a><code><span><span class="keyword">val</span> map_defining_expr_of_let : <span><a href="#type-let_expr">let_expr</a> <span class="arrow">&#45;&gt;</span></span> <span>f:<span>(<span><a href="#type-named">named</a> <span class="arrow">&#45;&gt;</span></span> <a href="#type-named">named</a>)</span> <span class="arrow">&#45;&gt;</span></span> <a href="#type-t">t</a></span></code></div><div class="spec-doc"><p>Apply the specified function <code>f</code> to the defining expression of the given <code>Let</code>-expression, returning a new <code>Let</code>.</p></div></div><div class="odoc-spec"><div class="spec module anchored" id="module-With_free_variables"><a href="#module-With_free_variables" class="anchor"></a><code><span><span class="keyword">module</span> <a href="With_free_variables/index.html">With_free_variables</a></span><span> : <span class="keyword">sig</span> ... <span class="keyword">end</span></span></code></div><div class="spec-doc"><p>A module for the manipulation of terms where the recomputation of free variable sets is to be kept to a minimum.</p></div></div><div class="odoc-spec"><div class="spec value anchored" id="val-create_function_declaration"><a href="#val-create_function_declaration" class="anchor"></a><code><span><span class="keyword">val</span> create_function_declaration :
<span>params:<span><a href="../Parameter/index.html#type-t">Parameter.t</a> list</span> <span class="arrow">&#45;&gt;</span></span>
<span>body:<a href="#type-t">t</a> <span class="arrow">&#45;&gt;</span></span>
<span>stub:bool <span class="arrow">&#45;&gt;</span></span>
<span>dbg:<a href="../Debuginfo/index.html#type-t">Debuginfo.t</a> <span class="arrow">&#45;&gt;</span></span>
<span>inline:<a href="../Lambda/index.html#type-inline_attribute">Lambda.inline_attribute</a> <span class="arrow">&#45;&gt;</span></span>
<span>specialise:<a href="../Lambda/index.html#type-specialise_attribute">Lambda.specialise_attribute</a> <span class="arrow">&#45;&gt;</span></span>
<span>is_a_functor:bool <span class="arrow">&#45;&gt;</span></span>
<span>closure_origin:<a href="../Closure_origin/index.html#type-t">Closure_origin.t</a> <span class="arrow">&#45;&gt;</span></span>
<span>poll:<a href="../Lambda/index.html#type-poll_attribute">Lambda.poll_attribute</a> <span class="arrow">&#45;&gt;</span></span>
<a href="#type-function_declaration">function_declaration</a></span></code></div><div class="spec-doc"><p>Create a function declaration. This calculates the free variables and symbols occurring in the specified <code>body</code>.</p></div></div><div class="odoc-spec"><div class="spec value anchored" id="val-update_function_declaration"><a href="#val-update_function_declaration" class="anchor"></a><code><span><span class="keyword">val</span> update_function_declaration :
<span><a href="#type-function_declaration">function_declaration</a> <span class="arrow">&#45;&gt;</span></span>
<span>params:<span><a href="../Parameter/index.html#type-t">Parameter.t</a> list</span> <span class="arrow">&#45;&gt;</span></span>
<span>body:<a href="#type-t">t</a> <span class="arrow">&#45;&gt;</span></span>
<a href="#type-function_declaration">function_declaration</a></span></code></div><div class="spec-doc"><p>Create a function declaration based on another function declaration</p></div></div><div class="odoc-spec"><div class="spec value anchored" id="val-create_function_declarations"><a href="#val-create_function_declarations" class="anchor"></a><code><span><span class="keyword">val</span> create_function_declarations :
<span>is_classic_mode:bool <span class="arrow">&#45;&gt;</span></span>
<span>funs:<span><a href="#type-function_declaration">function_declaration</a> <a href="../Variable/Map/index.html#type-t">Variable.Map.t</a></span> <span class="arrow">&#45;&gt;</span></span>
<a href="#type-function_declarations">function_declarations</a></span></code></div><div class="spec-doc"><p>Create a set of function declarations given the individual declarations.</p></div></div><div class="odoc-spec"><div class="spec value anchored" id="val-create_function_declarations_with_origin"><a href="#val-create_function_declarations_with_origin" class="anchor"></a><code><span><span class="keyword">val</span> create_function_declarations_with_origin :
<span>is_classic_mode:bool <span class="arrow">&#45;&gt;</span></span>
<span>funs:<span><a href="#type-function_declaration">function_declaration</a> <a href="../Variable/Map/index.html#type-t">Variable.Map.t</a></span> <span class="arrow">&#45;&gt;</span></span>
<span>set_of_closures_origin:<a href="../Set_of_closures_origin/index.html#type-t">Set_of_closures_origin.t</a> <span class="arrow">&#45;&gt;</span></span>
<a href="#type-function_declarations">function_declarations</a></span></code></div><div class="spec-doc"><p>Create a set of function declarations with a given set of closures origin.</p></div></div><div class="odoc-spec"><div class="spec value anchored" id="val-update_body_of_function_declaration"><a href="#val-update_body_of_function_declaration" class="anchor"></a><code><span><span class="keyword">val</span> update_body_of_function_declaration :
<span><a href="#type-function_declaration">function_declaration</a> <span class="arrow">&#45;&gt;</span></span>
<span>body:<a href="#type-expr">expr</a> <span class="arrow">&#45;&gt;</span></span>
<a href="#type-function_declaration">function_declaration</a></span></code></div><div class="spec-doc"><p>Change only the code of a function declaration.</p></div></div><div class="odoc-spec"><div class="spec value anchored" id="val-update_function_decl's_params_and_body"><a href="#val-update_function_decl's_params_and_body" class="anchor"></a><code><span><span class="keyword">val</span> update_function_decl's_params_and_body :
<span><a href="#type-function_declaration">function_declaration</a> <span class="arrow">&#45;&gt;</span></span>
<span>params:<span><a href="../Parameter/index.html#type-t">Parameter.t</a> list</span> <span class="arrow">&#45;&gt;</span></span>
<span>body:<a href="#type-expr">expr</a> <span class="arrow">&#45;&gt;</span></span>
<a href="#type-function_declaration">function_declaration</a></span></code></div><div class="spec-doc"><p>Change only the code and parameters of a function declaration.</p></div></div><div class="odoc-spec"><div class="spec value anchored" id="val-update_function_declarations"><a href="#val-update_function_declarations" class="anchor"></a><code><span><span class="keyword">val</span> update_function_declarations :
<span><a href="#type-function_declarations">function_declarations</a> <span class="arrow">&#45;&gt;</span></span>
<span>funs:<span><a href="#type-function_declaration">function_declaration</a> <a href="../Variable/Map/index.html#type-t">Variable.Map.t</a></span> <span class="arrow">&#45;&gt;</span></span>
<a href="#type-function_declarations">function_declarations</a></span></code></div><div class="spec-doc"><p>Create a set of function declarations based on another set of function declarations.</p></div></div><div class="odoc-spec"><div class="spec value anchored" id="val-create_function_declarations_with_closures_origin"><a href="#val-create_function_declarations_with_closures_origin" class="anchor"></a><code><span><span class="keyword">val</span> create_function_declarations_with_closures_origin :
<span>is_classic_mode:bool <span class="arrow">&#45;&gt;</span></span>
<span>funs:<span><a href="#type-function_declaration">function_declaration</a> <a href="../Variable/Map/index.html#type-t">Variable.Map.t</a></span> <span class="arrow">&#45;&gt;</span></span>
<span>set_of_closures_origin:<a href="../Set_of_closures_origin/index.html#type-t">Set_of_closures_origin.t</a> <span class="arrow">&#45;&gt;</span></span>
<a href="#type-function_declarations">function_declarations</a></span></code></div></div><div class="odoc-spec"><div class="spec value anchored" id="val-import_function_declarations_for_pack"><a href="#val-import_function_declarations_for_pack" class="anchor"></a><code><span><span class="keyword">val</span> import_function_declarations_for_pack :
<span><a href="#type-function_declarations">function_declarations</a> <span class="arrow">&#45;&gt;</span></span>
<span><span>(<span><a href="../Set_of_closures_id/index.html#type-t">Set_of_closures_id.t</a> <span class="arrow">&#45;&gt;</span></span> <a href="../Set_of_closures_id/index.html#type-t">Set_of_closures_id.t</a>)</span> <span class="arrow">&#45;&gt;</span></span>
<span><span>(<span><a href="../Set_of_closures_origin/index.html#type-t">Set_of_closures_origin.t</a> <span class="arrow">&#45;&gt;</span></span> <a href="../Set_of_closures_origin/index.html#type-t">Set_of_closures_origin.t</a>)</span> <span class="arrow">&#45;&gt;</span></span>
<a href="#type-function_declarations">function_declarations</a></span></code></div></div><div class="odoc-spec"><div class="spec value anchored" id="val-create_set_of_closures"><a href="#val-create_set_of_closures" class="anchor"></a><code><span><span class="keyword">val</span> create_set_of_closures :
<span>function_decls:<a href="#type-function_declarations">function_declarations</a> <span class="arrow">&#45;&gt;</span></span>
<span>free_vars:<span><a href="#type-specialised_to">specialised_to</a> <a href="../Variable/Map/index.html#type-t">Variable.Map.t</a></span> <span class="arrow">&#45;&gt;</span></span>
<span>specialised_args:<span><a href="#type-specialised_to">specialised_to</a> <a href="../Variable/Map/index.html#type-t">Variable.Map.t</a></span> <span class="arrow">&#45;&gt;</span></span>
<span>direct_call_surrogates:<span><a href="../Variable/index.html#type-t">Variable.t</a> <a href="../Variable/Map/index.html#type-t">Variable.Map.t</a></span> <span class="arrow">&#45;&gt;</span></span>
<a href="#type-set_of_closures">set_of_closures</a></span></code></div><div class="spec-doc"><p>Create a set of closures. Checks are made to ensure that <code>free_vars</code> and <code>specialised_args</code> are reasonable.</p></div></div><div class="odoc-spec"><div class="spec value anchored" id="val-used_params"><a href="#val-used_params" class="anchor"></a><code><span><span class="keyword">val</span> used_params : <span><a href="#type-function_declaration">function_declaration</a> <span class="arrow">&#45;&gt;</span></span> <a href="../Variable/Set/index.html#type-t">Variable.Set.t</a></span></code></div><div class="spec-doc"><p>Given a function declaration, find which of its parameters (if any) are used in the body.</p></div></div><div class="odoc-spec"><div class="spec type anchored" id="type-maybe_named"><a href="#type-maybe_named" class="anchor"></a><code><span><span class="keyword">type</span> maybe_named</span><span> = </span></code><ol><li id="type-maybe_named.Is_expr" class="def variant constructor anchored"><a href="#type-maybe_named.Is_expr" class="anchor"></a><code><span>| </span><span><span class="constructor">Is_expr</span> <span class="keyword">of</span> <a href="#type-t">t</a></span></code></li><li id="type-maybe_named.Is_named" class="def variant constructor anchored"><a href="#type-maybe_named.Is_named" class="anchor"></a><code><span>| </span><span><span class="constructor">Is_named</span> <span class="keyword">of</span> <a href="#type-named">named</a></span></code></li></ol></div></div><div class="odoc-spec"><div class="spec value anchored" id="val-iter_general"><a href="#val-iter_general" class="anchor"></a><code><span><span class="keyword">val</span> iter_general :
<span>toplevel:bool <span class="arrow">&#45;&gt;</span></span>
<span><span>(<span><a href="#type-t">t</a> <span class="arrow">&#45;&gt;</span></span> unit)</span> <span class="arrow">&#45;&gt;</span></span>
<span><span>(<span><a href="#type-named">named</a> <span class="arrow">&#45;&gt;</span></span> unit)</span> <span class="arrow">&#45;&gt;</span></span>
<span><a href="#type-maybe_named">maybe_named</a> <span class="arrow">&#45;&gt;</span></span>
unit</span></code></div><div class="spec-doc"><p>This function is designed for the internal use of <code>Flambda_iterators</code>. See that module for iterators to be used over Flambda terms.</p></div></div><div class="odoc-spec"><div class="spec value anchored" id="val-print"><a href="#val-print" class="anchor"></a><code><span><span class="keyword">val</span> print : <span><a href="../Stdlib/Format/index.html#type-formatter">Stdlib.Format.formatter</a> <span class="arrow">&#45;&gt;</span></span> <span><a href="#type-t">t</a> <span class="arrow">&#45;&gt;</span></span> unit</span></code></div></div><div class="odoc-spec"><div class="spec value anchored" id="val-print_named"><a href="#val-print_named" class="anchor"></a><code><span><span class="keyword">val</span> print_named : <span><a href="../Stdlib/Format/index.html#type-formatter">Stdlib.Format.formatter</a> <span class="arrow">&#45;&gt;</span></span> <span><a href="#type-named">named</a> <span class="arrow">&#45;&gt;</span></span> unit</span></code></div></div><div class="odoc-spec"><div class="spec value anchored" id="val-print_program"><a href="#val-print_program" class="anchor"></a><code><span><span class="keyword">val</span> print_program : <span><a href="../Stdlib/Format/index.html#type-formatter">Stdlib.Format.formatter</a> <span class="arrow">&#45;&gt;</span></span> <span><a href="#type-program">program</a> <span class="arrow">&#45;&gt;</span></span> unit</span></code></div></div><div class="odoc-spec"><div class="spec value anchored" id="val-print_const"><a href="#val-print_const" class="anchor"></a><code><span><span class="keyword">val</span> print_const : <span><a href="../Stdlib/Format/index.html#type-formatter">Stdlib.Format.formatter</a> <span class="arrow">&#45;&gt;</span></span> <span><a href="#type-const">const</a> <span class="arrow">&#45;&gt;</span></span> unit</span></code></div></div><div class="odoc-spec"><div class="spec value anchored" id="val-print_constant_defining_value"><a href="#val-print_constant_defining_value" class="anchor"></a><code><span><span class="keyword">val</span> print_constant_defining_value :
<span><a href="../Stdlib/Format/index.html#type-formatter">Stdlib.Format.formatter</a> <span class="arrow">&#45;&gt;</span></span>
<span><a href="#type-constant_defining_value">constant_defining_value</a> <span class="arrow">&#45;&gt;</span></span>
unit</span></code></div></div><div class="odoc-spec"><div class="spec value anchored" id="val-print_function_declaration"><a href="#val-print_function_declaration" class="anchor"></a><code><span><span class="keyword">val</span> print_function_declaration :
<span><a href="../Stdlib/Format/index.html#type-formatter">Stdlib.Format.formatter</a> <span class="arrow">&#45;&gt;</span></span>
<span><span>(<a href="../Variable/index.html#type-t">Variable.t</a> * <a href="#type-function_declaration">function_declaration</a>)</span> <span class="arrow">&#45;&gt;</span></span>
unit</span></code></div></div><div class="odoc-spec"><div class="spec value anchored" id="val-print_function_declarations"><a href="#val-print_function_declarations" class="anchor"></a><code><span><span class="keyword">val</span> print_function_declarations :
<span><a href="../Stdlib/Format/index.html#type-formatter">Stdlib.Format.formatter</a> <span class="arrow">&#45;&gt;</span></span>
<span><a href="#type-function_declarations">function_declarations</a> <span class="arrow">&#45;&gt;</span></span>
unit</span></code></div></div><div class="odoc-spec"><div class="spec value anchored" id="val-print_project_closure"><a href="#val-print_project_closure" class="anchor"></a><code><span><span class="keyword">val</span> print_project_closure : <span><a href="../Stdlib/Format/index.html#type-formatter">Stdlib.Format.formatter</a> <span class="arrow">&#45;&gt;</span></span> <span><a href="#type-project_closure">project_closure</a> <span class="arrow">&#45;&gt;</span></span> unit</span></code></div></div><div class="odoc-spec"><div class="spec value anchored" id="val-print_move_within_set_of_closures"><a href="#val-print_move_within_set_of_closures" class="anchor"></a><code><span><span class="keyword">val</span> print_move_within_set_of_closures :
<span><a href="../Stdlib/Format/index.html#type-formatter">Stdlib.Format.formatter</a> <span class="arrow">&#45;&gt;</span></span>
<span><a href="#type-move_within_set_of_closures">move_within_set_of_closures</a> <span class="arrow">&#45;&gt;</span></span>
unit</span></code></div></div><div class="odoc-spec"><div class="spec value anchored" id="val-print_project_var"><a href="#val-print_project_var" class="anchor"></a><code><span><span class="keyword">val</span> print_project_var : <span><a href="../Stdlib/Format/index.html#type-formatter">Stdlib.Format.formatter</a> <span class="arrow">&#45;&gt;</span></span> <span><a href="#type-project_var">project_var</a> <span class="arrow">&#45;&gt;</span></span> unit</span></code></div></div><div class="odoc-spec"><div class="spec value anchored" id="val-print_set_of_closures"><a href="#val-print_set_of_closures" class="anchor"></a><code><span><span class="keyword">val</span> print_set_of_closures : <span><a href="../Stdlib/Format/index.html#type-formatter">Stdlib.Format.formatter</a> <span class="arrow">&#45;&gt;</span></span> <span><a href="#type-set_of_closures">set_of_closures</a> <span class="arrow">&#45;&gt;</span></span> unit</span></code></div></div><div class="odoc-spec"><div class="spec value anchored" id="val-print_specialised_to"><a href="#val-print_specialised_to" class="anchor"></a><code><span><span class="keyword">val</span> print_specialised_to : <span><a href="../Stdlib/Format/index.html#type-formatter">Stdlib.Format.formatter</a> <span class="arrow">&#45;&gt;</span></span> <span><a href="#type-specialised_to">specialised_to</a> <span class="arrow">&#45;&gt;</span></span> unit</span></code></div></div><div class="odoc-spec"><div class="spec value anchored" id="val-equal_call_kind"><a href="#val-equal_call_kind" class="anchor"></a><code><span><span class="keyword">val</span> equal_call_kind : <span><a href="#type-call_kind">call_kind</a> <span class="arrow">&#45;&gt;</span></span> <span><a href="#type-call_kind">call_kind</a> <span class="arrow">&#45;&gt;</span></span> bool</span></code></div></div><div class="odoc-spec"><div class="spec value anchored" id="val-equal_specialised_to"><a href="#val-equal_specialised_to" class="anchor"></a><code><span><span class="keyword">val</span> equal_specialised_to : <span><a href="#type-specialised_to">specialised_to</a> <span class="arrow">&#45;&gt;</span></span> <span><a href="#type-specialised_to">specialised_to</a> <span class="arrow">&#45;&gt;</span></span> bool</span></code></div></div><div class="odoc-spec"><div class="spec value anchored" id="val-compare_const"><a href="#val-compare_const" class="anchor"></a><code><span><span class="keyword">val</span> compare_const : <span><a href="#type-const">const</a> <span class="arrow">&#45;&gt;</span></span> <span><a href="#type-const">const</a> <span class="arrow">&#45;&gt;</span></span> int</span></code></div></div><div class="odoc-spec"><div class="spec value anchored" id="val-compare_project_var"><a href="#val-compare_project_var" class="anchor"></a><code><span><span class="keyword">val</span> compare_project_var : <span><a href="#type-project_var">project_var</a> <span class="arrow">&#45;&gt;</span></span> <span><a href="#type-project_var">project_var</a> <span class="arrow">&#45;&gt;</span></span> int</span></code></div></div><div class="odoc-spec"><div class="spec value anchored" id="val-compare_move_within_set_of_closures"><a href="#val-compare_move_within_set_of_closures" class="anchor"></a><code><span><span class="keyword">val</span> compare_move_within_set_of_closures :
<span><a href="#type-move_within_set_of_closures">move_within_set_of_closures</a> <span class="arrow">&#45;&gt;</span></span>
<span><a href="#type-move_within_set_of_closures">move_within_set_of_closures</a> <span class="arrow">&#45;&gt;</span></span>
int</span></code></div></div><div class="odoc-spec"><div class="spec value anchored" id="val-compare_project_closure"><a href="#val-compare_project_closure" class="anchor"></a><code><span><span class="keyword">val</span> compare_project_closure : <span><a href="#type-project_closure">project_closure</a> <span class="arrow">&#45;&gt;</span></span> <span><a href="#type-project_closure">project_closure</a> <span class="arrow">&#45;&gt;</span></span> int</span></code></div></div></div></body></html>