File 2162-Eliminate-dialyzer-crashing-when-analyzing-try-catch.patch of Package erlang

From 55326873686afcd1596d2dd4a8c026219a44c63e Mon Sep 17 00:00:00 2001
From: =?UTF-8?q?Bj=C3=B6rn=20Gustavsson?= <bjorn@erlang.org>
Date: Tue, 12 Jan 2021 06:53:20 +0100
Subject: [PATCH] Eliminate dialyzer crashing when analyzing try/catch

In commit 8a9a443a454327cbf17120f63664caa0973e9050 introduced by
https://github.com/erlang/otp/pull/2662, a restriction regarding
variables in try/catch was lifted, allowing variables bound
between `try` and `of` to be used later:

    baz() ->
        try Bar = 0 of
          _ -> Bar
        after 0
        end.

(In OTP 23 and earlier that would be a compilation error because `Bar`
would be considered unsafe.)

The lifted restriction was not properly handled by dialyzer. Attempting
to analyze the the following module would crash dialyzer:

    -module(dialyzer_bug).
    -export([main/0]).

    main() ->
        try A = foo() of
            _ -> A
        after ok
        end.

    foo() -> 1.

https://bugs.erlang.org/browse/ERL-1454
---
 lib/dialyzer/src/dialyzer_dataflow.erl        | 48 +++++++++++--------
 .../test/small_SUITE_data/results/try2        |  2 +
 .../test/small_SUITE_data/src/try2.erl        | 46 ++++++++++++++++++
 3 files changed, 75 insertions(+), 21 deletions(-)
 create mode 100644 lib/dialyzer/test/small_SUITE_data/results/try2
 create mode 100644 lib/dialyzer/test/small_SUITE_data/src/try2.erl

diff --git a/lib/dialyzer/src/dialyzer_dataflow.erl b/lib/dialyzer/src/dialyzer_dataflow.erl
index a95bfeb49e..2f25da2a37 100644
--- a/lib/dialyzer/src/dialyzer_dataflow.erl
+++ b/lib/dialyzer/src/dialyzer_dataflow.erl
@@ -1143,27 +1143,33 @@ handle_try(Tree, Map, State) ->
   Vars = cerl:try_vars(Tree),
   Body = cerl:try_body(Tree),
   Handler = cerl:try_handler(Tree),
-  {State1, Map1, ArgType} = traverse(Arg, Map, State),
-  Map2 = mark_as_fresh(Vars, Map1),
-  {SuccState, SuccMap, SuccType} =
-    case bind_pat_vars(Vars, t_to_tlist(ArgType), [], Map2, State1) of
-      {error, _, _, _, _} ->
-	{State1, map__new(), t_none()};
-      {SuccMap1, VarTypes} ->
-	%% Try to bind the argument. Will only succeed if
-	%% it is a simple structured term.
-	SuccMap2 =
-	  case bind_pat_vars_reverse([Arg], [t_product(VarTypes)], [],
-				     SuccMap1, State1) of
-	    {error, _, _, _, _} -> SuccMap1;
-	    {SM, _} -> SM
-	  end,
-	traverse(Body, SuccMap2, State1)
-    end,
-  ExcMap1 = mark_as_fresh(EVars, Map),
-  {State2, ExcMap2, HandlerType} = traverse(Handler, ExcMap1, SuccState),
-  TryType = t_sup(SuccType, HandlerType),
-  {State2, join_maps([ExcMap2, SuccMap], Map1), TryType}.
+  {State1, Map1, ArgType} = SMA = traverse(Arg, Map, State),
+  TypeList = t_to_tlist(ArgType),
+  if
+    length(Vars) =/= length(TypeList) ->
+      SMA;
+    true ->
+      Map2 = mark_as_fresh(Vars, Map1),
+      {SuccState, SuccMap, SuccType} =
+        case bind_pat_vars(Vars, TypeList, [], Map2, State1) of
+          {error, _, _, _, _} ->
+            {State1, map__new(), t_none()};
+          {SuccMap1, VarTypes} ->
+            %% Try to bind the argument. Will only succeed if
+            %% it is a simple structured term.
+            SuccMap2 =
+              case bind_pat_vars_reverse([Arg], [t_product(VarTypes)], [],
+                                         SuccMap1, State1) of
+                {error, _, _, _, _} -> SuccMap1;
+                {SM, _} -> SM
+              end,
+            traverse(Body, SuccMap2, State1)
+        end,
+      ExcMap1 = mark_as_fresh(EVars, Map),
+      {State2, ExcMap2, HandlerType} = traverse(Handler, ExcMap1, SuccState),
+      TryType = t_sup(SuccType, HandlerType),
+      {State2, join_maps([ExcMap2, SuccMap], Map1), TryType}
+  end.
 
 %%----------------------------------------
 
diff --git a/lib/dialyzer/test/small_SUITE_data/results/try2 b/lib/dialyzer/test/small_SUITE_data/results/try2
new file mode 100644
index 0000000000..e96cb22057
--- /dev/null
+++ b/lib/dialyzer/test/small_SUITE_data/results/try2
@@ -0,0 +1,2 @@
+
+try2.erl:33: Function run3/2 has no local return
diff --git a/lib/dialyzer/test/small_SUITE_data/src/try2.erl b/lib/dialyzer/test/small_SUITE_data/src/try2.erl
new file mode 100644
index 0000000000..e85b241ca9
--- /dev/null
+++ b/lib/dialyzer/test/small_SUITE_data/src/try2.erl
@@ -0,0 +1,46 @@
+-module(try2).
+-export([main/0, run/2, run2/2, run3/2]).
+
+main() ->
+    try A = foo() of
+        _ -> A
+    after ok
+    end.
+
+foo() -> 1.
+
+run(Module, Args) ->
+    try
+        Module:main(Args),
+        halt(0)
+    catch
+        Class:Reason:StackTrace ->
+            format_exception(Class, Reason, StackTrace)
+    end.
+
+run2(Module, Args) ->
+    try
+        Result = Module:main(Args),
+        ok
+    of
+        ok ->
+            Result
+    catch
+        Class:Reason:StackTrace ->
+            format_exception(Class, Reason, StackTrace)
+    end.
+
+run3(Module, Args) ->                           %Function run3/2 has no local return
+    try
+        Result = error(badarg),
+        ok
+    of
+        ok ->
+            Result
+    catch
+        Class:Reason:StackTrace ->
+            format_exception(Class, Reason, StackTrace)
+    end.
+
+format_exception(Class, Reason, StackTrace) ->
+    erlang:raise(Class, Reason, StackTrace).
-- 
2.26.2

openSUSE Build Service is sponsored by