File 3941-Make-CATCH-macro-syntactical.patch of Package erlang

From 846ae26a5a6ef961ab9e5b2d06abfe2dde0e1517 Mon Sep 17 00:00:00 2001
From: =?UTF-8?q?Micha=C5=82=20Muska=C5=82a?= <micmus@whatsapp.com>
Date: Tue, 22 Mar 2022 15:19:15 +0000
Subject: [PATCH] Make ?CATCH macro "syntactical"
MIME-Version: 1.0
Content-Type: text/plain; charset=UTF-8
Content-Transfer-Encoding: 8bit

Hiding a keyword behind a macro messes up syntax highlighting and
some tools that rely on analysing code without expanding macros.

Additionally the `catch` keyword has a fairly surprising precedence,
wrapping it in a macro with a proper argument makes it less error prone.

Debugging is still possible by changing the macro to just

    -define(CATCH(Expr), Expr).

Co-authored-by: Björn Gustavsson <bgustavsson@gmail.com>
---
 erts/preloaded/src/prim_zip.erl |  6 +++---
 lib/stdlib/src/zip.erl          | 18 +++++++++---------
 2 files changed, 12 insertions(+), 12 deletions(-)

diff --git a/erts/preloaded/src/prim_zip.erl b/erts/preloaded/src/prim_zip.erl
index ca5cfec0e3..395b37cef6 100644
--- a/erts/preloaded/src/prim_zip.erl
+++ b/erts/preloaded/src/prim_zip.erl
@@ -42,7 +42,7 @@
 -define(READ_BLOCK_SIZE, 16*1024).
 
 %% for debugging, to turn off catch
--define(CATCH, catch).
+-define(CATCH(Expr), (catch (Expr))).
 
 -record(primzip_file,
 	{name,
@@ -203,7 +203,7 @@ get_z_all(?DEFLATED, Compressed, Z, _F) ->
     ok = zlib:inflateInit(Z, -?MAX_WBITS),
     Uncompressed = zlib:inflate(Z, Compressed),
     %%_CRC = zlib:crc32(Z),
-    ?CATCH zlib:inflateEnd(Z),
+    _ = ?CATCH(zlib:inflateEnd(Z)),
     erlang:iolist_to_binary(Uncompressed); % {erlang:iolist_to_binary(Uncompressed), CRC}
 get_z_all(?STORED, Stored, _Z, _F) ->
     %%CRC0 = zlib:crc32(Z, <<>>),
@@ -350,7 +350,7 @@ prim_file_io({file_info, F}, _) ->
 	{error, E} -> throw(E)
     end;
 prim_file_io({open, FN, Opts}, _) ->
-    case ?CATCH prim_file:open(FN, Opts++[binary]) of
+    case prim_file:open(FN, Opts++[binary]) of
 	{ok, H} ->
 	    H;
 	{error, E} ->
diff --git a/lib/stdlib/src/zip.erl b/lib/stdlib/src/zip.erl
index 4c606761ba..68a678f735 100644
--- a/lib/stdlib/src/zip.erl
+++ b/lib/stdlib/src/zip.erl
@@ -51,7 +51,7 @@
 -define(WRITE_BLOCK_SIZE, 8*1024).
 
 %% for debugging, to turn off catch
--define(CATCH, catch).
+-define(CATCH(Expr), (catch (Expr))).
 
 %% option sets
 -record(unzip_opts, {
@@ -227,7 +227,7 @@ openzip_open(F) ->
     openzip_open(F, []).
 
 openzip_open(F, Options) ->
-    case ?CATCH do_openzip_open(F, Options) of
+    case ?CATCH(do_openzip_open(F, Options)) of
 	{ok, OpenZip} ->
 	    {ok, OpenZip};
 	Error ->
@@ -252,7 +252,7 @@ do_openzip_open(F, Options) ->
 
 %% retrieve all files from an open archive
 openzip_get(OpenZip) ->
-    case ?CATCH do_openzip_get(OpenZip) of
+    case ?CATCH(do_openzip_get(OpenZip)) of
 	{ok, Result} -> {ok, Result};
 	Error -> {error, Error}
     end.
@@ -269,7 +269,7 @@ do_openzip_get(_) ->
 
 %% retrieve a file from an open archive
 openzip_get(FileName, OpenZip) ->
-    case ?CATCH do_openzip_get(FileName, OpenZip) of
+    case ?CATCH(do_openzip_get(FileName, OpenZip)) of
 	{ok, Result} -> {ok, Result};
 	Error -> {error, Error}
     end.
@@ -372,7 +372,7 @@ unzip(F) -> unzip(F, []).
                 | {error, {Name :: file:name(), Reason :: term()}}).
 
 unzip(F, Options) ->
-    case ?CATCH do_unzip(F, Options) of
+    case ?CATCH(do_unzip(F, Options)) of
 	{ok, R} -> {ok, R};
 	Error -> {error, Error}
     end.
@@ -452,7 +452,7 @@ zip(F, Files) -> zip(F, Files, []).
                 | {error, Reason :: term()}).
 
 zip(F, Files, Options) ->
-    case ?CATCH do_zip(F, Files, Options) of
+    case ?CATCH(do_zip(F, Files, Options)) of
 	{ok, R} -> {ok, R};
 	Error -> {error, Error}
     end.
@@ -496,7 +496,7 @@ list_dir(F) -> list_dir(F, []).
       Option :: cooked).
 
 list_dir(F, Options) ->
-    case ?CATCH do_list_dir(F, Options) of
+    case ?CATCH(do_list_dir(F, Options)) of
 	{ok, R} -> {ok, R};
 	Error -> {error, Error}
     end.
@@ -521,7 +521,7 @@ t(F) when is_record(F, openzip) -> openzip_t(F);
 t(F) -> t(F, fun raw_short_print_info_etc/5).
 
 t(F, RawPrint) ->
-    case ?CATCH do_t(F, RawPrint) of
+    case ?CATCH(do_t(F, RawPrint)) of
 	ok -> ok;
 	Error -> {error, Error}
     end.
@@ -1543,7 +1543,7 @@ get_z_data(?DEFLATED, In0, FileName, CompSize, Input, Output, OpO, Z) ->
     Out0 = Output({open, FileName, [write | OpO]}, []),
     CRC0 = 0,
     {In1, Out1, UncompSize, CRC} = get_z_data_loop(CompSize, 0, In0, Out0, Input, Output, CRC0, Z),
-    ?CATCH zlib:inflateEnd(Z),
+    _ = ?CATCH(zlib:inflateEnd(Z)),
     Out2 = Output({close, FileName}, Out1),
     {Out2, In1, CRC, UncompSize};
 get_z_data(?STORED, In0, FileName, CompSize, Input, Output, OpO, _Z) ->
-- 
2.34.1

openSUSE Build Service is sponsored by