File 3381-Handle-macros-in-patterns.patch of Package erlang

From f098f67215a484a17837fede5b9c0c7a23c4c411 Mon Sep 17 00:00:00 2001
From: =?UTF-8?q?P=C3=A9ter=20G=C3=B6m=C3=B6ri?= <gomoripeti@gmail.com>
Date: Mon, 11 Jan 2021 02:40:15 +0100
Subject: [PATCH] Handle macros in patterns

The dodger used to replace a macro with a local function call. That works in
expressions but not in patterns like function heads or catch patterns. Instead
of a function call a tuple syntax is used which works in more places.

This change is motivated by the commonly used `?EXCEPTION` macro

```
try
  ...
catch
  ?EXCEPTION(Class, Reason, StackToken) ->
    ...
end.
```

Open source examples:
https://github.com/devinus/poolboy/commit/5d40cc517edc9bb8ee70756544167b63f66662f0
https://github.com/eproxus/meck/commit/558e925b48ce257b12e381080c851dc49c87d7bb

Fixes ERL-1429
---
 lib/syntax_tools/src/epp_dodger.erl           | 65 ++++++++++++-------
 lib/syntax_tools/test/syntax_tools_SUITE.erl  | 34 +++++++++-
 .../epp_dodger_clever.erl                     | 12 ++++
 .../syntax_tools_test.erl                     | 19 +++++-
 4 files changed, 101 insertions(+), 29 deletions(-)
 create mode 100644 lib/syntax_tools/test/syntax_tools_SUITE_data/epp_dodger_clever.erl

