File 1153-Deprecate-old-catches-in-stdlib.patch of Package erlang

From 8cfd165ec99017aa1fbd88970db993f6cb8af076 Mon Sep 17 00:00:00 2001
From: Richard Carlsson <carlsson.richard@gmail.com>
Date: Sun, 8 Dec 2024 19:27:17 +0100
Subject: [PATCH 3/5] Deprecate old catches in stdlib

---
 lib/stdlib/src/Makefile                  | 2 +-
 lib/stdlib/src/beam_lib.erl              | 2 ++
 lib/stdlib/src/c.erl                     | 2 ++
 lib/stdlib/src/dets.erl                  | 2 ++
 lib/stdlib/src/dets_utils.erl            | 2 ++
 lib/stdlib/src/dets_v9.erl               | 2 ++
 lib/stdlib/src/edlin.erl                 | 2 ++
 lib/stdlib/src/edlin_type_suggestion.erl | 3 +++
 lib/stdlib/src/epp.erl                   | 2 ++
 lib/stdlib/src/erl_eval.erl              | 2 ++
 lib/stdlib/src/erl_parse.yrl             | 2 ++
 lib/stdlib/src/ets.erl                   | 2 ++
 lib/stdlib/src/eval_bits.erl             | 2 ++
 lib/stdlib/src/file_sorter.erl           | 2 ++
 lib/stdlib/src/filelib.erl               | 2 ++
 lib/stdlib/src/gen_event.erl             | 2 ++
 lib/stdlib/src/gen_fsm.erl               | 2 ++
 lib/stdlib/src/gen_server.erl            | 2 ++
 lib/stdlib/src/io.erl                    | 2 ++
 lib/stdlib/src/io_lib.erl                | 2 ++
 lib/stdlib/src/io_lib_format.erl         | 2 ++
 lib/stdlib/src/io_lib_fread.erl          | 2 ++
 lib/stdlib/src/log_mf_h.erl              | 2 ++
 lib/stdlib/src/ms_transform.erl          | 2 ++
 lib/stdlib/src/peer.erl                  | 2 ++
 lib/stdlib/src/proc_lib.erl              | 2 ++
 lib/stdlib/src/qlc.erl                   | 2 ++
 lib/stdlib/src/qlc_pt.erl                | 2 ++
 lib/stdlib/src/re.erl                    | 2 ++
 lib/stdlib/src/shell.erl                 | 2 ++
 lib/stdlib/src/slave.erl                 | 2 ++
 lib/stdlib/src/sofs.erl                  | 2 ++
 lib/stdlib/src/supervisor.erl            | 2 ++
 lib/stdlib/src/sys.erl                   | 2 ++
 lib/stdlib/src/unicode.erl               | 2 ++
 lib/stdlib/src/zip.erl                   | 2 ++
 36 files changed, 72 insertions(+), 1 deletion(-)

diff --git a/lib/stdlib/src/Makefile b/lib/stdlib/src/Makefile
index 9423528573..a6bb6bfd8c 100644
--- a/lib/stdlib/src/Makefile
+++ b/lib/stdlib/src/Makefile
@@ -171,7 +171,7 @@ endif
 # FLAGS
 # ----------------------------------------------------
 
-ERL_COMPILE_FLAGS += -Werror
+ERL_COMPILE_FLAGS += -Werror  +warn_deprecated_catch
 ERL_COMPILE_FLAGS += -I../include -I../../kernel/include
 
 ifeq ($(ERL_DETERMINISTIC),yes)
diff --git a/lib/stdlib/src/beam_lib.erl b/lib/stdlib/src/beam_lib.erl
index 4acae18ac7..532752beec 100644
--- a/lib/stdlib/src/beam_lib.erl
+++ b/lib/stdlib/src/beam_lib.erl
@@ -148,6 +148,8 @@ providing one key for module `t` and another key for all other modules:
 """.
 -behaviour(gen_server).
 
+-compile(nowarn_deprecated_catch).
+
 -include_lib("kernel/include/eep48.hrl").
 
 %% Avoid warning for local function error/1 clashing with autoimported BIF.
diff --git a/lib/stdlib/src/c.erl b/lib/stdlib/src/c.erl
index 85d5a07630..730b1f93cf 100644
--- a/lib/stdlib/src/c.erl
+++ b/lib/stdlib/src/c.erl
@@ -34,6 +34,8 @@ commands.
 `m:filename`, `m:compile`, `m:erlang`, `m:yecc`, `m:xref`
 """.
 
