Skip to content

Commit

Permalink
Deprecate old catches in stdlib
Browse files Browse the repository at this point in the history
  • Loading branch information
richcarl committed Jan 10, 2025
1 parent af5d68d commit 7999140
Show file tree
Hide file tree
Showing 36 changed files with 72 additions and 1 deletion.
2 changes: 1 addition & 1 deletion lib/stdlib/src/Makefile
Original file line number Diff line number Diff line change
Expand Up @@ -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)
Expand Down
2 changes: 2 additions & 0 deletions lib/stdlib/src/beam_lib.erl
Original file line number Diff line number Diff line change
Expand Up @@ -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.
Expand Down
2 changes: 2 additions & 0 deletions lib/stdlib/src/c.erl
Original file line number Diff line number Diff line change
Expand Up @@ -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.
Expand Down
2 changes: 2 additions & 0 deletions lib/stdlib/src/dets.erl
Original file line number Diff line number Diff line change
Expand Up @@ -86,6 +86,8 @@ message.
`m:ets`, `m:mnesia`, `m:qlc`
""".

-compile(nowarn_deprecated_catch).

%% Disk based linear hashing lookup dictionary.

%% Public.
Expand Down
2 changes: 2 additions & 0 deletions lib/stdlib/src/dets_utils.erl
Original file line number Diff line number Diff line change
Expand Up @@ -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.

Expand Down
2 changes: 2 additions & 0 deletions lib/stdlib/src/dets_v9.erl
Original file line number Diff line number Diff line change
Expand Up @@ -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.

Expand Down
2 changes: 2 additions & 0 deletions lib/stdlib/src/edlin.erl
Original file line number Diff line number Diff line change
Expand Up @@ -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.

Expand Down
3 changes: 3 additions & 0 deletions lib/stdlib/src/edlin_type_suggestion.erl
Original file line number Diff line number Diff line change
Expand Up @@ -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]).

Expand Down
2 changes: 2 additions & 0 deletions lib/stdlib/src/epp.erl
Original file line number Diff line number Diff line change
Expand Up @@ -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]).
Expand Down
2 changes: 2 additions & 0 deletions lib/stdlib/src/erl_eval.erl
Original file line number Diff line number Diff line change
Expand Up @@ -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,
Expand Down
2 changes: 2 additions & 0 deletions lib/stdlib/src/erl_parse.yrl
Original file line number Diff line number Diff line change
Expand Up @@ -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]).
Expand Down
2 changes: 2 additions & 0 deletions lib/stdlib/src/ets.erl
Original file line number Diff line number Diff line change
Expand Up @@ -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

Expand Down
2 changes: 2 additions & 0 deletions lib/stdlib/src/eval_bits.erl
Original file line number Diff line number Diff line change
Expand Up @@ -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,
Expand Down
2 changes: 2 additions & 0 deletions lib/stdlib/src/file_sorter.erl
Original file line number Diff line number Diff line change
Expand Up @@ -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,
Expand Down
2 changes: 2 additions & 0 deletions lib/stdlib/src/filelib.erl
Original file line number Diff line number Diff line change
Expand Up @@ -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]).
Expand Down
2 changes: 2 additions & 0 deletions lib/stdlib/src/gen_event.erl
Original file line number Diff line number Diff line change
Expand Up @@ -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,
Expand Down
2 changes: 2 additions & 0 deletions lib/stdlib/src/gen_fsm.erl
Original file line number Diff line number Diff line change
Expand Up @@ -359,6 +359,8 @@ that implements the state machine.
%%%
%%% ---------------------------------------------------

-compile(nowarn_deprecated_catch).

-include("logger.hrl").

-export([start/3, start/4,
Expand Down
2 changes: 2 additions & 0 deletions lib/stdlib/src/gen_server.erl
Original file line number Diff line number Diff line change
Expand Up @@ -182,6 +182,8 @@ using exit signals.
%%%
%%% ---------------------------------------------------

-compile(nowarn_deprecated_catch).

%% API
-export([start/3, start/4,
start_link/3, start_link/4,
Expand Down
2 changes: 2 additions & 0 deletions lib/stdlib/src/io.erl
Original file line number Diff line number Diff line change
Expand Up @@ -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,
Expand Down
2 changes: 2 additions & 0 deletions lib/stdlib/src/io_lib.erl
Original file line number Diff line number Diff line change
Expand Up @@ -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]).
Expand Down
2 changes: 2 additions & 0 deletions lib/stdlib/src/io_lib_format.erl
Original file line number Diff line number Diff line change
Expand Up @@ -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,
Expand Down
2 changes: 2 additions & 0 deletions lib/stdlib/src/io_lib_fread.erl
Original file line number Diff line number Diff line change
Expand Up @@ -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]).
Expand Down
2 changes: 2 additions & 0 deletions lib/stdlib/src/log_mf_h.erl
Original file line number Diff line number Diff line change
Expand Up @@ -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]).
Expand Down
2 changes: 2 additions & 0 deletions lib/stdlib/src/ms_transform.erl
Original file line number Diff line number Diff line change
Expand Up @@ -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]).

Expand Down
2 changes: 2 additions & 0 deletions lib/stdlib/src/peer.erl
Original file line number Diff line number Diff line change
Expand Up @@ -52,6 +52,8 @@
-moduledoc(#{since => "OTP 25.0"}).
-endif.

-compile(nowarn_deprecated_catch).

%% API
-export([
start_link/0,
Expand Down
2 changes: 2 additions & 0 deletions lib/stdlib/src/proc_lib.erl
Original file line number Diff line number Diff line change
Expand Up @@ -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
Expand Down
2 changes: 2 additions & 0 deletions lib/stdlib/src/qlc.erl
Original file line number Diff line number Diff line change
Expand Up @@ -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,
Expand Down
2 changes: 2 additions & 0 deletions lib/stdlib/src/qlc_pt.erl
Original file line number Diff line number Diff line change
Expand Up @@ -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,
Expand Down
2 changes: 2 additions & 0 deletions lib/stdlib/src/re.erl
Original file line number Diff line number Diff line change
Expand Up @@ -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.
Expand Down
2 changes: 2 additions & 0 deletions lib/stdlib/src/shell.erl
Original file line number Diff line number Diff line change
Expand Up @@ -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]).
Expand Down
2 changes: 2 additions & 0 deletions lib/stdlib/src/slave.erl
Original file line number Diff line number Diff line change
Expand Up @@ -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,
Expand Down
2 changes: 2 additions & 0 deletions lib/stdlib/src/sofs.erl
Original file line number Diff line number Diff line change
Expand Up @@ -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,
Expand Down
2 changes: 2 additions & 0 deletions lib/stdlib/src/supervisor.erl
Original file line number Diff line number Diff line change
Expand Up @@ -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
Expand Down
2 changes: 2 additions & 0 deletions lib/stdlib/src/sys.erl
Original file line number Diff line number Diff line change
Expand Up @@ -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,
Expand Down
2 changes: 2 additions & 0 deletions lib/stdlib/src/unicode.erl
Original file line number Diff line number Diff line change
Expand Up @@ -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,
Expand Down
2 changes: 2 additions & 0 deletions lib/stdlib/src/zip.erl
Original file line number Diff line number Diff line change
Expand Up @@ -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,
Expand Down

0 comments on commit 7999140

Please sign in to comment.