File 0696-stdlib-Correct-the-pretty-printing-of-catch-Expr.patch of Package erlang

From 2614577081342a7ddf2fbb773fbedbd23f239722 Mon Sep 17 00:00:00 2001
From: Richard Carlsson <carlsson.richard@gmail.com>
Date: Tue, 9 Dec 2025 09:38:14 +0100
Subject: [PATCH] stdlib: Correct the pretty-printing of `catch Expr`

In 3171f2b7 and 762a18aa the precedence levels used by `erl_pp` to
format `catch Expr` was adjusted to avoid parentheses in many cases.
However, this only works in situations where the catch is on the right
of the surrounding operator, as in `Pat = catch Expr`. If the catch is
on the left, as in `(catch Expr) + 1`, the parentheses must be
preserved. The `erl_pp` prettyprinter is not clever enough to
distinguish between these situatuions, so for now we must accept some
unnecessary parentheses.

This restores the precedence level for printing and adds test cases to
validate the parsing and semantics as well as the pretty printing.
---
 lib/compiler/test/misc_SUITE.erl | 20 +++++++++++++++++---
 lib/stdlib/src/erl_parse.yrl     |  2 +-
 lib/stdlib/test/erl_pp_SUITE.erl |  9 ++++++---
 3 files changed, 24 insertions(+), 7 deletions(-)

diff --git a/lib/compiler/test/misc_SUITE.erl b/lib/compiler/test/misc_SUITE.erl
index fae01d677e..ba05bae442 100644
--- a/lib/compiler/test/misc_SUITE.erl
+++ b/lib/compiler/test/misc_SUITE.erl
@@ -26,7 +26,7 @@
 	 init_per_testcase/2,end_per_testcase/2,
 	 tobias/1,empty_string/1,md5/1,silly_coverage/1,
 	 confused_literals/1,integer_encoding/0,integer_encoding/1,
-	 override_bif/1]).
+	 override_bif/1,catch_precedence/1]).
 	 
 -include_lib("common_test/include/ct.hrl").
 
@@ -71,7 +71,7 @@ all() ->
 groups() -> 
     [{p,[parallel],
       [tobias,empty_string,silly_coverage,
-       confused_literals,override_bif]},
+       confused_literals,override_bif,catch_precedence]},
      {slow,[parallel],[integer_encoding,md5]}].
 
 init_per_suite(Config) ->
@@ -103,7 +103,21 @@ slow_group() ->
             %% Cloned module. Don't run.
             []
     end.
-    
+
+catch_precedence(Config) when is_list(Config) ->
+        %% lower than addition
+        3 = begin (catch throw(2)) + 1 end,
+        2 = begin catch throw(2) + 1 end,
+
+        %% lower than comparison
+        true = begin (catch throw(false)) =/= true end,
+        false = begin catch throw(false) =/= true end,
+
+        %% lower than send (which has the same precedence as =)
+        Pid = spawn_link(fun () -> receive stop -> ok end end),
+        false = is_pid(begin (catch throw(Pid)) ! stop end),
+        true = is_pid(begin catch throw(Pid) ! stop end).
+
 %%
 %% Functions that override new and old bif's
 %%
diff --git a/lib/stdlib/src/erl_parse.yrl b/lib/stdlib/src/erl_parse.yrl
index 8d1de8a4e0..c34bd26521 100644
--- a/lib/stdlib/src/erl_parse.yrl
+++ b/lib/stdlib/src/erl_parse.yrl
@@ -2045,7 +2045,7 @@ inop_prec('.') -> {900,900,1000}.
 
 -spec preop_prec(pre_op()) -> {0 | 600 | 700, 100 | 700 | 800}.
 
-preop_prec('catch') -> {700,100};
+preop_prec('catch') -> {0,100};
 preop_prec('+') -> {600,700};
 preop_prec('-') -> {600,700};
 preop_prec('bnot') -> {600,700};
diff --git a/lib/stdlib/test/erl_pp_SUITE.erl b/lib/stdlib/test/erl_pp_SUITE.erl
index 7c82e1c0fc..4ee4fe1a3f 100644
--- a/lib/stdlib/test/erl_pp_SUITE.erl
+++ b/lib/stdlib/test/erl_pp_SUITE.erl
@@ -1341,11 +1341,14 @@ otp_16435(_Config) ->
     CheckF("f() ->\n    << \n      (catch <<1:4>>) ||\n"
            "          A <- []\n    >>.\n"),
     CheckF("f() ->\n    [ \n     catch foo ||\n         A <- []\n    ].\n"),
-    CheckF("f() ->\n    1 = catch 1.\n"),
-    CheckF("f() ->\n    catch 1 = catch 1.\n"),
-    CheckF("f() ->\n    A = catch 1 / 0.\n"),
+    CheckF("f() ->\n    1 = (catch 1).\n"),
+    CheckF("f() ->\n    catch 1 = (catch 1).\n"),
+    CheckF("f() ->\n    A = (catch 1 / 0).\n"),
     CheckF("f() when erlang:float(3.0) ->\n    true.\n"),
     CheckF("f() ->\n    (catch 16)#{}.\n"),
+    CheckF("f() ->\n    (catch throw(false)) =/= true.\n"),
+    CheckF("f() ->\n    (catch throw(2)) + 1.\n"),
+    CheckF("f() ->\n    (catch throw(Pid)) ! stop.\n"),
 
     Check = fun(S) -> S = flat_parse_and_pp_expr(S, 0, []) end,
     Check("5 #r4.f1"),
-- 
2.51.0

openSUSE Build Service is sponsored by