File 1071-Deprecate-lists-zf-2-and-remove-uses-in-OTP.patch of Package erlang
From cb643a2f6c120927fc648c70e95fe47d99b7b51e Mon Sep 17 00:00:00 2001
From: Richard Carlsson <carlsson.richard@gmail.com>
Date: Wed, 3 Sep 2025 14:48:42 +0200
Subject: [PATCH 1/3] Deprecate lists:zf/2 and remove uses in OTP
---
.../src/mnesia/mnesia_controller.erl | 24 +++++-----
.../r9c_SUITE_data/src/mnesia/mnesia_frag.erl | 44 +++++++++----------
.../r9c_SUITE_data/src/mnesia/mnesia_lib.erl | 32 +++++++-------
lib/kernel/src/application_controller.erl | 4 +-
lib/kernel/src/dist_ac.erl | 12 ++---
lib/mnesia/src/mnesia_controller.erl | 4 +-
lib/mnesia/src/mnesia_frag.erl | 2 +-
lib/mnesia/src/mnesia_lib.erl | 18 ++++----
lib/mnesia/test/mnesia_install_test.erl | 2 +-
lib/mnesia/test/mnesia_test_lib.erl | 4 +-
lib/reltool/src/reltool_app_win.erl | 4 +-
lib/reltool/src/reltool_server.erl | 2 +-
lib/reltool/src/reltool_target.erl | 6 +--
lib/reltool/src/reltool_utils.erl | 2 +-
lib/runtime_tools/src/dbg.erl | 2 +-
lib/sasl/src/rb.erl | 2 +-
lib/sasl/src/release_handler.erl | 4 +-
lib/sasl/src/release_handler_1.erl | 4 +-
lib/sasl/src/systools_lib.erl | 9 ++--
lib/sasl/src/systools_rc.erl | 2 +-
lib/snmp/src/compile/snmpc_lib.erl | 2 +-
lib/stdlib/src/gen_event.erl | 2 +-
lib/stdlib/src/lists.erl | 8 ++--
system/doc/general_info/DEPRECATIONS | 5 +++
system/doc/general_info/deprecations_29.md | 9 ++++
25 files changed, 111 insertions(+), 98 deletions(-)
create mode 100644 system/doc/general_info/deprecations_29.md
diff --git a/lib/dialyzer/test/r9c_SUITE_data/src/mnesia/mnesia_controller.erl b/lib/dialyzer/test/r9c_SUITE_data/src/mnesia/mnesia_controller.erl
index cf6a4c19cf..ddfe60ed80 100644
--- a/lib/dialyzer/test/r9c_SUITE_data/src/mnesia/mnesia_controller.erl
+++ b/lib/dialyzer/test/r9c_SUITE_data/src/mnesia/mnesia_controller.erl
@@ -1,4 +1,11 @@
-%% ``Licensed under the Apache License, Version 2.0 (the "License");
+%%
+%% %CopyrightBegin%
+%%
+%% SPDX-License-Identifier: Apache-2.0
+%%
+%% Copyright Ericsson AB 1996-2025. All Rights Reserved.
+%%
+%% Licensed under the Apache License, Version 2.0 (the "License");
%% you may not use this file except in compliance with the License.
%% You may obtain a copy of the License at
%%
@@ -10,11 +17,9 @@
%% See the License for the specific language governing permissions and
%% limitations under the License.
%%
-%% The Initial Developer of the Original Code is Ericsson Utvecklings AB.
-%% Portions created by Ericsson are Copyright 1999, Ericsson Utvecklings
-%% AB. All Rights Reserved.''
+%% %CopyrightEnd%
%%
-%% $Id: mnesia_controller.erl,v 1.3 2010/03/04 13:54:19 maria Exp $
+
%% The mnesia_init process loads tables from local disc or from
%% another nodes. It also coordinates updates of the info about
%% where we can read and write tables.
@@ -28,11 +33,6 @@
%% consistent replica and we have received mnesia_down from all
%% other nodes holding the table. Then we let the mnesia_init
%% process enter its normal working state.
-%%
-%% When we need to load a table we append a request to the load
-%% request queue. All other requests are regarded as high priority
-%% and are processed immediately (e.g. update table whereabouts).
-%% We processes the load request queue as a "background" job..
-module(mnesia_controller).
@@ -1375,7 +1375,7 @@ initial_safe_loads() ->
Downs = [],
Tabs = val({schema, local_tables}) -- [schema],
LastC = fun(T) -> last_consistent_replica(T, Downs) end,
- lists:zf(LastC, Tabs);
+ lists:filtermap(LastC, Tabs);
disc_copies ->
Downs = mnesia_recover:get_mnesia_downs(),
@@ -1383,7 +1383,7 @@ initial_safe_loads() ->
Tabs = val({schema, local_tables}) -- [schema],
LastC = fun(T) -> last_consistent_replica(T, Downs) end,
- lists:zf(LastC, Tabs)
+ lists:filtermap(LastC, Tabs)
end.
last_consistent_replica(Tab, Downs) ->
diff --git a/lib/dialyzer/test/r9c_SUITE_data/src/mnesia/mnesia_frag.erl b/lib/dialyzer/test/r9c_SUITE_data/src/mnesia/mnesia_frag.erl
index 04b9c1ea2f..640ee7d288 100644
--- a/lib/dialyzer/test/r9c_SUITE_data/src/mnesia/mnesia_frag.erl
+++ b/lib/dialyzer/test/r9c_SUITE_data/src/mnesia/mnesia_frag.erl
@@ -1,24 +1,24 @@
-%%% ``Licensed under the Apache License, Version 2.0 (the "License");
-%%% you may not use this file except in compliance with the License.
-%%% You may obtain a copy of the License at
-%%%
-%%% http://www.apache.org/licenses/LICENSE-2.0
-%%%
-%%% Unless required by applicable law or agreed to in writing, software
-%%% distributed under the License is distributed on an "AS IS" BASIS,
-%%% WITHOUT WARRANTIES OR CONDITIONS OF ANY KIND, either express or implied.
-%%% See the License for the specific language governing permissions and
-%%% limitations under the License.
-%%%
-%%% The Initial Developer of the Original Code is Ericsson Utvecklings AB.
-%%% Portions created by Ericsson are Copyright 1999, Ericsson Utvecklings
-%%% AB. All Rights Reserved.''
-%%%
-%%% $Id: mnesia_frag.erl,v 1.1 2008/12/17 09:53:38 mikpe Exp $
-%%%----------------------------------------------------------------------
-%%% Purpose : Support tables so large that they need
-%%% to be divided into several fragments.
-%%%----------------------------------------------------------------------
+%%
+%% %CopyrightBegin%
+%%
+%% SPDX-License-Identifier: Apache-2.0
+%%
+%% Copyright Ericsson AB 1996-2025. All Rights Reserved.
+%%
+%% Licensed under the Apache License, Version 2.0 (the "License");
+%% you may not use this file except in compliance with the License.
+%% You may obtain a copy of the License at
+%%
+%% http://www.apache.org/licenses/LICENSE-2.0
+%%
+%% Unless required by applicable law or agreed to in writing, software
+%% distributed under the License is distributed on an "AS IS" BASIS,
+%% WITHOUT WARRANTIES OR CONDITIONS OF ANY KIND, either express or implied.
+%% See the License for the specific language governing permissions and
+%% limitations under the License.
+%%
+%% %CopyrightEnd%
+%%
%header_doc_include
@@ -700,7 +700,7 @@ replace_frag_hash(Cs, FH) when record(FH, frag_state) ->
true
end
end,
- Props = lists:zf(Fun, Cs#cstruct.frag_properties),
+ Props = lists:filtermap(Fun, Cs#cstruct.frag_properties),
Cs#cstruct{frag_properties = Props}.
%% Adjust table info before split
diff --git a/lib/dialyzer/test/r9c_SUITE_data/src/mnesia/mnesia_lib.erl b/lib/dialyzer/test/r9c_SUITE_data/src/mnesia/mnesia_lib.erl
index 40b9111eea..821b765172 100644
--- a/lib/dialyzer/test/r9c_SUITE_data/src/mnesia/mnesia_lib.erl
+++ b/lib/dialyzer/test/r9c_SUITE_data/src/mnesia/mnesia_lib.erl
@@ -1,4 +1,11 @@
-%% ``Licensed under the Apache License, Version 2.0 (the "License");
+%%
+%% %CopyrightBegin%
+%%
+%% SPDX-License-Identifier: Apache-2.0
+%%
+%% Copyright Ericsson AB 1996-2025. All Rights Reserved.
+%%
+%% Licensed under the Apache License, Version 2.0 (the "License");
%% you may not use this file except in compliance with the License.
%% You may obtain a copy of the License at
%%
@@ -10,14 +17,8 @@
%% See the License for the specific language governing permissions and
%% limitations under the License.
%%
-%% The Initial Developer of the Original Code is Ericsson Utvecklings AB.
-%% Portions created by Ericsson are Copyright 1999, Ericsson Utvecklings
-%% AB. All Rights Reserved.''
+%% %CopyrightEnd%
%%
-%% $Id: mnesia_lib.erl,v 1.3 2009/07/01 15:45:40 kostis Exp $
-%% This module contains all sorts of various which doesn't fit
-%% anywhere else. Basically everything is exported.
-
-module(mnesia_lib).
-include("mnesia.hrl").
@@ -30,7 +31,6 @@
add/2,
add_list/2,
all_nodes/0,
-%% catch_val/1,
cleanup_tmp_files/1,
copy_file/2,
copy_holders/1,
@@ -442,7 +442,7 @@ ensure_loaded(Appl) ->
local_active_tables() ->
Tabs = val({schema, local_tables}),
- lists:zf(fun(Tab) -> active_here(Tab) end, Tabs).
+ lists:filtermap(fun(Tab) -> active_here(Tab) end, Tabs).
active_tables() ->
Tabs = val({schema, tables}),
@@ -452,7 +452,7 @@ active_tables() ->
_ -> {true, Tab}
end
end,
- lists:zf(F, Tabs).
+ lists:filtermap(F, Tabs).
etype(X) when integer(X) -> integer;
etype([]) -> nil;
@@ -588,7 +588,7 @@ mkcore(CrashInfo) ->
term_to_binary(Core).
procs() ->
- Fun = fun(P) -> {P, (catch lists:zf(fun proc_info/1, process_info(P)))} end,
+ Fun = fun(P) -> {P, (catch lists:filtermap(fun proc_info/1, process_info(P)))} end,
lists:map(Fun, processes()).
proc_info({registered_name, Val}) -> {true, Val};
@@ -626,7 +626,7 @@ relatives() ->
Pid -> {true, {Name, Pid, catch process_info(Pid)}}
end
end,
- lists:zf(Info, mnesia:ms()).
+ lists:filtermap(Info, mnesia:ms()).
workers({workers, Loader, Sender, Dumper}) ->
Info = fun({Name, Pid}) ->
@@ -635,7 +635,7 @@ workers({workers, Loader, Sender, Dumper}) ->
Pid -> {true, {Name, Pid, catch process_info(Pid)}}
end
end,
- lists:zf(Info, [{loader, Loader}, {sender, Sender}, {dumper, Dumper}]).
+ lists:filtermap(Info, [{loader, Loader}, {sender, Sender}, {dumper, Dumper}]).
locking_procs(LockList) when list(LockList) ->
Tids = [element(1, Lock) || Lock <- LockList],
@@ -649,7 +649,7 @@ locking_procs(LockList) when list(LockList) ->
false
end
end,
- lists:zf(Info, UT).
+ lists:filtermap(Info, UT).
view() ->
Bin = mkcore({crashinfo, {"view only~n", []}}),
@@ -693,7 +693,7 @@ vcore() ->
{ok, Cwd} = file:get_cwd(),
case file:list_dir(Cwd) of
{ok, Files}->
- CoreFiles = lists:sort(lists:zf(Filter, Files)),
+ CoreFiles = lists:sort(lists:filtermap(Filter, Files)),
show("Mnesia core files: ~p~n", [CoreFiles]),
vcore(lists:last(CoreFiles));
Error ->
diff --git a/lib/kernel/src/application_controller.erl b/lib/kernel/src/application_controller.erl
index 5b94880eec..4e8cba1df7 100644
--- a/lib/kernel/src/application_controller.erl
+++ b/lib/kernel/src/application_controller.erl
@@ -49,7 +49,7 @@
%% Test exports, only to be used from the test suites
-export([test_change_apps/2]).
--import(lists, [zf/2, map/2, foreach/2, foldl/3,
+-import(lists, [filtermap/2, map/2, foreach/2, foldl/3,
keyfind/3, keydelete/3, keyreplace/4]).
-include("application_master.hrl").
@@ -889,7 +889,7 @@ handle_call({config_change, EnvBefore}, _From, S) ->
{reply, R, S};
handle_call(which_applications, _From, S) ->
- Reply = zf(fun({Name, Id}) ->
+ Reply = filtermap(fun({Name, Id}) ->
case Id of
{distributed, _Node} ->
false;
diff --git a/lib/kernel/src/dist_ac.erl b/lib/kernel/src/dist_ac.erl
index 043742c193..6ececbd063 100644
--- a/lib/kernel/src/dist_ac.erl
+++ b/lib/kernel/src/dist_ac.erl
@@ -40,7 +40,7 @@
code_change/3, send_timeout/3]).
-export([info/0]).
--import(lists, [zf/2, filter/2, map/2, foreach/2, foldl/3, mapfoldl/3,
+-import(lists, [filtermap/2, filter/2, map/2, foreach/2, foldl/3, mapfoldl/3,
keysearch/3, keydelete/3, keyreplace/4, member/2]).
-define(AC, application_controller).
@@ -508,7 +508,7 @@ handle_info({ac_application_stopped, AppName}, S) ->
%%-----------------------------------------------------------------
handle_info({dist_ac_new_node, _Vsn, Node, HisAppls, []}, S) ->
Appls = S#state.appls,
- MyStarted = zf(fun(Appl) when Appl#appl.id =:= local ->
+ MyStarted = filtermap(fun(Appl) when Appl#appl.id =:= local ->
{true, {node(), Appl#appl.name}};
(_) ->
false
@@ -623,7 +623,7 @@ handle_info({nodedown, Node}, S) ->
(_) -> false
end,
S#state.appls),
- Appls2 = zf(fun(Appl) when Appl#appl.id =:= {distributed, Node} ->
+ Appls2 = filtermap(fun(Appl) when Appl#appl.id =:= {distributed, Node} ->
case lists:member(Appl#appl.name, AppNames) of
true ->
{true, Appl#appl{id = {failover, Node}}};
@@ -1419,7 +1419,7 @@ do_dist_change_update(Appls, AppName, NewTime, NewNodes) ->
%% Merge his Permissions with mine.
dist_merge(MyAppls, HisAppls, HisNode) ->
- zf(fun(Appl) ->
+ filtermap(fun(Appl) ->
#appl{name = AppName, run = Run} = Appl,
% #appl{name = AppName, nodes = Nodes, run = Run} = Appl,
% HeIsMember = lists:member(HisNode, flat_nodes(Nodes)),
@@ -1442,7 +1442,7 @@ dist_merge(MyAppls, HisAppls, HisNode) ->
dist_get_runnable_nodes(Appls, AppName) ->
case keysearch(AppName, #appl.name, Appls) of
{value, #appl{run = Run}} ->
- zf(fun({Node, true}) -> {true, Node};
+ filtermap(fun({Node, true}) -> {true, Node};
(_) -> false
end, Run);
false ->
@@ -1473,7 +1473,7 @@ is_loaded(AppName, #state{appls = Appls}) ->
end.
dist_get_runnable(Appls) ->
- zf(fun(#appl{name = AppName, run = Run}) ->
+ filtermap(fun(#appl{name = AppName, run = Run}) ->
case keysearch(node(), 1, Run) of
{value, {_, true}} -> {true, AppName};
_ -> false
diff --git a/lib/mnesia/src/mnesia_controller.erl b/lib/mnesia/src/mnesia_controller.erl
index f42b05362f..dc365ea70e 100644
--- a/lib/mnesia/src/mnesia_controller.erl
+++ b/lib/mnesia/src/mnesia_controller.erl
@@ -1597,7 +1597,7 @@ initial_safe_loads() ->
Downs = [],
Tabs = val({schema, local_tables}) -- [schema],
LastC = fun(T) -> last_consistent_replica(T, Downs) end,
- lists:zf(LastC, Tabs);
+ lists:filtermap(LastC, Tabs);
disc_copies ->
Downs = mnesia_recover:get_mnesia_downs(),
@@ -1605,7 +1605,7 @@ initial_safe_loads() ->
Tabs = val({schema, local_tables}) -- [schema],
LastC = fun(T) -> last_consistent_replica(T, Downs) end,
- lists:zf(LastC, Tabs)
+ lists:filtermap(LastC, Tabs)
end.
last_consistent_replica(Tab, Downs) ->
diff --git a/lib/mnesia/src/mnesia_frag.erl b/lib/mnesia/src/mnesia_frag.erl
index 831d4d535d..110eee6163 100644
--- a/lib/mnesia/src/mnesia_frag.erl
+++ b/lib/mnesia/src/mnesia_frag.erl
@@ -895,7 +895,7 @@ replace_frag_hash(Cs, FH) when is_record(FH, frag_state) ->
true
end
end,
- Props = lists:zf(Fun, Cs#cstruct.frag_properties),
+ Props = lists:filtermap(Fun, Cs#cstruct.frag_properties),
Cs#cstruct{frag_properties = Props}.
%% Adjust table info before split
diff --git a/lib/mnesia/src/mnesia_lib.erl b/lib/mnesia/src/mnesia_lib.erl
index 8fab6a85ba..7217b9153c 100644
--- a/lib/mnesia/src/mnesia_lib.erl
+++ b/lib/mnesia/src/mnesia_lib.erl
@@ -531,7 +531,7 @@ ensure_loaded(Appl) ->
local_active_tables() ->
Tabs = val({schema, local_tables}),
- lists:zf(fun(Tab) -> active_here(Tab) end, Tabs).
+ lists:filtermap(fun(Tab) -> active_here(Tab) end, Tabs).
active_tables() ->
Tabs = val({schema, tables}),
@@ -541,7 +541,7 @@ active_tables() ->
_ -> {true, Tab}
end
end,
- lists:zf(F, Tabs).
+ lists:filtermap(F, Tabs).
etype(X) when is_integer(X) -> integer;
etype([]) -> nil;
@@ -715,7 +715,7 @@ mkcore(CrashInfo) ->
term_to_binary(Core).
procs() ->
- Fun = fun(P) -> {P, (?CATCH(lists:zf(fun proc_info/1, process_info(P))))} end,
+ Fun = fun(P) -> {P, (?CATCH(lists:filtermap(fun proc_info/1, process_info(P))))} end,
lists:map(Fun, processes()).
proc_info({registered_name, Val}) -> {true, Val};
@@ -765,7 +765,7 @@ relatives() ->
Pid -> {true, {Name, Pid, proc_dbg_info(Pid)}}
end
end,
- lists:zf(Info, mnesia:ms()).
+ lists:filtermap(Info, mnesia:ms()).
workers({workers, Loaders, Senders, Dumper}) ->
Info = fun({Pid, {send_table, Tab, _Receiver, _St}}) ->
@@ -781,9 +781,9 @@ workers({workers, Loaders, Senders, Dumper}) ->
Pid -> {true, {Name, Pid, proc_dbg_info(Pid)}}
end
end,
- SInfo = lists:zf(Info, Senders),
- Linfo = lists:zf(Info, Loaders),
- [{senders, SInfo},{loader, Linfo}|lists:zf(Info, [{dumper, Dumper}])].
+ SInfo = lists:filtermap(Info, Senders),
+ Linfo = lists:filtermap(Info, Loaders),
+ [{senders, SInfo},{loader, Linfo}|lists:filtermap(Info, [{dumper, Dumper}])].
locking_procs(LockList) when is_list(LockList) ->
Tids = [element(3, Lock) || Lock <- LockList],
@@ -797,7 +797,7 @@ locking_procs(LockList) when is_list(LockList) ->
false
end
end,
- lists:zf(Info, UT).
+ lists:filtermap(Info, UT).
proc_dbg_info(Pid) ->
try
@@ -849,7 +849,7 @@ vcore() ->
{ok, Cwd} = file:get_cwd(),
case file:list_dir(Cwd) of
{ok, Files}->
- CoreFiles = lists:sort(lists:zf(Filter, Files)),
+ CoreFiles = lists:sort(lists:filtermap(Filter, Files)),
show("Mnesia core files: ~tp~n", [CoreFiles]),
vcore(lists:last(CoreFiles));
Error ->
diff --git a/lib/mnesia/test/mnesia_install_test.erl b/lib/mnesia/test/mnesia_install_test.erl
index 862422e4be..5833ac2e9d 100644
--- a/lib/mnesia/test/mnesia_install_test.erl
+++ b/lib/mnesia/test/mnesia_install_test.erl
@@ -291,7 +291,7 @@ transform_some_records(Tab1, _Tab2, Old) ->
Filter = fun(Rec) when element(1, Rec) == Tab1 -> {true, Fun(Rec)};
(_) -> true
end,
- lists:sort(lists:zf(Filter, Old)).
+ lists:sort(lists:filtermap(Filter, Old)).
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
diff --git a/lib/mnesia/test/mnesia_test_lib.erl b/lib/mnesia/test/mnesia_test_lib.erl
index 2c227bbb24..ed0884e5ec 100644
--- a/lib/mnesia/test/mnesia_test_lib.erl
+++ b/lib/mnesia/test/mnesia_test_lib.erl
@@ -434,7 +434,7 @@ default_module(DefaultModule, TestCases) when is_list(TestCases) ->
T -> {true, {DefaultModule, T}}
end
end,
- lists:zf(Fun, TestCases).
+ lists:filtermap(Fun, TestCases).
get_suite(Module, TestCase, Config) ->
case get_suite(Module, TestCase) of
@@ -1069,7 +1069,7 @@ verify_replica_location(Tab, DiscOnly0, Ram0, Disc0, AliveNodes0) ->
ignore_dead(Nodes, AliveNodes) ->
Filter = fun(Node) -> lists:member(Node, AliveNodes) end,
- lists:sort(lists:zf(Filter, Nodes)).
+ lists:sort(lists:filtermap(Filter, Nodes)).
remote_activate_debug_fun(N, I, F, C, File, Line) ->
diff --git a/lib/reltool/src/reltool_app_win.erl b/lib/reltool/src/reltool_app_win.erl
index 2ea34d1936..5ed1e47cb0 100644
--- a/lib/reltool/src/reltool_app_win.erl
+++ b/lib/reltool/src/reltool_app_win.erl
@@ -829,8 +829,8 @@ app_to_mods(#state{xref_pid = Xref, app = App}) ->
{true, M}
end
end,
- UsedByMods = lists:zf(GetMod, App#app.used_by_mods),
- UsesMods = lists:zf(GetMod, App#app.uses_mods),
+ UsedByMods = lists:filtermap(GetMod, App#app.used_by_mods),
+ UsesMods = lists:filtermap(GetMod, App#app.uses_mods),
{
[select_image(source, M) || M <- SourceMods],
[select_image(whitelist, M) || M <- WhiteMods],
diff --git a/lib/reltool/src/reltool_server.erl b/lib/reltool/src/reltool_server.erl
index e5f88580d8..a7cac48038 100644
--- a/lib/reltool/src/reltool_server.erl
+++ b/lib/reltool/src/reltool_server.erl
@@ -1808,7 +1808,7 @@ app_dirs2([Lib | Libs], Acc) ->
false
end
end,
- Files2 = lists:zf(Filter, Files),
+ Files2 = lists:filtermap(Filter, Files),
app_dirs2(Libs, [Files2 | Acc]);
{error, Reason} ->
reltool_utils:throw_error("Illegal library ~tp: ~ts",
diff --git a/lib/reltool/src/reltool_target.erl b/lib/reltool/src/reltool_target.erl
index de5fda563c..baeae88052 100644
--- a/lib/reltool/src/reltool_target.erl
+++ b/lib/reltool/src/reltool_target.erl
@@ -878,7 +878,7 @@ strip_sys_files(Relocatable, SysFiles, Apps, ExclRegexps) ->
true
end
end,
- SysFiles2 = lists:zf(FilterErts, SysFiles),
+ SysFiles2 = lists:filtermap(FilterErts, SysFiles),
SysFiles3 = lists:foldl(fun(F, Acc) -> lists:keydelete(F, 2, Acc) end,
SysFiles2,
["releases", "lib", "bin"]),
@@ -974,7 +974,7 @@ spec_escripts(#sys{apps = Apps}, ErtsBin, BinFiles) ->
false
end
end,
- lists:flatten(lists:zf(Filter, Apps)).
+ lists:flatten(lists:filtermap(Filter, Apps)).
do_spec_escript(File, ErtsBin, BinFiles) ->
[{copy_file, EscriptExe}] = safe_lookup_spec("escript", BinFiles),
@@ -1288,7 +1288,7 @@ filter_spec(List, InclRegexps, ExclRegexps) ->
do_filter_spec("", List, InclRegexps, ExclRegexps).
do_filter_spec(Path, List, InclRegexps, ExclRegexps) when is_list(List) ->
- lists:zf(fun(File) ->
+ lists:filtermap(fun(File) ->
do_filter_spec(Path, File, InclRegexps, ExclRegexps)
end,
List);
diff --git a/lib/reltool/src/reltool_utils.erl b/lib/reltool/src/reltool_utils.erl
index b0c2b1a53c..210abf91f9 100644
--- a/lib/reltool/src/reltool_utils.erl
+++ b/lib/reltool/src/reltool_utils.erl
@@ -399,7 +399,7 @@ select_items(ListCtrl, OldItems, NewItems) ->
false -> false
end
end,
- case lists:zf(Filter, OldItems) of
+ case lists:filtermap(Filter, OldItems) of
[] ->
%% None of the old selections are valid. Select the first.
select_item(ListCtrl, NewItems);
diff --git a/lib/runtime_tools/src/dbg.erl b/lib/runtime_tools/src/dbg.erl
index 1875164735..ed9633e57f 100644
--- a/lib/runtime_tools/src/dbg.erl
+++ b/lib/runtime_tools/src/dbg.erl
@@ -2858,7 +2858,7 @@ wrap_presort(Filename, Tail) ->
Dirname = filename:dirname(Filename),
case file:list_dir(Dirname) of
{ok, Files} ->
- lists:zf(
+ lists:filtermap(
fun(N) ->
case match_front(N, Name) of
false ->
diff --git a/lib/sasl/src/rb.erl b/lib/sasl/src/rb.erl
index 018ca1631b..20a97ebf2f 100644
--- a/lib/sasl/src/rb.erl
+++ b/lib/sasl/src/rb.erl
@@ -555,7 +555,7 @@ scan_files(RptDir, Max, Type) ->
make_file_list(Dir, FirstFileNo) ->
case file:list_dir(Dir) of
{ok, FileNames} ->
- FileNumbers = lists:zf(fun(Name) ->
+ FileNumbers = lists:filtermap(fun(Name) ->
case catch list_to_integer(Name) of
Int when is_integer(Int) ->
{true, Int};
diff --git a/lib/sasl/src/release_handler.erl b/lib/sasl/src/release_handler.erl
index 922216bf09..49b5c83035 100644
--- a/lib/sasl/src/release_handler.erl
+++ b/lib/sasl/src/release_handler.erl
@@ -2250,7 +2250,7 @@ try_downgrade(ToVsn, CurrentVsn, Relup, Masters) ->
%% Status = current | tmp_current | permanent
set_status(Vsn, Status, Releases) ->
- lists:zf(fun(Release) when Release#release.vsn == Vsn,
+ lists:filtermap(fun(Release) when Release#release.vsn == Vsn,
Release#release.status == permanent ->
%% If a permanent rel is installed, it keeps its
%% permanent status (not changed to current).
@@ -2572,7 +2572,7 @@ write_releases(Dir, Releases, Masters) ->
%% us after a node restart - since we would then have a permanent
%% release running, but state set to current for a non-running
%% release.
- NewReleases = lists:zf(fun(Release) when Release#release.status == current ->
+ NewReleases = lists:filtermap(fun(Release) when Release#release.status == current ->
{true, Release#release{status = unpacked}};
(_) ->
true
diff --git a/lib/sasl/src/release_handler_1.erl b/lib/sasl/src/release_handler_1.erl
index 56c936978e..2e8cab2fb1 100644
--- a/lib/sasl/src/release_handler_1.erl
+++ b/lib/sasl/src/release_handler_1.erl
@@ -483,7 +483,7 @@ get_opt(Tag, EvalState, Default) ->
%% goes for processes that didn't respond to the suspend message.
%%-----------------------------------------------------------------
suspend(Mod, Procs, Timeout) ->
- lists:zf(fun({_Sup, _Name, Pid, Mods}) ->
+ lists:filtermap(fun({_Sup, _Name, Pid, Mods}) ->
case lists:member(Mod, Mods) of
true ->
case catch sys_suspend(Pid, Timeout) of
@@ -525,7 +525,7 @@ sys_change_code(Pid, Mod, Vsn, Extra, Timeout) ->
sys:change_code(Pid, Mod, Vsn, Extra, Timeout).
stop(Mod, Procs) ->
- lists:zf(fun({undefined, _Name, _Pid, _Mods}) ->
+ lists:filtermap(fun({undefined, _Name, _Pid, _Mods}) ->
false;
({Sup, Name, _Pid, Mods}) ->
case lists:member(Mod, Mods) of
diff --git a/lib/sasl/src/systools_lib.erl b/lib/sasl/src/systools_lib.erl
index c46976e04a..b8c03a4a83 100644
--- a/lib/sasl/src/systools_lib.erl
+++ b/lib/sasl/src/systools_lib.erl
@@ -109,7 +109,7 @@ get_path(RegPath) when is_list(RegPath) ->
_ -> false
end
end,
- flat(lists:zf(F, RegPath), []);
+ flat(lists:filtermap(F, RegPath), []);
get_path(_) ->
[].
@@ -160,7 +160,7 @@ add_dir(Name, [], true) -> %% root
_ -> []
end;
add_dir(Name, Dirs, _Root) ->
- lists:zf(fun(D0) ->
+ lists:filtermap(fun(D0) ->
D = filename:join(D0, Name),
case dir_p(D) of
true -> {true, D};
@@ -177,13 +177,12 @@ add_dirs(RegName, Dirs, Root) ->
Fun = fun(Dir) ->
regexp_match(RegName, Dir, Root)
end,
- flat(lists:zf(Fun, Dirs), []).
+ flat(lists:filtermap(Fun, Dirs), []).
%%
%% Keep all directories (names) matching RegName and
%% create full directory names Dir ++ "/" ++ Name.
%%
-%% Called from lists:zf.
%% Returns: {true, [Dir]} | false
%%
regexp_match(RegName, D0, Root) ->
@@ -205,7 +204,7 @@ regexp_match(RegName, D0, Root) ->
false
end
end,
- {true,lists:zf(FR, Files)};
+ {true,lists:filtermap(FR, Files)};
_ ->
false
end;
diff --git a/lib/sasl/src/systools_rc.erl b/lib/sasl/src/systools_rc.erl
index 9fe40ef1ad..123de3296b 100644
--- a/lib/sasl/src/systools_rc.erl
+++ b/lib/sasl/src/systools_rc.erl
@@ -989,7 +989,7 @@ format_error(E) ->
%% filtermap(F, List1) -> List2
%% F(H) -> false | true | {true, Val}
filtermap(F, List) ->
- lists:zf(F, List).
+ lists:filtermap(F, List).
%% split(F, List1) -> {List2, List3}
%% F(H) -> true | false. Preserves order.
diff --git a/lib/snmp/src/compile/snmpc_lib.erl b/lib/snmp/src/compile/snmpc_lib.erl
index aa75b0403b..179a00386b 100644
--- a/lib/snmp/src/compile/snmpc_lib.erl
+++ b/lib/snmp/src/compile/snmpc_lib.erl
@@ -985,7 +985,7 @@ get_final_mib(Name, Options) ->
?vdebug("get_final_mib -> resolve oid", []),
%% FIXME: use list comprehension instead
MibFs = lists:keysort(1,
- lists:zf(fun({module, _Mod}) -> false;
+ lists:filtermap(fun({module, _Mod}) -> false;
(MF) -> {true, resolve_oid(MF,SortedMEs)}
end, MibFuncs)),
?vtrace("get_final_mib -> "
diff --git a/lib/stdlib/src/gen_event.erl b/lib/stdlib/src/gen_event.erl
index 8db8c01c2b..f90bcd4b7c 100644
--- a/lib/stdlib/src/gen_event.erl
+++ b/lib/stdlib/src/gen_event.erl
@@ -1757,7 +1757,7 @@ system_terminate(Reason, Parent, _Debug, [ServerName, MSL, _HibernateAfterTimeou
%%-----------------------------------------------------------------
-doc false.
system_code_change([ServerName, MSL, HibernateAfterTimeout, Hib], Module, OldVsn, Extra) ->
- MSL1 = lists:zf(fun(H) when H#handler.module =:= Module ->
+ MSL1 = lists:filtermap(fun(H) when H#handler.module =:= Module ->
{ok, NewState} =
Module:code_change(OldVsn,
H#handler.state, Extra),
diff --git a/lib/stdlib/src/lists.erl b/lib/stdlib/src/lists.erl
index 4ee8abe1e0..e93f564209 100644
--- a/lib/stdlib/src/lists.erl
+++ b/lib/stdlib/src/lists.erl
@@ -85,8 +85,9 @@ An example of a typical ordering function is less than or equal to: `=</2`.
splitwith/2, takewhile/2, uniq/2,
zipwith/3, zipwith/4, zipwith3/4, zipwith3/5]).
-%% Undocumented, but used within Erlang/OTP.
+%% Undocumented old name for filtermap
-export([zf/2]).
+-deprecated([{zf,2,"use filtermap/2 instead"}]).
%% Undocumented and unused merge functions for lists sorted in reverse
%% order. They are exported so that the fundamental building blocks
@@ -2273,7 +2274,7 @@ rumerge([], []) ->
%% foldl(Function, First, List)
%% foldr(Function, Last, List)
%% filter(Predicate, List)
-%% zf(Function, List)
+%% filtermap(Function, List)
%% mapfoldl(Function, First, List)
%% mapfoldr(Function, Last, List)
%% foreach(Function, List)
@@ -2281,8 +2282,6 @@ rumerge([], []) ->
%% dropwhile(Predicate, List)
%% splitwith(Predicate, List)
%% for list programming. Function here is a 'fun'.
-%%
-%% The name zf is a joke!
%%
%% N.B. Unless where the functions actually needs it only foreach/2/3,
%% which is meant to be used for its side effects, has a defined order
@@ -2617,6 +2616,7 @@ filtermap_1(F, [Hd|Tail]) ->
filtermap_1(_F, []) ->
[].
+%% The name zf was a joke. Kept for backwards compatibility only.
-doc false.
-spec zf(fun((T) -> boolean() | {'true', X}), [T]) -> [(T | X)].
diff --git a/system/doc/general_info/DEPRECATIONS b/system/doc/general_info/DEPRECATIONS
index 73621c3b30..172ce5e996 100644
--- a/system/doc/general_info/DEPRECATIONS
+++ b/system/doc/general_info/DEPRECATIONS
@@ -36,6 +36,11 @@
# is scheduled to be removed in OTP 25.
#
+#
+# Added in OTP 29.
+#
+lists:zf/2 since=29
+
#
# Added in OTP 28.
#
diff --git a/system/doc/general_info/deprecations_29.md b/system/doc/general_info/deprecations_29.md
new file mode 100644
index 0000000000..cb0487859c
--- /dev/null
+++ b/system/doc/general_info/deprecations_29.md
@@ -0,0 +1,9 @@
+<!--
+%CopyrightBegin%
+
+SPDX-License-Identifier: Apache-2.0
+
+Copyright Ericsson AB 2025. All Rights Reserved.
+
+%CopyrightEnd%
+-->
--
2.51.0