+-compile(nowarn_deprecated_catch).
+
 -include_lib("kernel/include/eep48.hrl").
 
 %% Utilities to use from shell.
diff --git a/lib/stdlib/src/dets.erl b/lib/stdlib/src/dets.erl
index 7f2e382a83..7f03b0b823 100644
--- a/lib/stdlib/src/dets.erl
+++ b/lib/stdlib/src/dets.erl
@@ -86,6 +86,8 @@ message.
 `m:ets`, `m:mnesia`, `m:qlc`
 """.
 
+-compile(nowarn_deprecated_catch).
+
 %% Disk based linear hashing lookup dictionary.
 
 %% Public.
diff --git a/lib/stdlib/src/dets_utils.erl b/lib/stdlib/src/dets_utils.erl
index 39ae4cbbdd..450036c7df 100644
--- a/lib/stdlib/src/dets_utils.erl
+++ b/lib/stdlib/src/dets_utils.erl
@@ -20,6 +20,8 @@
 -module(dets_utils).
 -moduledoc false.
 
+-compile(nowarn_deprecated_catch).
+
 %% Utility functions common to several dets file formats.
 %% To be used from modules dets and dets_v9 only.
 
diff --git a/lib/stdlib/src/dets_v9.erl b/lib/stdlib/src/dets_v9.erl
index 1e80985347..527d14e8d8 100644
--- a/lib/stdlib/src/dets_v9.erl
+++ b/lib/stdlib/src/dets_v9.erl
@@ -21,6 +21,8 @@
 -moduledoc false.
 -compile([{nowarn_deprecated_function, [{erlang,phash,2}]}]).
 
+-compile(nowarn_deprecated_catch).
+
 %% Dets files, implementation part. This module handles version 9.
 %% To be called from dets.erl only.
 
diff --git a/lib/stdlib/src/edlin.erl b/lib/stdlib/src/edlin.erl
index 567e47835b..ce4a6cd008 100644
--- a/lib/stdlib/src/edlin.erl
+++ b/lib/stdlib/src/edlin.erl
@@ -177,6 +177,8 @@ supports multiple lines.
 """.
 -moduledoc(#{since => "OTP 26.1"}).
 
+-compile(nowarn_deprecated_catch).
+
 %% A simple Emacs-like line editor.
 %% About Latin-1 characters: see the beginning of erl_scan.erl.
 
diff --git a/lib/stdlib/src/edlin_type_suggestion.erl b/lib/stdlib/src/edlin_type_suggestion.erl
index 1dcbb53b0a..903d9c3fdd 100644
--- a/lib/stdlib/src/edlin_type_suggestion.erl
+++ b/lib/stdlib/src/edlin_type_suggestion.erl
@@ -19,6 +19,9 @@
 %%
 -module(edlin_type_suggestion).
 -moduledoc false.
+
+-compile(nowarn_deprecated_catch).
+
 -include_lib("kernel/include/eep48.hrl").
 -export([type_tree/4, get_arity/3, get_atoms/3, get_types/3, get_types/4, get_function_type/4, print_type/3]).
 
diff --git a/lib/stdlib/src/epp.erl b/lib/stdlib/src/epp.erl
index bde54ea751..9a135ae7db 100644
--- a/lib/stdlib/src/epp.erl
+++ b/lib/stdlib/src/epp.erl
@@ -64,6 +64,8 @@ Module:format_error(ErrorDescriptor)
 `m:erl_parse`
 """.
 
+-compile(nowarn_deprecated_catch).
+
 %% An Erlang code preprocessor.
 
 -export([open/1,open/2,open/3,close/1,format_error/1]).
diff --git a/lib/stdlib/src/erl_eval.erl b/lib/stdlib/src/erl_eval.erl
index 9e362190ef..e752dc3484 100644
--- a/lib/stdlib/src/erl_eval.erl
+++ b/lib/stdlib/src/erl_eval.erl
@@ -125,6 +125,8 @@ the local function handler argument. A possible use is to call
 to be called.
 """.
 
+-compile(nowarn_deprecated_catch).
+
 %% An evaluator for Erlang abstract syntax.
 
 -export([exprs/2,exprs/3,exprs/4,expr/2,expr/3,expr/4,expr/5,
diff --git a/lib/stdlib/src/erl_parse.yrl b/lib/stdlib/src/erl_parse.yrl
index 090f74d7ad..308a728ba0 100644
--- a/lib/stdlib/src/erl_parse.yrl
+++ b/lib/stdlib/src/erl_parse.yrl
@@ -778,6 +778,8 @@ This function is usually called implicitly when an ErrorInfo structure is
 processed (see section [Error Information](#module-error-information)).
 """).
 
+-compile(nowarn_deprecated_catch).
+
 -export([parse_form/1,parse_exprs/1,parse_term/1]).
 -export([normalise/1,abstract/1,tokens/1,tokens/2]).
 -export([abstract/2]).
diff --git a/lib/stdlib/src/ets.erl b/lib/stdlib/src/ets.erl
index 4f92e3cf05..be63b6a1f4 100644
--- a/lib/stdlib/src/ets.erl
+++ b/lib/stdlib/src/ets.erl
@@ -226,6 +226,8 @@ A match specifications with excessive nesting will cause a
 [`system_limit`](`m:ets#ets_failures`) error exception to be raised.
 """.
 
+-compile(nowarn_deprecated_catch).
+
 %% Interface to the Term store BIF's
 %% ets == Erlang Term Store
 
diff --git a/lib/stdlib/src/eval_bits.erl b/lib/stdlib/src/eval_bits.erl
index ca80451949..4f6b20c87b 100644
--- a/lib/stdlib/src/eval_bits.erl
+++ b/lib/stdlib/src/eval_bits.erl
@@ -21,6 +21,8 @@
 -module(eval_bits).
 -moduledoc false.
 
+-compile(nowarn_deprecated_catch).
+
 %% Avoid warning for local function error/1 clashing with autoimported BIF.
 -compile({no_auto_import,[error/1]}).
 -export([expr_grp/3,expr_grp/4,match_bits/6,
diff --git a/lib/stdlib/src/file_sorter.erl b/lib/stdlib/src/file_sorter.erl
index 7127529217..a2ef53ff21 100644
--- a/lib/stdlib/src/file_sorter.erl
+++ b/lib/stdlib/src/file_sorter.erl
@@ -172,6 +172,8 @@ The possible values of `Reason` returned when an error occurs are:
   term.
 """.
 
+-compile(nowarn_deprecated_catch).
+
 %% Avoid warning for local function error/2 clashing with autoimported BIF.
 -compile({no_auto_import,[error/2]}).
 -export([sort/1, sort/2, sort/3, 
diff --git a/lib/stdlib/src/filelib.erl b/lib/stdlib/src/filelib.erl
index 51b6e21f76..e51a02c4a8 100644
--- a/lib/stdlib/src/filelib.erl
+++ b/lib/stdlib/src/filelib.erl
@@ -49,6 +49,8 @@ For more information about raw filenames, see the `m:file` module.
 > filenames.
 """.
 
+-compile(nowarn_deprecated_catch).
+
 %% File utilities.
 -export([wildcard/1, wildcard/2, is_dir/1, is_file/1, is_regular/1]).
 -export([fold_files/5, last_modified/1, file_size/1, ensure_dir/1, ensure_path/1]).
diff --git a/lib/stdlib/src/gen_event.erl b/lib/stdlib/src/gen_event.erl
index 5c4e930e91..f4cfc931bd 100644
--- a/lib/stdlib/src/gen_event.erl
+++ b/lib/stdlib/src/gen_event.erl
@@ -128,6 +128,8 @@ or if bad arguments are specified.
 %%%       above monitor_return() in gen.erl!
 %%%
 
+-compile(nowarn_deprecated_catch).
+
 -export([start/0, start/1, start/2,
          start_link/0, start_link/1, start_link/2,
          start_monitor/0, start_monitor/1, start_monitor/2,
diff --git a/lib/stdlib/src/gen_fsm.erl b/lib/stdlib/src/gen_fsm.erl
index 113d00166d..5e232f79a6 100644
--- a/lib/stdlib/src/gen_fsm.erl
+++ b/lib/stdlib/src/gen_fsm.erl
@@ -359,6 +359,8 @@ that implements the state machine.
 %%%
 %%% ---------------------------------------------------
 
+-compile(nowarn_deprecated_catch).
+
 -include("logger.hrl").
 
 -export([start/3, start/4,
diff --git a/lib/stdlib/src/gen_server.erl b/lib/stdlib/src/gen_server.erl
index b01df7555f..7c18705dad 100644
--- a/lib/stdlib/src/gen_server.erl
+++ b/lib/stdlib/src/gen_server.erl
@@ -182,6 +182,8 @@ using exit signals.
 %%%
 %%% ---------------------------------------------------
 
+-compile(nowarn_deprecated_catch).
+
 %% API
 -export([start/3, start/4,
 	 start_link/3, start_link/4,
diff --git a/lib/stdlib/src/io.erl b/lib/stdlib/src/io.erl
index 7cfe90e5db..6c167d77fa 100644
--- a/lib/stdlib/src/io.erl
+++ b/lib/stdlib/src/io.erl
@@ -66,6 +66,8 @@ Module:format_error(ErrorDescriptor)
 ```
 """.
 
+-compile(nowarn_deprecated_catch).
+
 -export([put_chars/1,put_chars/2,nl/0,nl/1,
 	 get_chars/2,get_chars/3,get_line/1,get_line/2,
 	 get_password/0, get_password/1,
diff --git a/lib/stdlib/src/io_lib.erl b/lib/stdlib/src/io_lib.erl
index 90e426ca0b..550142680d 100644
--- a/lib/stdlib/src/io_lib.erl
+++ b/lib/stdlib/src/io_lib.erl
@@ -69,6 +69,8 @@ functions are flat, they can be deep lists. Function `lists:flatten/1` can be
 used for flattening deep lists.
 """.
 
+-compile(nowarn_deprecated_catch).
+
 -export([fwrite/2,fwrite/3,fread/2,fread/3,format/2,format/3]).
 -export([scan_format/2,unscan_format/1,build_text/1,build_text/2]).
 -export([print/1,print/4,indentation/2]).
diff --git a/lib/stdlib/src/io_lib_format.erl b/lib/stdlib/src/io_lib_format.erl
index 422ab8b4d6..6e552a3503 100644
--- a/lib/stdlib/src/io_lib_format.erl
+++ b/lib/stdlib/src/io_lib_format.erl
@@ -20,6 +20,8 @@
 -module(io_lib_format).
 -moduledoc false.
 
+-compile(nowarn_deprecated_catch).
+
 %% Formatting functions of io library.
 
 -export([fwrite/2,fwrite/3,fwrite_g/1,indentation/2,scan/2,unscan/1,
diff --git a/lib/stdlib/src/io_lib_fread.erl b/lib/stdlib/src/io_lib_fread.erl
index b67bb2a67b..8eb4b8d5a9 100644
--- a/lib/stdlib/src/io_lib_fread.erl
+++ b/lib/stdlib/src/io_lib_fread.erl
@@ -20,6 +20,8 @@
 -module(io_lib_fread).
 -moduledoc false.
 
+-compile(nowarn_deprecated_catch).
+
 %% Formatted input functions of io library.
 
 -export([fread/2,fread/3]).
diff --git a/lib/stdlib/src/log_mf_h.erl b/lib/stdlib/src/log_mf_h.erl
index 980255e3b2..7091d0bec6 100644
--- a/lib/stdlib/src/log_mf_h.erl
+++ b/lib/stdlib/src/log_mf_h.erl
@@ -35,6 +35,8 @@ one file called `index`, and report files `1, 2, ...`.
 `m:gen_event`, `m:rb`
 """.
 
+-compile(nowarn_deprecated_catch).
+
 -behaviour(gen_event).
 
 -export([init/3, init/4]).
diff --git a/lib/stdlib/src/ms_transform.erl b/lib/stdlib/src/ms_transform.erl
index 5eb834e058..1c1ef23a92 100644
--- a/lib/stdlib/src/ms_transform.erl
+++ b/lib/stdlib/src/ms_transform.erl
@@ -20,6 +20,8 @@
 -module(ms_transform).
 -moduledoc({file, "../doc/src/ms_transform.md"}).
 
+-compile(nowarn_deprecated_catch).
+
 -export([format_error/1,transform_from_shell/3,
          parse_transform/2,parse_transform_info/0]).
 
diff --git a/lib/stdlib/src/peer.erl b/lib/stdlib/src/peer.erl
index fc657fb891..ce1737e6b7 100644
--- a/lib/stdlib/src/peer.erl
+++ b/lib/stdlib/src/peer.erl
@@ -52,6 +52,8 @@
 -moduledoc(#{since => "OTP 25.0"}).
 -endif.
 
+-compile(nowarn_deprecated_catch).
+
 %% API
 -export([
          start_link/0,
diff --git a/lib/stdlib/src/proc_lib.erl b/lib/stdlib/src/proc_lib.erl
index 1a5dbd2169..231ef6a49f 100644
--- a/lib/stdlib/src/proc_lib.erl
+++ b/lib/stdlib/src/proc_lib.erl
@@ -60,6 +60,8 @@ processes that terminate as a result of this process terminating.
 `m:logger`
 """.
 
+-compile(nowarn_deprecated_catch).
+
 %% This module is used to set some initial information
 %% in each created process. 
 %% Then a process terminates the Reason is checked and
diff --git a/lib/stdlib/src/qlc.erl b/lib/stdlib/src/qlc.erl
index ec6c8d27f1..2c1bb0eb44 100644
--- a/lib/stdlib/src/qlc.erl
+++ b/lib/stdlib/src/qlc.erl
@@ -26,6 +26,8 @@
 
 %% External exports 
 
+-compile(nowarn_deprecated_catch).
+
 %% Avoid warning for local function error/1 clashing with autoimported BIF.
 -compile({no_auto_import,[error/1]}).
 -export([parse_transform/2,
diff --git a/lib/stdlib/src/qlc_pt.erl b/lib/stdlib/src/qlc_pt.erl
index eae3655c45..a7bd91d425 100644
--- a/lib/stdlib/src/qlc_pt.erl
+++ b/lib/stdlib/src/qlc_pt.erl
@@ -20,6 +20,8 @@
 -module(qlc_pt).
 -moduledoc false.
 
+-compile(nowarn_deprecated_catch).
+
 %%% Purpose: Implements the qlc Parse Transform.
 
 -export([parse_transform/2, transform_from_evaluator/2,
diff --git a/lib/stdlib/src/re.erl b/lib/stdlib/src/re.erl
index 31103b3931..4dbedfd33a 100644
--- a/lib/stdlib/src/re.erl
+++ b/lib/stdlib/src/re.erl
@@ -23,6 +23,8 @@
 
 -export_type([mp/0, compile_options/0, options/0]).
 
+-compile(nowarn_deprecated_catch).
+
 -doc """
 Opaque data type containing a compiled regular expression.
 
diff --git a/lib/stdlib/src/shell.erl b/lib/stdlib/src/shell.erl
index 85bce919bc..623e6618b4 100644
--- a/lib/stdlib/src/shell.erl
+++ b/lib/stdlib/src/shell.erl
@@ -20,6 +20,8 @@
 -module(shell).
 -moduledoc({file, "../doc/src/shell.md"}).
 
+-compile(nowarn_deprecated_catch).
+
 -export([start/0, start/1, start/2, server/1, server/2, history/1, results/1]).
 -export([get_state/0, get_function/2]).
 -export([start_restricted/1, stop_restricted/0]).
diff --git a/lib/stdlib/src/slave.erl b/lib/stdlib/src/slave.erl
index be4c1be1fd..f40db7a35b 100644
--- a/lib/stdlib/src/slave.erl
+++ b/lib/stdlib/src/slave.erl
@@ -68,6 +68,8 @@ The master node must be alive.
 %% (the example is for tcsh)
 
 
+-compile(nowarn_deprecated_catch).
+
 -export([pseudo/1,
 	 pseudo/2,
 	 start/1, start/2, start/3,
diff --git a/lib/stdlib/src/sofs.erl b/lib/stdlib/src/sofs.erl
index 0141c6d08c..be0a2819a4 100644
--- a/lib/stdlib/src/sofs.erl
+++ b/lib/stdlib/src/sofs.erl
@@ -20,6 +20,8 @@
 -module(sofs).
 -moduledoc({file, "../doc/src/sofs.md"}).
 
+-compile(nowarn_deprecated_catch).
+
 -export([from_term/1, from_term/2, from_external/2, empty_set/0,
          is_type/1, set/1, set/2, from_sets/1, relation/1, relation/2,
          a_function/1, a_function/2, family/1, family/2,
diff --git a/lib/stdlib/src/supervisor.erl b/lib/stdlib/src/supervisor.erl
index 64517e0454..0ed4cec9f2 100644
--- a/lib/stdlib/src/supervisor.erl
+++ b/lib/stdlib/src/supervisor.erl
@@ -277,6 +277,8 @@ but the map is preferred.
 `m:gen_event`, `m:gen_statem`, `m:gen_server`, `m:sys`
 """.
 
+-compile(nowarn_deprecated_catch).
+
 -behaviour(gen_server).
 
 %% External exports
diff --git a/lib/stdlib/src/sys.erl b/lib/stdlib/src/sys.erl
index 5302a0da4b..5abe646bf5 100644
--- a/lib/stdlib/src/sys.erl
+++ b/lib/stdlib/src/sys.erl
@@ -77,6 +77,8 @@ the process itself to format these events.
                  [{function,<<"Process Implementation Functions">>},
                   {callback,<<"Process Implementation Functions">>}]}).
 
+-compile(nowarn_deprecated_catch).
+
 %% External exports
 -export([suspend/1, suspend/2, resume/1, resume/2,
 	 get_status/1, get_status/2,
diff --git a/lib/stdlib/src/unicode.erl b/lib/stdlib/src/unicode.erl
index 727fb27bb9..c91858771c 100644
--- a/lib/stdlib/src/unicode.erl
+++ b/lib/stdlib/src/unicode.erl
@@ -57,6 +57,8 @@ normalization can be found in the
 [Unicode FAQ](http://unicode.org/faq/normalization.html).
 """.
 
+-compile(nowarn_deprecated_catch).
+
 -export([characters_to_list/1, characters_to_list_int/2,
 	 characters_to_binary/1, characters_to_binary_int/2,
 	 characters_to_binary/3,
diff --git a/lib/stdlib/src/zip.erl b/lib/stdlib/src/zip.erl
index 4293500502..069a3db613 100644
--- a/lib/stdlib/src/zip.erl
+++ b/lib/stdlib/src/zip.erl
@@ -62,6 +62,8 @@ convention, add `.zip` to the filename.
 -define(ERL_TAR_COMPATIBILITY, ~"erl_tar compatibility functions").
 -moduledoc(#{ titles => [{function, ?ERL_TAR_COMPATIBILITY}]}).
 
+-compile(nowarn_deprecated_catch).
+
 %% Basic api
 -export([unzip/1, unzip/2, extract/1, extract/2,
 	 zip/2, zip/3, create/2, create/3, foldl/3,
-- 
2.43.0

openSUSE Build Service is sponsored by