diff --git a/lib/syntax_tools/src/epp_dodger.erl b/lib/syntax_tools/src/epp_dodger.erl
index da22a91de0..8ee6368868 100644
--- a/lib/syntax_tools/src/epp_dodger.erl
+++ b/lib/syntax_tools/src/epp_dodger.erl
@@ -544,6 +544,7 @@ quickscan_macros([{'?',_}, {Type, _, _}=N | [{'(',_}|_]=Ts],
     Ts1 = case skip_macro_args(Ts) of
 	      {_, [{'->',_} | _] = Ts2} -> Ts2;
 	      {_, [{'when',_} | _] = Ts2} -> Ts2;
+	      {_, [{':',_} | _] = Ts2} -> Ts2;
 	      _ -> Ts    %% assume macro without arguments
 	  end,
     quickscan_macros_1(N, Ts1, As);
@@ -705,6 +706,8 @@ scan_macros([{'?', L}, {Type, _, _}=N | [{'(',_}|_]=Ts],
 	    macro_call(Args, L, N, Rest, As, Opt);
 	[{'when',_} | _] ->
 	    macro_call(Args, L, N, Rest, As, Opt);
+	[{':',_} | _] ->
+	    macro_call(Args, L, N, Rest, As, Opt);
 	_ ->
 	    macro(L, N, Ts, As, Opt)
     end;
@@ -722,7 +725,7 @@ scan_macros([T | Ts], As, Opt) ->
 scan_macros([], As, _Opt) ->
     lists:reverse(As).
 
-%% Rewriting to a call which will be recognized by the post-parse pass
+%% Rewriting to a tuple which will be recognized by the post-parse pass
 %% (we insert parentheses to preserve the precedences when parsing).
 
 macro(L, {Type, _, A}, Rest, As, Opt) ->
@@ -731,17 +734,28 @@ macro(L, {Type, _, A}, Rest, As, Opt) ->
 macro_call([{'(',_}, {')',_}], L, {_, Ln, _}=N, Rest, As, Opt) ->
     {Open, Close} = parentheses(As),
     scan_macros_1([], Rest,
-		  lists:reverse(Open ++ [{atom,L,?macro_call},
-					 {'(',L}, N, {')',Ln}] ++ Close,
-				As), Opt);
+                  %% {'?macro_call', N }
+                  lists:reverse(Open ++ [{'{', L},
+                                         {atom, L, ?macro_call},
+                                         {',', L},
+                                         N,
+                                         {'}', Ln}] ++ Close,
+                                As), Opt);
 macro_call([{'(',_} | Args], L, {_, Ln, _}=N, Rest, As, Opt) ->
     {Open, Close} = parentheses(As),
+    %% drop closing parenthesis
+    {')', _} = lists:last(Args), %% assert
+    Args1 = lists:droplast(Args),
     %% note that we must scan the argument list; it may not be skipped
-    scan_macros_1(Args ++ Close,
-		  Rest,
-		  lists:reverse(Open ++ [{atom,L,?macro_call},
-					 {'(',L}, N, {',',Ln}],
-				As), Opt).
+    scan_macros_1(Args1 ++ [{'}', Ln} | Close],
+                  Rest,
+                  %% {'?macro_call', N, Arg1, ... }
+                  lists:reverse(Open ++ [{'{', L},
+                                         {atom, L, ?macro_call},
+                                         {',', L},
+                                         N,
+                                         {',', Ln}],
+                                As), Opt).
 
 macro_atom(atom, A) ->
     list_to_atom(?atom_prefix ++ atom_to_list(A));
@@ -798,21 +812,24 @@ rewrite(Node) ->
 		_ ->
 		    Node
 	    end;
-	application ->
-	    F = erl_syntax:application_operator(Node),
-	    case erl_syntax:type(F) of
-		atom ->
-		    case erl_syntax:atom_value(F) of
-			?macro_call ->
-			    [A | As] = erl_syntax:application_arguments(Node),
-			    M = erl_syntax:macro(A, rewrite_list(As)),
-			    erl_syntax:copy_pos(Node, M);
-			_ ->
-			    rewrite_1(Node)
-		    end;
-		_ ->
-		    rewrite_1(Node)
-	    end;
+        tuple ->
+            case erl_syntax:tuple_elements(Node) of
+                [MagicWord, A | As] ->
+                    case erl_syntax:type(MagicWord) of
+                        atom ->
+                            case erl_syntax:atom_value(MagicWord) of
+                                ?macro_call ->
+                                    M = erl_syntax:macro(A, rewrite_list(As)),
+                                    erl_syntax:copy_pos(Node, M);
+                                _ ->
+                                    rewrite_1(Node)
+                            end;
+                        _ ->
+                            rewrite_1(Node)
+                    end;
+                _ ->
+                    rewrite_1(Node)
+            end;
 	_ ->
 	    rewrite_1(Node)
     end.
diff --git a/lib/syntax_tools/test/syntax_tools_SUITE.erl b/lib/syntax_tools/test/syntax_tools_SUITE.erl
index 9baf36ce11..14a7912642 100644
--- a/lib/syntax_tools/test/syntax_tools_SUITE.erl
+++ b/lib/syntax_tools/test/syntax_tools_SUITE.erl
@@ -25,7 +25,8 @@
 %% Test cases
 -export([app_test/1,appup_test/1,smoke_test/1,revert/1,revert_map/1,
          revert_map_type/1,wrapped_subtrees/1,
-	t_abstract_type/1,t_erl_parse_type/1,t_type/1, t_epp_dodger/1,
+         t_abstract_type/1,t_erl_parse_type/1,t_type/1,
+         t_epp_dodger/1,t_epp_dodger_clever/1,
 	t_comment_scan/1,t_igor/1,t_erl_tidy/1,t_prettypr/1]).
 
 suite() -> [{ct_hooks,[ts_install_cth]}].
@@ -33,7 +34,8 @@ suite() -> [{ct_hooks,[ts_install_cth]}].
 all() -> 
     [app_test,appup_test,smoke_test,revert,revert_map,revert_map_type,
      wrapped_subtrees,
-    t_abstract_type,t_erl_parse_type,t_type,t_epp_dodger,
+     t_abstract_type,t_erl_parse_type,t_type,
+     t_epp_dodger,t_epp_dodger_clever,
     t_comment_scan,t_igor,t_erl_tidy,t_prettypr].
 
 groups() -> 
@@ -330,6 +332,13 @@ t_epp_dodger(Config) when is_list(Config) ->
     ok = test_epp_dodger(Filenames,DataDir,PrivDir),
     ok.
 
+t_epp_dodger_clever(Config) when is_list(Config) ->
+    DataDir   = ?config(data_dir, Config),
+    PrivDir   = ?config(priv_dir, Config),
+    Filenames = ["epp_dodger_clever.erl"],
+    ok = test_epp_dodger_clever(Filenames,DataDir,PrivDir),
+    ok.
+
 t_comment_scan(Config) when is_list(Config) ->
     DataDir   = ?config(data_dir, Config),
     Filenames = test_files(),
@@ -447,9 +456,30 @@ test_epp_dodger([Filename|Files],DataDir,PrivDir) ->
     ok = pretty_print_parse_forms(FsForms,PrivDir,Filename),
     test_epp_dodger(Files,DataDir,PrivDir).
 
+test_epp_dodger_clever([], _, _) -> ok;
+test_epp_dodger_clever([Filename|Files],DataDir,PrivDir) ->
+    io:format("Parsing ~p~n", [Filename]),
+    InFile   = filename:join(DataDir, Filename),
+    Parsers  = [{fun(File) ->
+                         epp_dodger:parse_file(File, [clever])
+                 end, parse_file},
+		{fun(File) ->
+                         epp_dodger:quick_parse_file(File, [clever])
+                 end, quick_parse_file}],
+    FsForms  = parse_with(Parsers, InFile),
+    ok = pretty_print_parse_forms(FsForms,PrivDir,Filename),
+    test_epp_dodger_clever(Files,DataDir,PrivDir).
+
 parse_with([],_) -> [];
 parse_with([{Fun,ParserType}|Funs],File) ->
     {ok, Fs} = Fun(File),
+    ErrorMarkers = [begin
+                        print_error_markers(F, File),
+                        F
+                    end
+                    || F <- Fs,
+                       erl_syntax:type(F) =:= error_marker],
+    [] = ErrorMarkers,
     [{Fs,ParserType}|parse_with(Funs,File)].
 
 pretty_print_parse_forms([],_,_) -> ok;
diff --git a/lib/syntax_tools/test/syntax_tools_SUITE_data/epp_dodger_clever.erl b/lib/syntax_tools/test/syntax_tools_SUITE_data/epp_dodger_clever.erl
new file mode 100644
index 0000000000..4a3be06d98
--- /dev/null
+++ b/lib/syntax_tools/test/syntax_tools_SUITE_data/epp_dodger_clever.erl
@@ -0,0 +1,12 @@
+-module(epp_dodger_clever).
+
+-export([foo1/0]).
+
+-define(macro_string, "hello world").
+
+foo1() ->
+    % string combining ?
+    [?macro_string
+     "hello world ",
+     "more hello"
+     ?macro_string].
diff --git a/lib/syntax_tools/test/syntax_tools_SUITE_data/syntax_tools_test.erl b/lib/syntax_tools/test/syntax_tools_SUITE_data/syntax_tools_test.erl
index dd3f88d7a8..b8a21ef0ab 100644
--- a/lib/syntax_tools/test/syntax_tools_SUITE_data/syntax_tools_test.erl
+++ b/lib/syntax_tools/test/syntax_tools_SUITE_data/syntax_tools_test.erl
@@ -6,7 +6,7 @@
 
 -module(syntax_tools_test).
 
--export([foo1/0,foo2/2,foo3/0,foo4/3,foo5/1]).
+-export([foo1/0,foo2/2,foo3/0,foo4/3,foo5/1,foo6/2]).
 
 -include_lib("kernel/include/file.hrl").
 -record(state, { a, b, c, d}).
@@ -24,6 +24,7 @@
 -define(macro_string, "hello world").
 -define(macro_argument1(X), (X + 3)).
 -define(macro_argument2(X,Y), (X + 3 * Y)).
+-define(macro_argument3(X), {error, X}).
 -define(macro_block(X), begin X end).
 -define(macro_if(X1,X2), if X1 -> X2; true -> none end).
 
@@ -48,8 +49,7 @@ foo1() ->
 %% macro test
 foo2(A,B) ->
     % string combining ?
-    [?macro_string, ?macro_string
-     ?macro_string,
+    [?macro_string, ?macro_string ++
      "hello world "
      "more hello",
      [?macro_simple1,
@@ -113,3 +113,16 @@ foo5(A) ->
 	error:?macro_simple5 ->
 	    nope
     end.
+
+%% macros in patterns
+foo6(?MACRO_SIMPLE2, ?macro_argument3(A)) ->
+    try foo2(A,A) of
+	R -> R
+    catch
+	?macro_argument3(B) ->
+	    B;
+	error:?macro_argument3(B) ->
+	    B;
+	error:?macro_argument3(B):_ ->
+	    B
+    end.
-- 
2.26.2

openSUSE Build Service is sponsored by