moonpool/dev/ocaml/Simple_value_approx/index.html

83 lines
No EOL
72 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>Simple_value_approx (ocaml.Simple_value_approx)</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; Simple_value_approx</nav><header class="odoc-preamble"><h1>Module <code><span>Simple_value_approx</span></code></h1><p>Simple approximations to the runtime results of computations. This pass is designed for speed rather than accuracy; the performance is important since it is used heavily during inlining.</p></header><div class="odoc-content"><div class="odoc-spec"><div class="spec type anchored" id="type-boxed_int"><a href="#type-boxed_int" class="anchor"></a><code><span><span class="keyword">type</span> <span>'a boxed_int</span></span><span> = </span></code><ol><li id="type-boxed_int.Int32" class="def variant constructor anchored"><a href="#type-boxed_int.Int32" class="anchor"></a><code><span>| </span><span><span class="constructor">Int32</span> : <span>int32 <a href="#type-boxed_int">boxed_int</a></span></span></code></li><li id="type-boxed_int.Int64" class="def variant constructor anchored"><a href="#type-boxed_int.Int64" class="anchor"></a><code><span>| </span><span><span class="constructor">Int64</span> : <span>int64 <a href="#type-boxed_int">boxed_int</a></span></span></code></li><li id="type-boxed_int.Nativeint" class="def variant constructor anchored"><a href="#type-boxed_int.Nativeint" class="anchor"></a><code><span>| </span><span><span class="constructor">Nativeint</span> : <span>nativeint <a href="#type-boxed_int">boxed_int</a></span></span></code></li></ol></div></div><div class="odoc-spec"><div class="spec type anchored" id="type-value_string"><a href="#type-value_string" class="anchor"></a><code><span><span class="keyword">type</span> value_string</span><span> = </span><span>{</span></code><ol><li id="type-value_string.contents" class="def record field anchored"><a href="#type-value_string.contents" class="anchor"></a><code><span>contents : <span>string option</span>;</span></code></li><li id="type-value_string.size" class="def record field anchored"><a href="#type-value_string.size" class="anchor"></a><code><span>size : int;</span></code></li></ol><code><span>}</span></code></div></div><div class="odoc-spec"><div class="spec type anchored" id="type-unresolved_value"><a href="#type-unresolved_value" class="anchor"></a><code><span><span class="keyword">type</span> unresolved_value</span><span> = </span></code><ol><li id="type-unresolved_value.Set_of_closures_id" class="def variant constructor anchored"><a href="#type-unresolved_value.Set_of_closures_id" class="anchor"></a><code><span>| </span><span><span class="constructor">Set_of_closures_id</span> <span class="keyword">of</span> <a href="../Set_of_closures_id/index.html#type-t">Set_of_closures_id.t</a></span></code></li><li id="type-unresolved_value.Symbol" class="def variant constructor anchored"><a href="#type-unresolved_value.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></ol></div></div><div class="odoc-spec"><div class="spec type anchored" id="type-unknown_because_of"><a href="#type-unknown_because_of" class="anchor"></a><code><span><span class="keyword">type</span> unknown_because_of</span><span> = </span></code><ol><li id="type-unknown_because_of.Unresolved_value" class="def variant constructor anchored"><a href="#type-unknown_because_of.Unresolved_value" class="anchor"></a><code><span>| </span><span><span class="constructor">Unresolved_value</span> <span class="keyword">of</span> <a href="#type-unresolved_value">unresolved_value</a></span></code></li><li id="type-unknown_because_of.Other" class="def variant constructor anchored"><a href="#type-unknown_because_of.Other" class="anchor"></a><code><span>| </span><span><span class="constructor">Other</span></span></code></li></ol></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 class="keyword">private</span> </span><span>{</span></code><ol><li id="type-t.descr" class="def record field anchored"><a href="#type-t.descr" class="anchor"></a><code><span>descr : <a href="#type-descr">descr</a>;</span></code></li><li id="type-t.var" class="def record field anchored"><a href="#type-t.var" class="anchor"></a><code><span>var : <span><a href="../Variable/index.html#type-t">Variable.t</a> option</span>;</span></code></li><li id="type-t.symbol" class="def record field anchored"><a href="#type-t.symbol" class="anchor"></a><code><span>symbol : <span><span>(<a href="../Symbol/index.html#type-t">Symbol.t</a> * <span>int option</span>)</span> option</span>;</span></code></li></ol><code><span>}</span></code></div><div class="spec-doc"><p>A value of type <code>t</code> corresponds to an &quot;approximation&quot; of the result of a computation in the program being compiled. That is to say, it represents what knowledge we have about such a result at compile time. The simplification pass exploits this information to partially evaluate computations.</p><p>At a high level, an approximation for a value <code>v</code> has three parts:</p><ul><li>the &quot;description&quot; (for example, &quot;the constant integer 42&quot;);</li><li>an optional variable;</li><li>an optional symbol or symbol field. If the variable (resp. symbol) is present then that variable (resp. symbol) may be used to obtain the value <code>v</code>.</li></ul><p>The exact semantics of the variable and symbol fields follows.</p><p>Approximations are deduced at particular points in an expression tree, but may subsequently be propagated to other locations.</p><p>At the point at which an approximation is built for some value <code>v</code>, we can construct a set of variables (call the set <code>S</code>) that are known to alias the same value <code>v</code>. Each member of <code>S</code> will have the same or a more precise <code>descr</code> field in its approximation relative to the approximation for <code>v</code>. (An increase in precision may currently be introduced for pattern matches.) If <code>S</code> is non-empty then it is guaranteed that there is a unique member of <code>S</code> that was declared in a scope further out (&quot;earlier&quot;) than all other members of <code>S</code>. If such a member exists then it is recorded in the <code>var</code> field. Otherwise <code>var</code> is <code>None</code>.</p><p>Analogous to the construction of the set <code>S</code>, we can construct a set <code>T</code> consisting of all symbols that are known to alias the value whose approximation is being constructed. If <code>T</code> is non-empty then the <code>symbol</code> field is set to some member of <code>T</code>; it does not matter which one. (There is no notion of scope for symbols.)</p><p>Note about mutable blocks:</p><p>Mutable blocks are always represented by <code>Value_unknown</code> or <code>Value_bottom</code>. Any other approximation could leave the door open to a miscompilation. Such bad scenarios are most likely a user using <code>Obj.magic</code> or <code>Obj.set_field</code> in an inappropriate situation. Such a situation might be: <code>let x = (1, 1) in
Obj.set_field (Obj.repr x) 0 (Obj.repr 2);
assert(fst x = 2)</code> The user would probably expect the assertion to be true, but the compiler could in fact propagate the value of <code>x</code> across the <code>Obj.set_field</code>.</p><p>Insisting that mutable blocks have <code>Value_unknown</code> or <code>Value_bottom</code> approximations certainly won't always prevent this kind of error, but should help catch many of them.</p><p>It is possible that there may be some false positives, with correct but unreachable code causing this check to fail. However the likelihood of this seems sufficiently low, especially compared to the advantages gained by performing the check, that we include it.</p><p>An example of a pattern that might trigger a false positive is: <code>type a = { a : int }
type b = { mutable b : int }
type _ t =
| A : a t
| B : b t
let f (type x) (v:x t) (r:x) =
match v with
| A -&gt; r.a
| B -&gt; r.b &lt;- 2; 3
let v =
let r =
ref A in
r := A; (* Some pattern that the compiler can't understand *)
f !r { a = 1 }</code> When inlining <code>f</code>, the B branch is unreachable, yet the compiler cannot prove it and must therefore keep it.</p></div></div><div class="odoc-spec"><div class="spec type anchored" id="type-descr"><a href="#type-descr" class="anchor"></a><code><span><span class="keyword">and</span> descr</span><span> = <span class="keyword">private</span> </span></code><ol><li id="type-descr.Value_block" class="def variant constructor anchored"><a href="#type-descr.Value_block" class="anchor"></a><code><span>| </span><span><span class="constructor">Value_block</span> <span class="keyword">of</span> <a href="../Tag/index.html#type-t">Tag.t</a> * <span><a href="#type-t">t</a> array</span></span></code></li><li id="type-descr.Value_int" class="def variant constructor anchored"><a href="#type-descr.Value_int" class="anchor"></a><code><span>| </span><span><span class="constructor">Value_int</span> <span class="keyword">of</span> int</span></code></li><li id="type-descr.Value_char" class="def variant constructor anchored"><a href="#type-descr.Value_char" class="anchor"></a><code><span>| </span><span><span class="constructor">Value_char</span> <span class="keyword">of</span> char</span></code></li><li id="type-descr.Value_float" class="def variant constructor anchored"><a href="#type-descr.Value_float" class="anchor"></a><code><span>| </span><span><span class="constructor">Value_float</span> <span class="keyword">of</span> <span>float option</span></span></code></li><li id="type-descr.Value_boxed_int" class="def variant constructor anchored"><a href="#type-descr.Value_boxed_int" class="anchor"></a><code><span>| </span><span><span class="constructor">Value_boxed_int</span> : <span><span class="type-var">'a</span> <a href="#type-boxed_int">boxed_int</a></span> * <span class="type-var">'a</span> <span class="arrow">&#45;&gt;</span> <a href="#type-descr">descr</a></span></code></li><li id="type-descr.Value_set_of_closures" class="def variant constructor anchored"><a href="#type-descr.Value_set_of_closures" class="anchor"></a><code><span>| </span><span><span class="constructor">Value_set_of_closures</span> <span class="keyword">of</span> <a href="#type-value_set_of_closures">value_set_of_closures</a></span></code></li><li id="type-descr.Value_closure" class="def variant constructor anchored"><a href="#type-descr.Value_closure" class="anchor"></a><code><span>| </span><span><span class="constructor">Value_closure</span> <span class="keyword">of</span> <a href="#type-value_closure">value_closure</a></span></code></li><li id="type-descr.Value_string" class="def variant constructor anchored"><a href="#type-descr.Value_string" class="anchor"></a><code><span>| </span><span><span class="constructor">Value_string</span> <span class="keyword">of</span> <a href="#type-value_string">value_string</a></span></code></li><li id="type-descr.Value_float_array" class="def variant constructor anchored"><a href="#type-descr.Value_float_array" class="anchor"></a><code><span>| </span><span><span class="constructor">Value_float_array</span> <span class="keyword">of</span> <a href="#type-value_float_array">value_float_array</a></span></code></li><li id="type-descr.Value_unknown" class="def variant constructor anchored"><a href="#type-descr.Value_unknown" class="anchor"></a><code><span>| </span><span><span class="constructor">Value_unknown</span> <span class="keyword">of</span> <a href="#type-unknown_because_of">unknown_because_of</a></span></code></li><li id="type-descr.Value_bottom" class="def variant constructor anchored"><a href="#type-descr.Value_bottom" class="anchor"></a><code><span>| </span><span><span class="constructor">Value_bottom</span></span></code></li><li id="type-descr.Value_extern" class="def variant constructor anchored"><a href="#type-descr.Value_extern" class="anchor"></a><code><span>| </span><span><span class="constructor">Value_extern</span> <span class="keyword">of</span> <a href="../Export_id/index.html#type-t">Export_id.t</a></span></code></li><li id="type-descr.Value_symbol" class="def variant constructor anchored"><a href="#type-descr.Value_symbol" class="anchor"></a><code><span>| </span><span><span class="constructor">Value_symbol</span> <span class="keyword">of</span> <a href="../Symbol/index.html#type-t">Symbol.t</a></span></code></li><li id="type-descr.Value_unresolved" class="def variant constructor anchored"><a href="#type-descr.Value_unresolved" class="anchor"></a><code><span>| </span><span><span class="constructor">Value_unresolved</span> <span class="keyword">of</span> <a href="#type-unresolved_value">unresolved_value</a></span></code></li></ol></div></div><div class="odoc-spec"><div class="spec type anchored" id="type-value_closure"><a href="#type-value_closure" class="anchor"></a><code><span><span class="keyword">and</span> value_closure</span><span> = </span><span>{</span></code><ol><li id="type-value_closure.set_of_closures" class="def record field anchored"><a href="#type-value_closure.set_of_closures" class="anchor"></a><code><span>set_of_closures : <a href="#type-t">t</a>;</span></code></li><li id="type-value_closure.closure_id" class="def record field anchored"><a href="#type-value_closure.closure_id" class="anchor"></a><code><span>closure_id : <a href="../Closure_id/index.html#type-t">Closure_id.t</a>;</span></code></li></ol><code><span>}</span></code></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></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></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></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></li></ol><code><span>}</span></code></div></div><div class="odoc-spec"><div class="spec type anchored" id="type-function_body"><a href="#type-function_body" class="anchor"></a><code><span><span class="keyword">and</span> function_body</span><span> = <span class="keyword">private</span> </span><span>{</span></code><ol><li id="type-function_body.free_variables" class="def record field anchored"><a href="#type-function_body.free_variables" class="anchor"></a><code><span>free_variables : <a href="../Variable/Set/index.html#type-t">Variable.Set.t</a>;</span></code></li><li id="type-function_body.free_symbols" class="def record field anchored"><a href="#type-function_body.free_symbols" class="anchor"></a><code><span>free_symbols : <a href="../Symbol/Set/index.html#type-t">Symbol.Set.t</a>;</span></code></li><li id="type-function_body.stub" class="def record field anchored"><a href="#type-function_body.stub" class="anchor"></a><code><span>stub : bool;</span></code></li><li id="type-function_body.dbg" class="def record field anchored"><a href="#type-function_body.dbg" class="anchor"></a><code><span>dbg : <a href="../Debuginfo/index.html#type-t">Debuginfo.t</a>;</span></code></li><li id="type-function_body.inline" class="def record field anchored"><a href="#type-function_body.inline" class="anchor"></a><code><span>inline : <a href="../Lambda/index.html#type-inline_attribute">Lambda.inline_attribute</a>;</span></code></li><li id="type-function_body.specialise" class="def record field anchored"><a href="#type-function_body.specialise" class="anchor"></a><code><span>specialise : <a href="../Lambda/index.html#type-specialise_attribute">Lambda.specialise_attribute</a>;</span></code></li><li id="type-function_body.is_a_functor" class="def record field anchored"><a href="#type-function_body.is_a_functor" class="anchor"></a><code><span>is_a_functor : bool;</span></code></li><li id="type-function_body.body" class="def record field anchored"><a href="#type-function_body.body" class="anchor"></a><code><span>body : <a href="../Flambda/index.html#type-t">Flambda.t</a>;</span></code></li><li id="type-function_body.poll" class="def record field anchored"><a href="#type-function_body.poll" class="anchor"></a><code><span>poll : <a href="../Lambda/index.html#type-poll_attribute">Lambda.poll_attribute</a>;</span></code></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.function_body" class="def record field anchored"><a href="#type-function_declaration.function_body" class="anchor"></a><code><span>function_body : <span><a href="#type-function_body">function_body</a> option</span>;</span></code></li></ol><code><span>}</span></code></div></div><div class="odoc-spec"><div class="spec type anchored" id="type-value_set_of_closures"><a href="#type-value_set_of_closures" class="anchor"></a><code><span><span class="keyword">and</span> value_set_of_closures</span><span> = <span class="keyword">private</span> </span><span>{</span></code><ol><li id="type-value_set_of_closures.function_decls" class="def record field anchored"><a href="#type-value_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-value_set_of_closures.bound_vars" class="def record field anchored"><a href="#type-value_set_of_closures.bound_vars" class="anchor"></a><code><span>bound_vars : <span><a href="#type-t">t</a> <a href="../Var_within_closure/Map/index.html#type-t">Var_within_closure.Map.t</a></span>;</span></code></li><li id="type-value_set_of_closures.free_vars" class="def record field anchored"><a href="#type-value_set_of_closures.free_vars" class="anchor"></a><code><span>free_vars : <span><a href="../Flambda/index.html#type-specialised_to">Flambda.specialised_to</a> <a href="../Variable/Map/index.html#type-t">Variable.Map.t</a></span>;</span></code></li><li id="type-value_set_of_closures.invariant_params" class="def record field anchored"><a href="#type-value_set_of_closures.invariant_params" class="anchor"></a><code><span>invariant_params : <span><span><a href="../Variable/Set/index.html#type-t">Variable.Set.t</a> <a href="../Variable/Map/index.html#type-t">Variable.Map.t</a></span> <a href="../Stdlib/Lazy/index.html#type-t">Stdlib.Lazy.t</a></span>;</span></code></li><li id="type-value_set_of_closures.recursive" class="def record field anchored"><a href="#type-value_set_of_closures.recursive" class="anchor"></a><code><span>recursive : <span><a href="../Variable/Set/index.html#type-t">Variable.Set.t</a> <a href="../Stdlib/Lazy/index.html#type-t">Stdlib.Lazy.t</a></span>;</span></code></li><li id="type-value_set_of_closures.size" class="def record field anchored"><a href="#type-value_set_of_closures.size" class="anchor"></a><code><span>size : <span><span><span>int option</span> <a href="../Variable/Map/index.html#type-t">Variable.Map.t</a></span> <a href="../Stdlib/Lazy/index.html#type-t">Stdlib.Lazy.t</a></span>;</span></code><div class="def-doc"><span class="comment-delim">(*</span><p>For functions that are very likely to be inlined, the size of the function's body.</p><span class="comment-delim">*)</span></div></li><li id="type-value_set_of_closures.specialised_args" class="def record field anchored"><a href="#type-value_set_of_closures.specialised_args" class="anchor"></a><code><span>specialised_args : <span><a href="../Flambda/index.html#type-specialised_to">Flambda.specialised_to</a> <a href="../Variable/Map/index.html#type-t">Variable.Map.t</a></span>;</span></code></li><li id="type-value_set_of_closures.freshening" class="def record field anchored"><a href="#type-value_set_of_closures.freshening" class="anchor"></a><code><span>freshening : <a href="../Freshening/Project_var/index.html#type-t">Freshening.Project_var.t</a>;</span></code></li><li id="type-value_set_of_closures.direct_call_surrogates" class="def record field anchored"><a href="#type-value_set_of_closures.direct_call_surrogates" class="anchor"></a><code><span>direct_call_surrogates : <span><a href="../Closure_id/index.html#type-t">Closure_id.t</a> <a href="../Closure_id/Map/index.html#type-t">Closure_id.Map.t</a></span>;</span></code></li></ol><code><span>}</span></code></div></div><div class="odoc-spec"><div class="spec type anchored" id="type-value_float_array_contents"><a href="#type-value_float_array_contents" class="anchor"></a><code><span><span class="keyword">and</span> value_float_array_contents</span><span> = </span></code><ol><li id="type-value_float_array_contents.Contents" class="def variant constructor anchored"><a href="#type-value_float_array_contents.Contents" class="anchor"></a><code><span>| </span><span><span class="constructor">Contents</span> <span class="keyword">of</span> <span><a href="#type-t">t</a> array</span></span></code></li><li id="type-value_float_array_contents.Unknown_or_mutable" class="def variant constructor anchored"><a href="#type-value_float_array_contents.Unknown_or_mutable" class="anchor"></a><code><span>| </span><span><span class="constructor">Unknown_or_mutable</span></span></code></li></ol></div></div><div class="odoc-spec"><div class="spec type anchored" id="type-value_float_array"><a href="#type-value_float_array" class="anchor"></a><code><span><span class="keyword">and</span> value_float_array</span><span> = </span><span>{</span></code><ol><li id="type-value_float_array.contents" class="def record field anchored"><a href="#type-value_float_array.contents" class="anchor"></a><code><span>contents : <a href="#type-value_float_array_contents">value_float_array_contents</a>;</span></code></li><li id="type-value_float_array.size" class="def record field anchored"><a href="#type-value_float_array.size" class="anchor"></a><code><span>size : int;</span></code></li></ol><code><span>}</span></code></div></div><div class="odoc-spec"><div class="spec value anchored" id="val-descr"><a href="#val-descr" class="anchor"></a><code><span><span class="keyword">val</span> descr : <span><a href="#type-t">t</a> <span class="arrow">&#45;&gt;</span></span> <a href="#type-descr">descr</a></span></code></div><div class="spec-doc"><p>Extraction of the description of approximation(s).</p></div></div><div class="odoc-spec"><div class="spec value anchored" id="val-descrs"><a href="#val-descrs" class="anchor"></a><code><span><span class="keyword">val</span> descrs : <span><span><a href="#type-t">t</a> list</span> <span class="arrow">&#45;&gt;</span></span> <span><a href="#type-descr">descr</a> list</span></span></code></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 class="spec-doc"><p>Pretty-printing of approximations to a formatter.</p></div></div><div class="odoc-spec"><div class="spec value anchored" id="val-print_descr"><a href="#val-print_descr" class="anchor"></a><code><span><span class="keyword">val</span> print_descr : <span><a href="../Stdlib/Format/index.html#type-formatter">Stdlib.Format.formatter</a> <span class="arrow">&#45;&gt;</span></span> <span><a href="#type-descr">descr</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_value_set_of_closures"><a href="#val-print_value_set_of_closures" class="anchor"></a><code><span><span class="keyword">val</span> print_value_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-value_set_of_closures">value_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_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-function_declarations_approx"><a href="#val-function_declarations_approx" class="anchor"></a><code><span><span class="keyword">val</span> function_declarations_approx :
<span>keep_body:<span>(<span><a href="../Variable/index.html#type-t">Variable.t</a> <span class="arrow">&#45;&gt;</span></span> <span><a href="../Flambda/index.html#type-function_declaration">Flambda.function_declaration</a> <span class="arrow">&#45;&gt;</span></span> bool)</span> <span class="arrow">&#45;&gt;</span></span>
<span><a href="../Flambda/index.html#type-function_declarations">Flambda.function_declarations</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-create_value_set_of_closures"><a href="#val-create_value_set_of_closures" class="anchor"></a><code><span><span class="keyword">val</span> create_value_set_of_closures :
<span>function_decls:<a href="#type-function_declarations">function_declarations</a> <span class="arrow">&#45;&gt;</span></span>
<span>bound_vars:<span><a href="#type-t">t</a> <a href="../Var_within_closure/Map/index.html#type-t">Var_within_closure.Map.t</a></span> <span class="arrow">&#45;&gt;</span></span>
<span>free_vars:<span><a href="../Flambda/index.html#type-specialised_to">Flambda.specialised_to</a> <a href="../Variable/Map/index.html#type-t">Variable.Map.t</a></span> <span class="arrow">&#45;&gt;</span></span>
<span>invariant_params:<span><span><a href="../Variable/Set/index.html#type-t">Variable.Set.t</a> <a href="../Variable/Map/index.html#type-t">Variable.Map.t</a></span> lazy_t</span> <span class="arrow">&#45;&gt;</span></span>
<span>recursive:<span><a href="../Variable/Set/index.html#type-t">Variable.Set.t</a> <a href="../Stdlib/Lazy/index.html#type-t">Stdlib.Lazy.t</a></span> <span class="arrow">&#45;&gt;</span></span>
<span>specialised_args:<span><a href="../Flambda/index.html#type-specialised_to">Flambda.specialised_to</a> <a href="../Variable/Map/index.html#type-t">Variable.Map.t</a></span> <span class="arrow">&#45;&gt;</span></span>
<span>freshening:<a href="../Freshening/Project_var/index.html#type-t">Freshening.Project_var.t</a> <span class="arrow">&#45;&gt;</span></span>
<span>direct_call_surrogates:<span><a href="../Closure_id/index.html#type-t">Closure_id.t</a> <a href="../Closure_id/Map/index.html#type-t">Closure_id.Map.t</a></span> <span class="arrow">&#45;&gt;</span></span>
<a href="#type-value_set_of_closures">value_set_of_closures</a></span></code></div></div><div class="odoc-spec"><div class="spec value anchored" id="val-update_freshening_of_value_set_of_closures"><a href="#val-update_freshening_of_value_set_of_closures" class="anchor"></a><code><span><span class="keyword">val</span> update_freshening_of_value_set_of_closures :
<span><a href="#type-value_set_of_closures">value_set_of_closures</a> <span class="arrow">&#45;&gt;</span></span>
<span>freshening:<a href="../Freshening/Project_var/index.html#type-t">Freshening.Project_var.t</a> <span class="arrow">&#45;&gt;</span></span>
<a href="#type-value_set_of_closures">value_set_of_closures</a></span></code></div></div><div class="odoc-spec"><div class="spec value anchored" id="val-value_unknown"><a href="#val-value_unknown" class="anchor"></a><code><span><span class="keyword">val</span> value_unknown : <span><a href="#type-unknown_because_of">unknown_because_of</a> <span class="arrow">&#45;&gt;</span></span> <a href="#type-t">t</a></span></code></div><div class="spec-doc"><p>Basic construction of approximations.</p></div></div><div class="odoc-spec"><div class="spec value anchored" id="val-value_int"><a href="#val-value_int" class="anchor"></a><code><span><span class="keyword">val</span> value_int : <span>int <span class="arrow">&#45;&gt;</span></span> <a href="#type-t">t</a></span></code></div></div><div class="odoc-spec"><div class="spec value anchored" id="val-value_char"><a href="#val-value_char" class="anchor"></a><code><span><span class="keyword">val</span> value_char : <span>char <span class="arrow">&#45;&gt;</span></span> <a href="#type-t">t</a></span></code></div></div><div class="odoc-spec"><div class="spec value anchored" id="val-value_float"><a href="#val-value_float" class="anchor"></a><code><span><span class="keyword">val</span> value_float : <span>float <span class="arrow">&#45;&gt;</span></span> <a href="#type-t">t</a></span></code></div></div><div class="odoc-spec"><div class="spec value anchored" id="val-value_any_float"><a href="#val-value_any_float" class="anchor"></a><code><span><span class="keyword">val</span> value_any_float : <a href="#type-t">t</a></span></code></div></div><div class="odoc-spec"><div class="spec value anchored" id="val-value_mutable_float_array"><a href="#val-value_mutable_float_array" class="anchor"></a><code><span><span class="keyword">val</span> value_mutable_float_array : <span>size:int <span class="arrow">&#45;&gt;</span></span> <a href="#type-t">t</a></span></code></div></div><div class="odoc-spec"><div class="spec value anchored" id="val-value_immutable_float_array"><a href="#val-value_immutable_float_array" class="anchor"></a><code><span><span class="keyword">val</span> value_immutable_float_array : <span><span><a href="#type-t">t</a> array</span> <span class="arrow">&#45;&gt;</span></span> <a href="#type-t">t</a></span></code></div></div><div class="odoc-spec"><div class="spec value anchored" id="val-value_string"><a href="#val-value_string" class="anchor"></a><code><span><span class="keyword">val</span> value_string : <span>int <span class="arrow">&#45;&gt;</span></span> <span><span>string option</span> <span class="arrow">&#45;&gt;</span></span> <a href="#type-t">t</a></span></code></div></div><div class="odoc-spec"><div class="spec value anchored" id="val-value_boxed_int"><a href="#val-value_boxed_int" class="anchor"></a><code><span><span class="keyword">val</span> value_boxed_int : <span><span><span class="type-var">'i</span> <a href="#type-boxed_int">boxed_int</a></span> <span class="arrow">&#45;&gt;</span></span> <span><span class="type-var">'i</span> <span class="arrow">&#45;&gt;</span></span> <a href="#type-t">t</a></span></code></div></div><div class="odoc-spec"><div class="spec value anchored" id="val-value_block"><a href="#val-value_block" class="anchor"></a><code><span><span class="keyword">val</span> value_block : <span><a href="../Tag/index.html#type-t">Tag.t</a> <span class="arrow">&#45;&gt;</span></span> <span><span><a href="#type-t">t</a> array</span> <span class="arrow">&#45;&gt;</span></span> <a href="#type-t">t</a></span></code></div></div><div class="odoc-spec"><div class="spec value anchored" id="val-value_extern"><a href="#val-value_extern" class="anchor"></a><code><span><span class="keyword">val</span> value_extern : <span><a href="../Export_id/index.html#type-t">Export_id.t</a> <span class="arrow">&#45;&gt;</span></span> <a href="#type-t">t</a></span></code></div></div><div class="odoc-spec"><div class="spec value anchored" id="val-value_symbol"><a href="#val-value_symbol" class="anchor"></a><code><span><span class="keyword">val</span> value_symbol : <span><a href="../Symbol/index.html#type-t">Symbol.t</a> <span class="arrow">&#45;&gt;</span></span> <a href="#type-t">t</a></span></code></div></div><div class="odoc-spec"><div class="spec value anchored" id="val-value_bottom"><a href="#val-value_bottom" class="anchor"></a><code><span><span class="keyword">val</span> value_bottom : <a href="#type-t">t</a></span></code></div></div><div class="odoc-spec"><div class="spec value anchored" id="val-value_unresolved"><a href="#val-value_unresolved" class="anchor"></a><code><span><span class="keyword">val</span> value_unresolved : <span><a href="#type-unresolved_value">unresolved_value</a> <span class="arrow">&#45;&gt;</span></span> <a href="#type-t">t</a></span></code></div></div><div class="odoc-spec"><div class="spec value anchored" id="val-value_closure"><a href="#val-value_closure" class="anchor"></a><code><span><span class="keyword">val</span> value_closure :
<span>?closure_var:<a href="../Variable/index.html#type-t">Variable.t</a> <span class="arrow">&#45;&gt;</span></span>
<span>?set_of_closures_var:<a href="../Variable/index.html#type-t">Variable.t</a> <span class="arrow">&#45;&gt;</span></span>
<span>?set_of_closures_symbol:<a href="../Symbol/index.html#type-t">Symbol.t</a> <span class="arrow">&#45;&gt;</span></span>
<span><a href="#type-value_set_of_closures">value_set_of_closures</a> <span class="arrow">&#45;&gt;</span></span>
<span><a href="../Closure_id/index.html#type-t">Closure_id.t</a> <span class="arrow">&#45;&gt;</span></span>
<a href="#type-t">t</a></span></code></div><div class="spec-doc"><p>Construct a closure approximation given the approximation of the corresponding set of closures and the closure ID of the closure to be projected from such set. <code>closure_var</code> and/or <code>set_of_closures_var</code> may be specified to augment the approximation with variables that may be used to access the closure value itself, so long as they are in scope at the proposed point of use.</p></div></div><div class="odoc-spec"><div class="spec value anchored" id="val-value_set_of_closures"><a href="#val-value_set_of_closures" class="anchor"></a><code><span><span class="keyword">val</span> value_set_of_closures :
<span>?set_of_closures_var:<a href="../Variable/index.html#type-t">Variable.t</a> <span class="arrow">&#45;&gt;</span></span>
<span><a href="#type-value_set_of_closures">value_set_of_closures</a> <span class="arrow">&#45;&gt;</span></span>
<a href="#type-t">t</a></span></code></div><div class="spec-doc"><p>Construct a set of closures approximation. <code>set_of_closures_var</code> is as for the parameter of the same name in <code>value_closure</code>, above.</p></div></div><div class="odoc-spec"><div class="spec value anchored" id="val-make_const_int"><a href="#val-make_const_int" class="anchor"></a><code><span><span class="keyword">val</span> make_const_int : <span>int <span class="arrow">&#45;&gt;</span></span> <a href="../Flambda/index.html#type-t">Flambda.t</a> * <a href="#type-t">t</a></span></code></div><div class="spec-doc"><p>Take the given constant and produce an appropriate approximation for it together with an Flambda expression representing it.</p></div></div><div class="odoc-spec"><div class="spec value anchored" id="val-make_const_char"><a href="#val-make_const_char" class="anchor"></a><code><span><span class="keyword">val</span> make_const_char : <span>char <span class="arrow">&#45;&gt;</span></span> <a href="../Flambda/index.html#type-t">Flambda.t</a> * <a href="#type-t">t</a></span></code></div></div><div class="odoc-spec"><div class="spec value anchored" id="val-make_const_bool"><a href="#val-make_const_bool" class="anchor"></a><code><span><span class="keyword">val</span> make_const_bool : <span>bool <span class="arrow">&#45;&gt;</span></span> <a href="../Flambda/index.html#type-t">Flambda.t</a> * <a href="#type-t">t</a></span></code></div></div><div class="odoc-spec"><div class="spec value anchored" id="val-make_const_float"><a href="#val-make_const_float" class="anchor"></a><code><span><span class="keyword">val</span> make_const_float : <span>float <span class="arrow">&#45;&gt;</span></span> <a href="../Flambda/index.html#type-t">Flambda.t</a> * <a href="#type-t">t</a></span></code></div></div><div class="odoc-spec"><div class="spec value anchored" id="val-make_const_boxed_int"><a href="#val-make_const_boxed_int" class="anchor"></a><code><span><span class="keyword">val</span> make_const_boxed_int : <span><span><span class="type-var">'i</span> <a href="#type-boxed_int">boxed_int</a></span> <span class="arrow">&#45;&gt;</span></span> <span><span class="type-var">'i</span> <span class="arrow">&#45;&gt;</span></span> <a href="../Flambda/index.html#type-t">Flambda.t</a> * <a href="#type-t">t</a></span></code></div></div><div class="odoc-spec"><div class="spec value anchored" id="val-make_const_int_named"><a href="#val-make_const_int_named" class="anchor"></a><code><span><span class="keyword">val</span> make_const_int_named : <span>int <span class="arrow">&#45;&gt;</span></span> <a href="../Flambda/index.html#type-named">Flambda.named</a> * <a href="#type-t">t</a></span></code></div></div><div class="odoc-spec"><div class="spec value anchored" id="val-make_const_char_named"><a href="#val-make_const_char_named" class="anchor"></a><code><span><span class="keyword">val</span> make_const_char_named : <span>char <span class="arrow">&#45;&gt;</span></span> <a href="../Flambda/index.html#type-named">Flambda.named</a> * <a href="#type-t">t</a></span></code></div></div><div class="odoc-spec"><div class="spec value anchored" id="val-make_const_bool_named"><a href="#val-make_const_bool_named" class="anchor"></a><code><span><span class="keyword">val</span> make_const_bool_named : <span>bool <span class="arrow">&#45;&gt;</span></span> <a href="../Flambda/index.html#type-named">Flambda.named</a> * <a href="#type-t">t</a></span></code></div></div><div class="odoc-spec"><div class="spec value anchored" id="val-make_const_float_named"><a href="#val-make_const_float_named" class="anchor"></a><code><span><span class="keyword">val</span> make_const_float_named : <span>float <span class="arrow">&#45;&gt;</span></span> <a href="../Flambda/index.html#type-named">Flambda.named</a> * <a href="#type-t">t</a></span></code></div></div><div class="odoc-spec"><div class="spec value anchored" id="val-make_const_boxed_int_named"><a href="#val-make_const_boxed_int_named" class="anchor"></a><code><span><span class="keyword">val</span> make_const_boxed_int_named : <span><span><span class="type-var">'i</span> <a href="#type-boxed_int">boxed_int</a></span> <span class="arrow">&#45;&gt;</span></span> <span><span class="type-var">'i</span> <span class="arrow">&#45;&gt;</span></span> <a href="../Flambda/index.html#type-named">Flambda.named</a> * <a href="#type-t">t</a></span></code></div></div><div class="odoc-spec"><div class="spec value anchored" id="val-augment_with_variable"><a href="#val-augment_with_variable" class="anchor"></a><code><span><span class="keyword">val</span> augment_with_variable : <span><a href="#type-t">t</a> <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> <a href="#type-t">t</a></span></code></div><div class="spec-doc"><p>Augment an approximation with a given variable (see comment above). If the approximation was already augmented with a variable, the one passed to this function replaces it within the approximation.</p></div></div><div class="odoc-spec"><div class="spec value anchored" id="val-augment_with_symbol"><a href="#val-augment_with_symbol" class="anchor"></a><code><span><span class="keyword">val</span> augment_with_symbol : <span><a href="#type-t">t</a> <span class="arrow">&#45;&gt;</span></span> <span><a href="../Symbol/index.html#type-t">Symbol.t</a> <span class="arrow">&#45;&gt;</span></span> <a href="#type-t">t</a></span></code></div><div class="spec-doc"><p>Like <code>augment_with_variable</code>, but for symbol information.</p></div></div><div class="odoc-spec"><div class="spec value anchored" id="val-augment_with_symbol_field"><a href="#val-augment_with_symbol_field" class="anchor"></a><code><span><span class="keyword">val</span> augment_with_symbol_field : <span><a href="#type-t">t</a> <span class="arrow">&#45;&gt;</span></span> <span><a href="../Symbol/index.html#type-t">Symbol.t</a> <span class="arrow">&#45;&gt;</span></span> <span>int <span class="arrow">&#45;&gt;</span></span> <a href="#type-t">t</a></span></code></div><div class="spec-doc"><p>Like <code>augment_with_symbol</code>, but for symbol field information.</p></div></div><div class="odoc-spec"><div class="spec value anchored" id="val-replace_description"><a href="#val-replace_description" class="anchor"></a><code><span><span class="keyword">val</span> replace_description : <span><a href="#type-t">t</a> <span class="arrow">&#45;&gt;</span></span> <span><a href="#type-descr">descr</a> <span class="arrow">&#45;&gt;</span></span> <a href="#type-t">t</a></span></code></div><div class="spec-doc"><p>Replace the description within an approximation.</p></div></div><div class="odoc-spec"><div class="spec value anchored" id="val-augment_with_kind"><a href="#val-augment_with_kind" class="anchor"></a><code><span><span class="keyword">val</span> augment_with_kind : <span><a href="#type-t">t</a> <span class="arrow">&#45;&gt;</span></span> <span><a href="../Lambda/index.html#type-value_kind">Lambda.value_kind</a> <span class="arrow">&#45;&gt;</span></span> <a href="#type-t">t</a></span></code></div><div class="spec-doc"><p>Improve the description by taking the kind into account</p></div></div><div class="odoc-spec"><div class="spec value anchored" id="val-augment_kind_with_approx"><a href="#val-augment_kind_with_approx" class="anchor"></a><code><span><span class="keyword">val</span> augment_kind_with_approx : <span><a href="#type-t">t</a> <span class="arrow">&#45;&gt;</span></span> <span><a href="../Lambda/index.html#type-value_kind">Lambda.value_kind</a> <span class="arrow">&#45;&gt;</span></span> <a href="../Lambda/index.html#type-value_kind">Lambda.value_kind</a></span></code></div><div class="spec-doc"><p>Improve the kind by taking the description into account</p></div></div><div class="odoc-spec"><div class="spec value anchored" id="val-equal_boxed_int"><a href="#val-equal_boxed_int" class="anchor"></a><code><span><span class="keyword">val</span> equal_boxed_int : <span><span><span class="type-var">'a</span> <a href="#type-boxed_int">boxed_int</a></span> <span class="arrow">&#45;&gt;</span></span> <span><span class="type-var">'a</span> <span class="arrow">&#45;&gt;</span></span> <span><span><span class="type-var">'b</span> <a href="#type-boxed_int">boxed_int</a></span> <span class="arrow">&#45;&gt;</span></span> <span><span class="type-var">'b</span> <span class="arrow">&#45;&gt;</span></span> bool</span></code></div></div><div class="odoc-spec"><div class="spec value anchored" id="val-meet"><a href="#val-meet" class="anchor"></a><code><span><span class="keyword">val</span> meet : <span>really_import_approx:<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><a href="#type-t">t</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><div class="odoc-spec"><div class="spec value anchored" id="val-known"><a href="#val-known" class="anchor"></a><code><span><span class="keyword">val</span> known : <span><a href="#type-t">t</a> <span class="arrow">&#45;&gt;</span></span> bool</span></code></div><div class="spec-doc"><p>An approximation is &quot;known&quot; iff it is not <code>Value_unknown</code>.</p></div></div><div class="odoc-spec"><div class="spec value anchored" id="val-useful"><a href="#val-useful" class="anchor"></a><code><span><span class="keyword">val</span> useful : <span><a href="#type-t">t</a> <span class="arrow">&#45;&gt;</span></span> bool</span></code></div><div class="spec-doc"><p>An approximation is &quot;useful&quot; iff it is neither unknown nor bottom.</p></div></div><div class="odoc-spec"><div class="spec value anchored" id="val-all_not_useful"><a href="#val-all_not_useful" class="anchor"></a><code><span><span class="keyword">val</span> all_not_useful : <span><span><a href="#type-t">t</a> list</span> <span class="arrow">&#45;&gt;</span></span> bool</span></code></div><div class="spec-doc"><p>Whether all approximations in the given list do *not* satisfy <code>useful</code>.</p></div></div><div class="odoc-spec"><div class="spec value anchored" id="val-warn_on_mutation"><a href="#val-warn_on_mutation" class="anchor"></a><code><span><span class="keyword">val</span> warn_on_mutation : <span><a href="#type-t">t</a> <span class="arrow">&#45;&gt;</span></span> bool</span></code></div><div class="spec-doc"><p>Whether to warn on attempts to mutate a value. It must have been resolved (it cannot be <code>Value_extern</code> or <code>Value_symbol</code>). (See comment above for further explanation.)</p></div></div><div class="odoc-spec"><div class="spec type anchored" id="type-simplification_summary"><a href="#type-simplification_summary" class="anchor"></a><code><span><span class="keyword">type</span> simplification_summary</span><span> = </span></code><ol><li id="type-simplification_summary.Nothing_done" class="def variant constructor anchored"><a href="#type-simplification_summary.Nothing_done" class="anchor"></a><code><span>| </span><span><span class="constructor">Nothing_done</span></span></code></li><li id="type-simplification_summary.Replaced_term" class="def variant constructor anchored"><a href="#type-simplification_summary.Replaced_term" class="anchor"></a><code><span>| </span><span><span class="constructor">Replaced_term</span></span></code></li></ol></div></div><div class="odoc-spec"><div class="spec type anchored" id="type-simplification_result"><a href="#type-simplification_result" class="anchor"></a><code><span><span class="keyword">type</span> simplification_result</span><span> = <a href="../Flambda/index.html#type-t">Flambda.t</a> * <a href="#type-simplification_summary">simplification_summary</a> * <a href="#type-t">t</a></span></code></div></div><div class="odoc-spec"><div class="spec type anchored" id="type-simplification_result_named"><a href="#type-simplification_result_named" class="anchor"></a><code><span><span class="keyword">type</span> simplification_result_named</span><span> = <a href="../Flambda/index.html#type-named">Flambda.named</a> * <a href="#type-simplification_summary">simplification_summary</a> * <a href="#type-t">t</a></span></code></div></div><div class="odoc-spec"><div class="spec value anchored" id="val-simplify"><a href="#val-simplify" class="anchor"></a><code><span><span class="keyword">val</span> simplify : <span><a href="#type-t">t</a> <span class="arrow">&#45;&gt;</span></span> <span><a href="../Flambda/index.html#type-t">Flambda.t</a> <span class="arrow">&#45;&gt;</span></span> <a href="#type-simplification_result">simplification_result</a></span></code></div><div class="spec-doc"><p>Given an expression and its approximation, attempt to simplify the expression to a constant (with associated approximation), taking into account whether the expression has any side effects.</p></div></div><div class="odoc-spec"><div class="spec value anchored" id="val-simplify_using_env"><a href="#val-simplify_using_env" class="anchor"></a><code><span><span class="keyword">val</span> simplify_using_env :
<span><a href="#type-t">t</a> <span class="arrow">&#45;&gt;</span></span>
<span>is_present_in_env:<span>(<span><a href="../Variable/index.html#type-t">Variable.t</a> <span class="arrow">&#45;&gt;</span></span> bool)</span> <span class="arrow">&#45;&gt;</span></span>
<span><a href="../Flambda/index.html#type-t">Flambda.t</a> <span class="arrow">&#45;&gt;</span></span>
<a href="#type-simplification_result">simplification_result</a></span></code></div><div class="spec-doc"><p>As for <code>simplify</code>, but also enables us to simplify based on equalities between variables. The caller must provide a function that tells us whether, if we simplify to a given variable, the value of that variable will be accessible in the current environment.</p></div></div><div class="odoc-spec"><div class="spec value anchored" id="val-simplify_named"><a href="#val-simplify_named" class="anchor"></a><code><span><span class="keyword">val</span> simplify_named : <span><a href="#type-t">t</a> <span class="arrow">&#45;&gt;</span></span> <span><a href="../Flambda/index.html#type-named">Flambda.named</a> <span class="arrow">&#45;&gt;</span></span> <a href="#type-simplification_result_named">simplification_result_named</a></span></code></div></div><div class="odoc-spec"><div class="spec value anchored" id="val-simplify_named_using_env"><a href="#val-simplify_named_using_env" class="anchor"></a><code><span><span class="keyword">val</span> simplify_named_using_env :
<span><a href="#type-t">t</a> <span class="arrow">&#45;&gt;</span></span>
<span>is_present_in_env:<span>(<span><a href="../Variable/index.html#type-t">Variable.t</a> <span class="arrow">&#45;&gt;</span></span> bool)</span> <span class="arrow">&#45;&gt;</span></span>
<span><a href="../Flambda/index.html#type-named">Flambda.named</a> <span class="arrow">&#45;&gt;</span></span>
<a href="#type-simplification_result_named">simplification_result_named</a></span></code></div></div><div class="odoc-spec"><div class="spec value anchored" id="val-simplify_var_to_var_using_env"><a href="#val-simplify_var_to_var_using_env" class="anchor"></a><code><span><span class="keyword">val</span> simplify_var_to_var_using_env :
<span><a href="#type-t">t</a> <span class="arrow">&#45;&gt;</span></span>
<span>is_present_in_env:<span>(<span><a href="../Variable/index.html#type-t">Variable.t</a> <span class="arrow">&#45;&gt;</span></span> bool)</span> <span class="arrow">&#45;&gt;</span></span>
<span><a href="../Variable/index.html#type-t">Variable.t</a> option</span></span></code></div><div class="spec-doc"><p>If the given approximation identifies another variable and <code>is_present_in_env</code> deems it to be in scope, return that variable (wrapped in a <code>Some</code>), otherwise return <code>None</code>.</p></div></div><div class="odoc-spec"><div class="spec value anchored" id="val-simplify_var"><a href="#val-simplify_var" class="anchor"></a><code><span><span class="keyword">val</span> simplify_var : <span><a href="#type-t">t</a> <span class="arrow">&#45;&gt;</span></span> <span><span>(<a href="../Flambda/index.html#type-named">Flambda.named</a> * <a href="#type-t">t</a>)</span> option</span></span></code></div></div><div class="odoc-spec"><div class="spec type anchored" id="type-get_field_result"><a href="#type-get_field_result" class="anchor"></a><code><span><span class="keyword">type</span> get_field_result</span><span> = </span></code><ol><li id="type-get_field_result.Ok" class="def variant constructor anchored"><a href="#type-get_field_result.Ok" class="anchor"></a><code><span>| </span><span><span class="constructor">Ok</span> <span class="keyword">of</span> <a href="#type-t">t</a></span></code></li><li id="type-get_field_result.Unreachable" class="def variant constructor anchored"><a href="#type-get_field_result.Unreachable" class="anchor"></a><code><span>| </span><span><span class="constructor">Unreachable</span></span></code></li></ol></div></div><div class="odoc-spec"><div class="spec value anchored" id="val-get_field"><a href="#val-get_field" class="anchor"></a><code><span><span class="keyword">val</span> get_field : <span><a href="#type-t">t</a> <span class="arrow">&#45;&gt;</span></span> <span>field_index:int <span class="arrow">&#45;&gt;</span></span> <a href="#type-get_field_result">get_field_result</a></span></code></div><div class="spec-doc"><p>Given the approximation <code>t</code> of a value, expected to correspond to a block (in the <code>Pmakeblock</code> sense of the word), and a field index then return an appropriate approximation for that field of the block (or <code>Unreachable</code> if the code with the approximation <code>t</code> is unreachable). N.B. Not all cases of unreachable code are returned as <code>Unreachable</code>.</p></div></div><div class="odoc-spec"><div class="spec type anchored" id="type-checked_approx_for_block"><a href="#type-checked_approx_for_block" class="anchor"></a><code><span><span class="keyword">type</span> checked_approx_for_block</span><span> = </span></code><ol><li id="type-checked_approx_for_block.Wrong" class="def variant constructor anchored"><a href="#type-checked_approx_for_block.Wrong" class="anchor"></a><code><span>| </span><span><span class="constructor">Wrong</span></span></code></li><li id="type-checked_approx_for_block.Ok" class="def variant constructor anchored"><a href="#type-checked_approx_for_block.Ok" class="anchor"></a><code><span>| </span><span><span class="constructor">Ok</span> <span class="keyword">of</span> <a href="../Tag/index.html#type-t">Tag.t</a> * <span><a href="#type-t">t</a> array</span></span></code></li></ol></div></div><div class="odoc-spec"><div class="spec value anchored" id="val-check_approx_for_block"><a href="#val-check_approx_for_block" class="anchor"></a><code><span><span class="keyword">val</span> check_approx_for_block : <span><a href="#type-t">t</a> <span class="arrow">&#45;&gt;</span></span> <a href="#type-checked_approx_for_block">checked_approx_for_block</a></span></code></div><div class="spec-doc"><p>Try to prove that a value with the given approximation may be used as a block.</p></div></div><div class="odoc-spec"><div class="spec value anchored" id="val-approx_for_bound_var"><a href="#val-approx_for_bound_var" class="anchor"></a><code><span><span class="keyword">val</span> approx_for_bound_var : <span><a href="#type-value_set_of_closures">value_set_of_closures</a> <span class="arrow">&#45;&gt;</span></span> <span><a href="../Var_within_closure/index.html#type-t">Var_within_closure.t</a> <span class="arrow">&#45;&gt;</span></span> <a href="#type-t">t</a></span></code></div><div class="spec-doc"><p>Find the approximation for a bound variable in a set-of-closures approximation. A fatal error is produced if the variable is not bound in the given approximation.</p></div></div><div class="odoc-spec"><div class="spec value anchored" id="val-freshen_and_check_closure_id"><a href="#val-freshen_and_check_closure_id" class="anchor"></a><code><span><span class="keyword">val</span> freshen_and_check_closure_id :
<span><a href="#type-value_set_of_closures">value_set_of_closures</a> <span class="arrow">&#45;&gt;</span></span>
<span><a href="../Closure_id/index.html#type-t">Closure_id.t</a> <span class="arrow">&#45;&gt;</span></span>
<a href="../Closure_id/index.html#type-t">Closure_id.t</a></span></code></div><div class="spec-doc"><p>Given a set-of-closures approximation and a closure ID, apply any freshening specified by the approximation to the closure ID, and return the resulting ID. Causes a fatal error if the resulting closure ID does not correspond to any function declaration in the approximation.</p></div></div><div class="odoc-spec"><div class="spec type anchored" id="type-strict_checked_approx_for_set_of_closures"><a href="#type-strict_checked_approx_for_set_of_closures" class="anchor"></a><code><span><span class="keyword">type</span> strict_checked_approx_for_set_of_closures</span><span> = </span></code><ol><li id="type-strict_checked_approx_for_set_of_closures.Wrong" class="def variant constructor anchored"><a href="#type-strict_checked_approx_for_set_of_closures.Wrong" class="anchor"></a><code><span>| </span><span><span class="constructor">Wrong</span></span></code></li><li id="type-strict_checked_approx_for_set_of_closures.Ok" class="def variant constructor anchored"><a href="#type-strict_checked_approx_for_set_of_closures.Ok" class="anchor"></a><code><span>| </span><span><span class="constructor">Ok</span> <span class="keyword">of</span> <span><a href="../Variable/index.html#type-t">Variable.t</a> option</span> * <a href="#type-value_set_of_closures">value_set_of_closures</a></span></code></li></ol></div></div><div class="odoc-spec"><div class="spec value anchored" id="val-strict_check_approx_for_set_of_closures"><a href="#val-strict_check_approx_for_set_of_closures" class="anchor"></a><code><span><span class="keyword">val</span> strict_check_approx_for_set_of_closures :
<span><a href="#type-t">t</a> <span class="arrow">&#45;&gt;</span></span>
<a href="#type-strict_checked_approx_for_set_of_closures">strict_checked_approx_for_set_of_closures</a></span></code></div></div><div class="odoc-spec"><div class="spec type anchored" id="type-checked_approx_for_set_of_closures"><a href="#type-checked_approx_for_set_of_closures" class="anchor"></a><code><span><span class="keyword">type</span> checked_approx_for_set_of_closures</span><span> = </span></code><ol><li id="type-checked_approx_for_set_of_closures.Wrong" class="def variant constructor anchored"><a href="#type-checked_approx_for_set_of_closures.Wrong" class="anchor"></a><code><span>| </span><span><span class="constructor">Wrong</span></span></code></li><li id="type-checked_approx_for_set_of_closures.Unresolved" class="def variant constructor anchored"><a href="#type-checked_approx_for_set_of_closures.Unresolved" class="anchor"></a><code><span>| </span><span><span class="constructor">Unresolved</span> <span class="keyword">of</span> <a href="#type-unresolved_value">unresolved_value</a></span></code></li><li id="type-checked_approx_for_set_of_closures.Unknown" class="def variant constructor anchored"><a href="#type-checked_approx_for_set_of_closures.Unknown" class="anchor"></a><code><span>| </span><span><span class="constructor">Unknown</span></span></code></li><li id="type-checked_approx_for_set_of_closures.Unknown_because_of_unresolved_value" class="def variant constructor anchored"><a href="#type-checked_approx_for_set_of_closures.Unknown_because_of_unresolved_value" class="anchor"></a><code><span>| </span><span><span class="constructor">Unknown_because_of_unresolved_value</span> <span class="keyword">of</span> <a href="#type-unresolved_value">unresolved_value</a></span></code></li><li id="type-checked_approx_for_set_of_closures.Ok" class="def variant constructor anchored"><a href="#type-checked_approx_for_set_of_closures.Ok" class="anchor"></a><code><span>| </span><span><span class="constructor">Ok</span> <span class="keyword">of</span> <span><a href="../Variable/index.html#type-t">Variable.t</a> option</span> * <a href="#type-value_set_of_closures">value_set_of_closures</a></span></code></li></ol></div></div><div class="odoc-spec"><div class="spec value anchored" id="val-check_approx_for_set_of_closures"><a href="#val-check_approx_for_set_of_closures" class="anchor"></a><code><span><span class="keyword">val</span> check_approx_for_set_of_closures : <span><a href="#type-t">t</a> <span class="arrow">&#45;&gt;</span></span> <a href="#type-checked_approx_for_set_of_closures">checked_approx_for_set_of_closures</a></span></code></div><div class="spec-doc"><p>Try to prove that a value with the given approximation may be used as a set of closures. Values coming from external compilation units with unresolved approximations are permitted.</p></div></div><div class="odoc-spec"><div class="spec type anchored" id="type-checked_approx_for_closure"><a href="#type-checked_approx_for_closure" class="anchor"></a><code><span><span class="keyword">type</span> checked_approx_for_closure</span><span> = </span></code><ol><li id="type-checked_approx_for_closure.Wrong" class="def variant constructor anchored"><a href="#type-checked_approx_for_closure.Wrong" class="anchor"></a><code><span>| </span><span><span class="constructor">Wrong</span></span></code></li><li id="type-checked_approx_for_closure.Ok" class="def variant constructor anchored"><a href="#type-checked_approx_for_closure.Ok" class="anchor"></a><code><span>| </span><span><span class="constructor">Ok</span> <span class="keyword">of</span> <a href="#type-value_closure">value_closure</a>
* <span><a href="../Variable/index.html#type-t">Variable.t</a> option</span>
* <span><a href="../Symbol/index.html#type-t">Symbol.t</a> option</span>
* <a href="#type-value_set_of_closures">value_set_of_closures</a></span></code></li></ol></div></div><div class="odoc-spec"><div class="spec value anchored" id="val-check_approx_for_closure"><a href="#val-check_approx_for_closure" class="anchor"></a><code><span><span class="keyword">val</span> check_approx_for_closure : <span><a href="#type-t">t</a> <span class="arrow">&#45;&gt;</span></span> <a href="#type-checked_approx_for_closure">checked_approx_for_closure</a></span></code></div><div class="spec-doc"><p>Try to prove that a value with the given approximation may be used as a closure. Values coming from external compilation units with unresolved approximations are not permitted.</p></div></div><div class="odoc-spec"><div class="spec type anchored" id="type-checked_approx_for_closure_allowing_unresolved"><a href="#type-checked_approx_for_closure_allowing_unresolved" class="anchor"></a><code><span><span class="keyword">type</span> checked_approx_for_closure_allowing_unresolved</span><span> = </span></code><ol><li id="type-checked_approx_for_closure_allowing_unresolved.Wrong" class="def variant constructor anchored"><a href="#type-checked_approx_for_closure_allowing_unresolved.Wrong" class="anchor"></a><code><span>| </span><span><span class="constructor">Wrong</span></span></code></li><li id="type-checked_approx_for_closure_allowing_unresolved.Unresolved" class="def variant constructor anchored"><a href="#type-checked_approx_for_closure_allowing_unresolved.Unresolved" class="anchor"></a><code><span>| </span><span><span class="constructor">Unresolved</span> <span class="keyword">of</span> <a href="#type-unresolved_value">unresolved_value</a></span></code></li><li id="type-checked_approx_for_closure_allowing_unresolved.Unknown" class="def variant constructor anchored"><a href="#type-checked_approx_for_closure_allowing_unresolved.Unknown" class="anchor"></a><code><span>| </span><span><span class="constructor">Unknown</span></span></code></li><li id="type-checked_approx_for_closure_allowing_unresolved.Unknown_because_of_unresolved_value" class="def variant constructor anchored"><a href="#type-checked_approx_for_closure_allowing_unresolved.Unknown_because_of_unresolved_value" class="anchor"></a><code><span>| </span><span><span class="constructor">Unknown_because_of_unresolved_value</span> <span class="keyword">of</span> <a href="#type-unresolved_value">unresolved_value</a></span></code></li><li id="type-checked_approx_for_closure_allowing_unresolved.Ok" class="def variant constructor anchored"><a href="#type-checked_approx_for_closure_allowing_unresolved.Ok" class="anchor"></a><code><span>| </span><span><span class="constructor">Ok</span> <span class="keyword">of</span> <a href="#type-value_closure">value_closure</a>
* <span><a href="../Variable/index.html#type-t">Variable.t</a> option</span>
* <span><a href="../Symbol/index.html#type-t">Symbol.t</a> option</span>
* <a href="#type-value_set_of_closures">value_set_of_closures</a></span></code></li></ol></div></div><div class="odoc-spec"><div class="spec value anchored" id="val-check_approx_for_closure_allowing_unresolved"><a href="#val-check_approx_for_closure_allowing_unresolved" class="anchor"></a><code><span><span class="keyword">val</span> check_approx_for_closure_allowing_unresolved :
<span><a href="#type-t">t</a> <span class="arrow">&#45;&gt;</span></span>
<a href="#type-checked_approx_for_closure_allowing_unresolved">checked_approx_for_closure_allowing_unresolved</a></span></code></div><div class="spec-doc"><p>As for <code>check_approx_for_closure</code>, but values coming from external compilation units with unresolved approximations are permitted.</p></div></div><div class="odoc-spec"><div class="spec value anchored" id="val-check_approx_for_float"><a href="#val-check_approx_for_float" class="anchor"></a><code><span><span class="keyword">val</span> check_approx_for_float : <span><a href="#type-t">t</a> <span class="arrow">&#45;&gt;</span></span> <span>float option</span></span></code></div><div class="spec-doc"><p>Returns the value if it can be proved to be a constant float</p></div></div><div class="odoc-spec"><div class="spec value anchored" id="val-float_array_as_constant"><a href="#val-float_array_as_constant" class="anchor"></a><code><span><span class="keyword">val</span> float_array_as_constant : <span><a href="#type-value_float_array">value_float_array</a> <span class="arrow">&#45;&gt;</span></span> <span><span>float list</span> option</span></span></code></div><div class="spec-doc"><p>Returns the value if it can be proved to be a constant float array</p></div></div><div class="odoc-spec"><div class="spec value anchored" id="val-check_approx_for_string"><a href="#val-check_approx_for_string" class="anchor"></a><code><span><span class="keyword">val</span> check_approx_for_string : <span><a href="#type-t">t</a> <span class="arrow">&#45;&gt;</span></span> <span>string option</span></span></code></div><div class="spec-doc"><p>Returns the value if it can be proved to be a constant string</p></div></div><div class="odoc-spec"><div class="spec type anchored" id="type-switch_branch_selection"><a href="#type-switch_branch_selection" class="anchor"></a><code><span><span class="keyword">type</span> switch_branch_selection</span><span> = </span></code><ol><li id="type-switch_branch_selection.Cannot_be_taken" class="def variant constructor anchored"><a href="#type-switch_branch_selection.Cannot_be_taken" class="anchor"></a><code><span>| </span><span><span class="constructor">Cannot_be_taken</span></span></code></li><li id="type-switch_branch_selection.Can_be_taken" class="def variant constructor anchored"><a href="#type-switch_branch_selection.Can_be_taken" class="anchor"></a><code><span>| </span><span><span class="constructor">Can_be_taken</span></span></code></li><li id="type-switch_branch_selection.Must_be_taken" class="def variant constructor anchored"><a href="#type-switch_branch_selection.Must_be_taken" class="anchor"></a><code><span>| </span><span><span class="constructor">Must_be_taken</span></span></code></li></ol></div></div><div class="odoc-spec"><div class="spec value anchored" id="val-potentially_taken_const_switch_branch"><a href="#val-potentially_taken_const_switch_branch" class="anchor"></a><code><span><span class="keyword">val</span> potentially_taken_const_switch_branch : <span><a href="#type-t">t</a> <span class="arrow">&#45;&gt;</span></span> <span>int <span class="arrow">&#45;&gt;</span></span> <a href="#type-switch_branch_selection">switch_branch_selection</a></span></code></div><div class="spec-doc"><p>Check that the branch is compatible with the approximation</p></div></div><div class="odoc-spec"><div class="spec value anchored" id="val-potentially_taken_block_switch_branch"><a href="#val-potentially_taken_block_switch_branch" class="anchor"></a><code><span><span class="keyword">val</span> potentially_taken_block_switch_branch : <span><a href="#type-t">t</a> <span class="arrow">&#45;&gt;</span></span> <span>int <span class="arrow">&#45;&gt;</span></span> <a href="#type-switch_branch_selection">switch_branch_selection</a></span></code></div></div><div class="odoc-spec"><div class="spec value anchored" id="val-function_arity"><a href="#val-function_arity" class="anchor"></a><code><span><span class="keyword">val</span> function_arity : <span><a href="#type-function_declaration">function_declaration</a> <span class="arrow">&#45;&gt;</span></span> int</span></code></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-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-update_function_declaration_body"><a href="#val-update_function_declaration_body" class="anchor"></a><code><span><span class="keyword">val</span> update_function_declaration_body :
<span><a href="#type-function_declaration">function_declaration</a> <span class="arrow">&#45;&gt;</span></span>
<span><span>(<span><a href="../Flambda/index.html#type-t">Flambda.t</a> <span class="arrow">&#45;&gt;</span></span> <a href="../Flambda/index.html#type-t">Flambda.t</a>)</span> <span class="arrow">&#45;&gt;</span></span>
<a href="#type-function_declaration">function_declaration</a></span></code></div></div><div class="odoc-spec"><div class="spec value anchored" id="val-make_closure_map"><a href="#val-make_closure_map" class="anchor"></a><code><span><span class="keyword">val</span> make_closure_map :
<span><span><a href="#type-function_declarations">function_declarations</a> <a href="../Set_of_closures_id/Map/index.html#type-t">Set_of_closures_id.Map.t</a></span> <span class="arrow">&#45;&gt;</span></span>
<span><a href="#type-function_declarations">function_declarations</a> <a href="../Closure_id/Map/index.html#type-t">Closure_id.Map.t</a></span></span></code></div><div class="spec-doc"><p>Creates a map from closure IDs to function declarations by iterating over all sets of closures in the given map.</p></div></div><div class="odoc-spec"><div class="spec value anchored" id="val-clear_function_bodies"><a href="#val-clear_function_bodies" class="anchor"></a><code><span><span class="keyword">val</span> clear_function_bodies : <span><a href="#type-function_declarations">function_declarations</a> <span class="arrow">&#45;&gt;</span></span> <a href="#type-function_declarations">function_declarations</a></span></code></div></div></div></body></html>