Skip to content

Commit

Permalink
Fix marking of if condition as inconstant in flambda Fix #10603 (#10611)
Browse files Browse the repository at this point in the history
The if condition was marked as systematically inconstant. This was not
often problematic since most of the time this means that the if is
eliminated by simplify. But this is not the case in let rec's where
the approximation of the value is not known by simplify.

But the problem is noticeable in this example

type t = A | B of (int -> int)

let p = 1 + 1

let rec b = B g
and g n =
  let b' = b in
  match b' with
  | A -> n + p
  | B f -> f n

The inconstant_ident pass correctly identifies b and g as constants, but
marks b' as inconstant due to this bug (because match on this kind of
type is compiled as an if). When lifting the definition of g into a
let_rec_symbol, the alias_analysis does not keep the alias of b' to b
because b' is considered as inconstant. Hence no substitution is applied
to it. This leads to building a closed function with free variables,
which is obviously wrong.
  • Loading branch information
chambart committed Sep 9, 2021
1 parent ba4dad6 commit b8efbfb
Show file tree
Hide file tree
Showing 4 changed files with 17 additions and 2 deletions.
3 changes: 3 additions & 0 deletions Changes
Expand Up @@ -162,6 +162,9 @@ Working version
- #10590: Some typechecker optimisations
(Stephen Dolan, review by Gabriel Scherer and Leo White)

- #10603, #10611: Fix if condition marked as inconstant in flambda
(Vincent Laviron and Pierre Chambart, report by Marcello Seri)

OCaml 4.13.0
-------------

Expand Down
4 changes: 2 additions & 2 deletions middle_end/flambda/inconstant_idents.ml
Expand Up @@ -269,9 +269,9 @@ module Inconstants (P:Param) (Backend:Backend_intf.S) = struct
mark_curr curr;
mark_loop ~toplevel [] f1;
mark_loop ~toplevel:false [] body
| If_then_else (f1,f2,f3) ->
| If_then_else (cond,f2,f3) ->
mark_curr curr;
mark_curr [Var f1];
mark_var cond curr;
mark_loop ~toplevel [] f2;
mark_loop ~toplevel [] f3
| Static_raise (_,l) ->
Expand Down
12 changes: 12 additions & 0 deletions testsuite/tests/regression/pr10611/pr10611.ml
@@ -0,0 +1,12 @@
(* TEST *)

type t = A | B of (int -> int)

let p = 1 + 1

let rec b = B g
and g n =
let b' = b in
match b' with
| A -> n + p
| B f -> f n
Empty file.

0 comments on commit b8efbfb

Please sign in to comment.