File 0372-sys_core_fold-Fix-name-capture-problem.patch of Package erlang

From 7eb06ed5ac1687d38245db2e0aef2756cb43b1ae Mon Sep 17 00:00:00 2001
From: =?UTF-8?q?Bj=C3=B6rn=20Gustavsson?= <bjorn@erlang.org>
Date: Mon, 4 Jun 2018 06:14:19 +0200
Subject: [PATCH 2/2] sys_core_fold: Fix name capture problem

sys_core_fold could do unsafe transformations on the
code from the old inliner (invoked using the compiler
option `{inline,[{F/A}]}` to request inlining of specific
functions).

To explain the bug, let's first look at an example that
sys_core_fold handles correctly. Consider this code:

    'foo'/2 =
        fun (Arg1,Arg2) ->
          let <B> = Arg2
          in let <A,B> = <B,Arg1>
             in {A,B}

In this example, the lets can be completely eliminated,
since the arguments for the lets are variables (as opposed
to expressions). Since the variable B is rebound in the
inner let, `sys_core_fold` must take special care when
doing the substitutions.

Here is the correct result:

    'foo'/2 =
        fun (Arg1, Arg2) ->
          {Arg2,Arg1}

Consider a slight modifictation of the example:

    'bar'/2 =
        fun (Arg1,Arg2) ->
            let <B> = [Arg2]
            in let <A,B> = <B,[Arg1]>
               in {A,B}

Here some of the arguments for the lets are expressions, so
the lets must be kept. sys_core_fold does not handle this
example correctly:

    'bar'/2 =
        fun (Arg1,Arg2) ->
          let <B> = [Arg2]
    	  in let <B> = [Arg1]
    	     in {B,B}

In the inner let, the variable A has been eliminated and
replaced with the variable B in the body (the first B in
the tuple). Since the B in the outer let is never used,
the outer let will be eliminated, giving:

    'bar'/2 =
        fun (Arg1,Arg2) ->
    	  let <B> = [Arg1]
    	  in {B,B}

To handle this example correctly, sys_core_fold must
rename the variable B in the inner let like this to
avoid capturing B:

    'bar'/2 =
       fun (Arg1,Arg2) ->
         let <B> = [Arg2]
         in let <NewName> = [Arg1]
            in {B,NewName}

(Note: The `v3_kernel` pass alreday handles those examples correctly
in case `sys_core_fold` has been disabled.)
---
 lib/compiler/src/sys_core_fold.erl                 |  37 +++----
 lib/compiler/test/core_SUITE.erl                   |   5 +-
 .../test/core_SUITE_data/name_capture.core         | 110 +++++++++++++++++++++
 3 files changed, 124 insertions(+), 28 deletions(-)
 create mode 100644 lib/compiler/test/core_SUITE_data/name_capture.core

