File 2113-compiler-Fix-awkward-match-context-substitution.patch of Package erlang
From 6ae9975689858d0e0c9af0a36869c012bb3762c0 Mon Sep 17 00:00:00 2001
From: =?UTF-8?q?John=20H=C3=B6gberg?= <john@erlang.org>
Date: Wed, 7 Aug 2019 14:00:09 +0200
Subject: [PATCH 2/2] compiler: Fix awkward match context substitution
This worked out by accident since codegen never actually looks at
the arguments for 'succeeded'; it just assumes that they reference
the preceding instruction.
---
 lib/compiler/src/beam_ssa_lint.erl        | 20 +++++++++++++++++++-
 lib/compiler/src/beam_ssa_pre_codegen.erl |  4 ++++
 lib/compiler/test/misc_SUITE.erl          | 24 ++++++++++++++++++++++--
 3 files changed, 45 insertions(+), 3 deletions(-)
diff --git a/lib/compiler/src/beam_ssa_lint.erl b/lib/compiler/src/beam_ssa_lint.erl
index b2a8c1a0d1..224095d4c4 100644
--- a/lib/compiler/src/beam_ssa_lint.erl
+++ b/lib/compiler/src/beam_ssa_lint.erl
@@ -65,7 +65,13 @@ format_error({{_M,F,A},{phi_inside_block, Name, Id}}) ->
                   [F, A, format_var(Name), Id]);
 format_error({{_M,F,A},{undefined_label_in_phi, Label, I}}) ->
     io_lib:format("~p/~p: Unknown block label ~p in phi node ~ts",
-                  [F, A, Label, format_instr(I)]).
+                  [F, A, Label, format_instr(I)]);
+format_error({{_M,F,A},{succeeded_not_preceded, I}}) ->
+    io_lib:format("~p/~p: ~ts does not reference the preceding instruction",
+                  [F, A, format_instr(I)]);
+format_error({{_M,F,A},{succeeded_not_last, I}}) ->
+    io_lib:format("~p/~p: ~ts is not the last instruction in its block",
+                  [F, A, format_instr(I)]).
 
 format_instr(I) ->
     [$',beam_ssa_pp:format_instr(I),$'].
@@ -229,6 +235,18 @@ vvars_block(Id, State0) ->
       State :: #vvars{}.
 vvars_block_1([], State) ->
     State;
+vvars_block_1([#b_set{dst=OpVar,args=OpArgs}=I,
+               #b_set{op=succeeded,args=[OpVar],dst=SuccVar}], State) ->
+    ok = vvars_assert_args(OpArgs, I, State),
+    vvars_save_var(SuccVar, vvars_save_var(OpVar, State));
+vvars_block_1([#b_set{op=succeeded,args=Args}=I | [_|_]], State) ->
+    ok = vvars_assert_args(Args, I, State),
+    %% 'succeeded' must be the last instruction in its block.
+    throw({succeeded_not_last, I});
+vvars_block_1([#b_set{op=succeeded,args=Args}=I], State)->
+    ok = vvars_assert_args(Args, I, State),
+    %% 'succeeded' must be be directly preceded by the operation it checks.
+    throw({succeeded_not_preceded, I});
 vvars_block_1([#b_set{ dst = Dst, op = phi } | Is], State) ->
     %% We don't check phi node arguments at this point since we may not have
     %% visited their definition yet. They'll be handled later on in
diff --git a/lib/compiler/src/beam_ssa_pre_codegen.erl b/lib/compiler/src/beam_ssa_pre_codegen.erl
index 9847b87b18..61b2155e39 100644
--- a/lib/compiler/src/beam_ssa_pre_codegen.erl
+++ b/lib/compiler/src/beam_ssa_pre_codegen.erl
@@ -603,6 +603,10 @@ bs_instrs([{L,#b_blk{is=Is0}=Blk}|Bs], CtxChain, Acc0) ->
 bs_instrs([], _, Acc) ->
     reverse(Acc).
 
+bs_instrs_is([#b_set{op=succeeded}=I|Is], CtxChain, Acc) ->
+    %% This instruction refers to a specific operation, so we must not
+    %% substitute the context argument.
+    bs_instrs_is(Is, CtxChain, [I | Acc]);
 bs_instrs_is([#b_set{op=Op,args=Args0}=I0|Is], CtxChain, Acc) ->
     Args = [bs_subst_ctx(A, CtxChain) || A <- Args0],
     I1 = I0#b_set{args=Args},
diff --git a/lib/compiler/test/misc_SUITE.erl b/lib/compiler/test/misc_SUITE.erl
index eb60dc049d..20fadc4fdb 100644
--- a/lib/compiler/test/misc_SUITE.erl
+++ b/lib/compiler/test/misc_SUITE.erl
@@ -274,13 +274,33 @@ silly_coverage(Config) when is_list(Config) ->
 
 bad_ssa_lint_input() ->
     {b_module,#{},t,
-     [{foobar,1},{module_info,0},{module_info,1}],
+     [{a,1},{b,1},{c,1},{module_info,0},{module_info,1}],
      [],
      [{b_function,
-       #{func_info => {t,foobar,1},location => {"t.erl",4}},
+       #{func_info => {t,a,1},location => {"t.erl",4}},
        [{b_var,0}],
        #{0 => {b_blk,#{},[],{b_ret,#{},{b_var,'@undefined_var'}}}},
        3},
+      {b_function,
+       #{func_info => {t,b,1},location => {"t.erl",5}},
+       [{b_var,0}],
+       #{0 =>
+             {b_blk,#{},
+              [{b_set,#{},{b_var,'@first_var'},first_op,[]},
+               {b_set,#{},{b_var,'@second_var'},second_op,[]},
+               {b_set,#{},{b_var,'@ret'},succeeded,[{b_var,'@first_var'}]}],
+              {b_ret,#{},{b_var,'@ret'}}}},
+       3},
+      {b_function,
+       #{func_info => {t,c,1},location => {"t.erl",6}},
+       [{b_var,0}],
+       #{0 =>
+             {b_blk,#{},
+              [{b_set,#{},{b_var,'@first_var'},first_op,[]},
+               {b_set,#{},{b_var,'@ret'},succeeded,[{b_var,'@first_var'}]},
+               {b_set,#{},{b_var,'@second_var'},second_op,[]}],
+              {b_ret,#{},{b_var,'@ret'}}}},
+       3},
       {b_function,
        #{func_info => {t,module_info,0}},
        [],
-- 
2.16.4