diff --git a/lib/compiler/src/sys_core_fold.erl b/lib/compiler/src/sys_core_fold.erl
index a13bdedaf9..47042c2393 100644
--- a/lib/compiler/src/sys_core_fold.erl
+++ b/lib/compiler/src/sys_core_fold.erl
@@ -1275,13 +1275,18 @@ let_subst_list([], [], _) -> {[],[],[]}.
 %%pattern(Pat, Sub) -> pattern(Pat, Sub, Sub).
 
 pattern(#c_var{}=Pat, Isub, Osub) ->
-    case sub_is_val(Pat, Isub) of
+    case sub_is_in_scope(Pat, Isub) of
 	true ->
+            %% This variable either has a substitution or is used in
+            %% the variable list of an enclosing `let`. In either
+            %% case, it must be renamed to an unused name to avoid
+            %% name capture problems.
 	    V1 = make_var_name(),
 	    Pat1 = #c_var{name=V1},
 	    {Pat1,sub_set_var(Pat, Pat1, sub_add_scope([V1], Osub))};
 	false ->
-	    {Pat,sub_del_var(Pat, Osub)}
+            %% This variable has never been used. Add it to the scope.
+	    {Pat,sub_add_scope([Pat#c_var.name], Osub)}
     end;
 pattern(#c_literal{}=Pat, _, Osub) -> {Pat,Osub};
 pattern(#c_cons{anno=Anno,hd=H0,tl=T0}, Isub, Osub0) ->
@@ -1460,8 +1465,8 @@ is_subst(_) -> false.
 %% sub_set_name(Name, Value, #sub{}) -> #sub{}.
 %% sub_del_var(Var, #sub{}) -> #sub{}.
 %% sub_subst_var(Var, Value, #sub{}) -> [{Name,Value}].
-%% sub_is_val(Var, #sub{}) -> boolean().
-%% sub_add_scope(#sub{}) -> #sub{}
+%% sub_is_in_scope(Var, #sub{}) -> boolean().
+%% sub_add_scope([Var], #sub{}) -> #sub{}
 %% sub_subst_scope(#sub{}) -> #sub{}
 %%
 %%  We use the variable name as key so as not have problems with
@@ -1496,18 +1501,6 @@ sub_set_name(V, Val, #sub{v=S,s=Scope,t=Tdb0}=Sub) ->
     Tdb = copy_type(V, Val, Tdb1),
     Sub#sub{v=orddict:store(V, Val, S),s=cerl_sets:add_element(V, Scope),t=Tdb}.
 
-sub_del_var(#c_var{name=V}, #sub{v=S,s=Scope,t=Tdb}=Sub) ->
-    %% Profiling shows that for programs with many record operations,
-    %% sub_del_var/2 is a bottleneck. Since the scope contains all
-    %% variables that are live, we know that V cannot be present in S
-    %% if it is not in the scope.
-    case cerl_sets:is_element(V, Scope) of
-	false ->
-	    Sub#sub{s=cerl_sets:add_element(V, Scope)};
-	true ->
-	    Sub#sub{v=orddict:erase(V, S),t=kill_types(V, Tdb)}
-    end.
-
 sub_subst_var(#c_var{name=V}, Val, #sub{v=S0}) ->
     %% Fold chained substitutions.
     [{V,Val}] ++ [ {K,Val} || {K,#c_var{name=V1}} <- S0, V1 =:= V].
@@ -1533,16 +1526,8 @@ sub_subst_scope_1([H|T], Key, Acc) ->
     S = [{-1,#c_var{name=Sv}} || Sv <- cerl_sets:to_list(Scope)]++S0,
     Sub#sub{v=S}.
 
-sub_is_val(#c_var{name=V}, #sub{v=S,s=Scope}) ->
-    %% When the bottleneck in sub_del_var/2 was eliminated, this
-    %% became the new bottleneck. Since the scope contains all
-    %% live variables, a variable V can only be the target for
-    %% a substitution if it is in the scope.
-    cerl_sets:is_element(V, Scope) andalso v_is_value(V, S).
-
-v_is_value(Var, [{_,#c_var{name=Var}}|_]) -> true;
-v_is_value(Var, [_|T]) -> v_is_value(Var, T);
-v_is_value(_, []) -> false.
+sub_is_in_scope(#c_var{name=V}, #sub{s=Scope}) ->
+    cerl_sets:is_element(V, Scope).
 
 %% warn_no_clause_match(CaseOrig, CaseOpt) -> ok
 %%  Generate a warning if none of the user-specified clauses
diff --git a/lib/compiler/test/core_SUITE.erl b/lib/compiler/test/core_SUITE.erl
index 0e07e8dd2e..d07cd3b8b7 100644
--- a/lib/compiler/test/core_SUITE.erl
+++ b/lib/compiler/test/core_SUITE.erl
@@ -26,7 +26,8 @@
 	 seq_in_guard/1,make_effect_seq/1,eval_is_boolean/1,
 	 unsafe_case/1,nomatch_shadow/1,reversed_annos/1,
 	 map_core_test/1,eval_case/1,bad_boolean_guard/1,
-	 bs_shadowed_size_var/1
+	 bs_shadowed_size_var/1,
+	 name_capture/1
 	]).
 
 -include_lib("common_test/include/ct.hrl").
@@ -53,7 +54,8 @@ groups() ->
       [dehydrated_itracer,nested_tries,seq_in_guard,make_effect_seq,
        eval_is_boolean,unsafe_case,nomatch_shadow,reversed_annos,
        map_core_test,eval_case,bad_boolean_guard,
-       bs_shadowed_size_var
+       bs_shadowed_size_var,
+       name_capture
    ]}].
 
 
@@ -82,7 +84,7 @@ end_per_group(_GroupName, Config) ->
 ?comp(eval_case).
 ?comp(bad_boolean_guard).
 ?comp(bs_shadowed_size_var).
-
+?comp(name_capture).
 
 try_it(Mod, Conf) ->
     Src = filename:join(proplists:get_value(data_dir, Conf),
diff --git a/lib/compiler/test/core_SUITE_data/name_capture.core b/lib/compiler/test/core_SUITE_data/name_capture.core
new file mode 100644
index 0000000000..0969f95b72
--- /dev/null
+++ b/lib/compiler/test/core_SUITE_data/name_capture.core
@@ -0,0 +1,110 @@
+module 'name_capture' ['module_info'/0,
+		       'module_info'/1,
+		       'name_capture'/0]
+    attributes ['compile' =
+		    [{'inline',[{'badarg_exit',2}]}]]
+'name_capture'/0 =
+    fun () ->
+	case <> of
+	  <> when 'true' ->
+	      let <_0> =
+		  catch
+		      apply 'first'/1
+			  ('badarg')
+	      in  case _0 of
+		    <{'EXIT',{'badarg',_7}}> when 'true' ->
+			let <Seq> =
+			    call 'lists':'seq'
+				(7, 17)
+			in  case apply 'first'/1
+				     ({'ok',Seq}) of
+			      <_8>
+				  when call 'erlang':'=:='
+					(_8,
+					 Seq) ->
+				  let <SomeOtherTerm> =
+				      {'some','other','term'}
+				  in  let <_5> =
+					  catch
+					      apply 'first'/1
+						  (SomeOtherTerm)
+				      in  case _5 of
+					    <{'EXIT',_9}>
+						when call 'erlang':'=:='
+						      (_9,
+						       SomeOtherTerm) ->
+						'ok'
+					    <_6> when 'true' ->
+						primop 'match_fail'
+						    ({'badmatch',_6})
+					  end
+			      <_3> when 'true' ->
+				  primop 'match_fail'
+				      ({'badmatch',_3})
+			    end
+		    <_1> when 'true' ->
+			primop 'match_fail'
+			    ({'badmatch',_1})
+		  end
+	  <> when 'true' ->
+	      primop 'match_fail'
+		  ({'function_clause'})
+	end
+'first'/1 =
+    fun (_0) ->
+	case _0 of
+	  <Tab> when 'true' ->
+	      let <_1> =
+		  apply 'treq'/2
+		      (Tab, 'first')
+		      %% The _1 variable in the `let` must be renamed
+		      %% to avoid a name capture problem.
+	      in  let <_0,_1> =
+		      <_1,[Tab|[]]>
+		  in  case <_0,_1> of
+			<'badarg',A> when 'true' ->
+			    call 'erlang':'error'
+				('badarg', A)
+			<{'ok',Reply},_X_A> when 'true' ->
+			    Reply
+			<Reply,_X_A> when 'true' ->
+			    call 'erlang':'exit'
+				(Reply)
+			<_3,_2> when 'true' ->
+			    primop 'match_fail'
+				({'function_clause',_3,_2})
+		      end
+	  <_2> when 'true' ->
+	      primop 'match_fail'
+		  ({'function_clause',_2})
+	end
+'treq'/2 =
+    fun (_0,_1) ->
+	case <_0,_1> of
+	  <Action,_4> when 'true' ->
+	      Action
+	  <_3,_2> when 'true' ->
+	      primop 'match_fail'
+		  ({'function_clause',_3,_2})
+	end
+'module_info'/0 =
+    fun () ->
+	case <> of
+	  <> when 'true' ->
+	      call 'erlang':'get_module_info'
+		  ('name_capture')
+	  <> when 'true' ->
+	      primop 'match_fail'
+		  ({'function_clause'})
+	end
+'module_info'/1 =
+    fun (_0) ->
+	case _0 of
+	  <X> when 'true' ->
+	      call 'erlang':'get_module_info'
+		  ('name_capture', X)
+	  <_1> when 'true' ->
+	      primop 'match_fail'
+		  ({'function_clause',_1})
+	end
+end
-- 
2.16.4

openSUSE Build Service is sponsored by