Skip to content

Commit 4911d41

Browse files
authored
Merge pull request #10161 from richcarl/replace-zf
Deprecate lists:zf/2 and remove uses in OTP OTP-19783
2 parents 841002c + 6661354 commit 4911d41

28 files changed

+116
-98
lines changed
80 Bytes
Binary file not shown.

lib/dialyzer/test/r9c_SUITE_data/src/mnesia/mnesia_controller.erl

Lines changed: 12 additions & 12 deletions
Original file line numberDiff line numberDiff line change
@@ -1,4 +1,11 @@
1-
%% ``Licensed under the Apache License, Version 2.0 (the "License");
1+
%%
2+
%% %CopyrightBegin%
3+
%%
4+
%% SPDX-License-Identifier: Apache-2.0
5+
%%
6+
%% Copyright Ericsson AB 1996-2025. All Rights Reserved.
7+
%%
8+
%% Licensed under the Apache License, Version 2.0 (the "License");
29
%% you may not use this file except in compliance with the License.
310
%% You may obtain a copy of the License at
411
%%
@@ -10,11 +17,9 @@
1017
%% See the License for the specific language governing permissions and
1118
%% limitations under the License.
1219
%%
13-
%% The Initial Developer of the Original Code is Ericsson Utvecklings AB.
14-
%% Portions created by Ericsson are Copyright 1999, Ericsson Utvecklings
15-
%% AB. All Rights Reserved.''
20+
%% %CopyrightEnd%
1621
%%
17-
%% $Id: mnesia_controller.erl,v 1.3 2010/03/04 13:54:19 maria Exp $
22+
1823
%% The mnesia_init process loads tables from local disc or from
1924
%% another nodes. It also coordinates updates of the info about
2025
%% where we can read and write tables.
@@ -28,11 +33,6 @@
2833
%% consistent replica and we have received mnesia_down from all
2934
%% other nodes holding the table. Then we let the mnesia_init
3035
%% process enter its normal working state.
31-
%%
32-
%% When we need to load a table we append a request to the load
33-
%% request queue. All other requests are regarded as high priority
34-
%% and are processed immediately (e.g. update table whereabouts).
35-
%% We processes the load request queue as a "background" job..
3636

3737
-module(mnesia_controller).
3838

@@ -1375,15 +1375,15 @@ initial_safe_loads() ->
13751375
Downs = [],
13761376
Tabs = val({schema, local_tables}) -- [schema],
13771377
LastC = fun(T) -> last_consistent_replica(T, Downs) end,
1378-
lists:zf(LastC, Tabs);
1378+
lists:filtermap(LastC, Tabs);
13791379

13801380
disc_copies ->
13811381
Downs = mnesia_recover:get_mnesia_downs(),
13821382
dbg_out("mnesia_downs = ~p~n", [Downs]),
13831383

13841384
Tabs = val({schema, local_tables}) -- [schema],
13851385
LastC = fun(T) -> last_consistent_replica(T, Downs) end,
1386-
lists:zf(LastC, Tabs)
1386+
lists:filtermap(LastC, Tabs)
13871387
end.
13881388

13891389
last_consistent_replica(Tab, Downs) ->

lib/dialyzer/test/r9c_SUITE_data/src/mnesia/mnesia_frag.erl

Lines changed: 22 additions & 22 deletions
Original file line numberDiff line numberDiff line change
@@ -1,24 +1,24 @@
1-
%%% ``Licensed under the Apache License, Version 2.0 (the "License");
2-
%%% you may not use this file except in compliance with the License.
3-
%%% You may obtain a copy of the License at
4-
%%%
5-
%%% http://www.apache.org/licenses/LICENSE-2.0
6-
%%%
7-
%%% Unless required by applicable law or agreed to in writing, software
8-
%%% distributed under the License is distributed on an "AS IS" BASIS,
9-
%%% WITHOUT WARRANTIES OR CONDITIONS OF ANY KIND, either express or implied.
10-
%%% See the License for the specific language governing permissions and
11-
%%% limitations under the License.
12-
%%%
13-
%%% The Initial Developer of the Original Code is Ericsson Utvecklings AB.
14-
%%% Portions created by Ericsson are Copyright 1999, Ericsson Utvecklings
15-
%%% AB. All Rights Reserved.''
16-
%%%
17-
%%% $Id: mnesia_frag.erl,v 1.1 2008/12/17 09:53:38 mikpe Exp $
18-
%%%----------------------------------------------------------------------
19-
%%% Purpose : Support tables so large that they need
20-
%%% to be divided into several fragments.
21-
%%%----------------------------------------------------------------------
1+
%%
2+
%% %CopyrightBegin%
3+
%%
4+
%% SPDX-License-Identifier: Apache-2.0
5+
%%
6+
%% Copyright Ericsson AB 1996-2025. All Rights Reserved.
7+
%%
8+
%% Licensed under the Apache License, Version 2.0 (the "License");
9+
%% you may not use this file except in compliance with the License.
10+
%% You may obtain a copy of the License at
11+
%%
12+
%% http://www.apache.org/licenses/LICENSE-2.0
13+
%%
14+
%% Unless required by applicable law or agreed to in writing, software
15+
%% distributed under the License is distributed on an "AS IS" BASIS,
16+
%% WITHOUT WARRANTIES OR CONDITIONS OF ANY KIND, either express or implied.
17+
%% See the License for the specific language governing permissions and
18+
%% limitations under the License.
19+
%%
20+
%% %CopyrightEnd%
21+
%%
2222

2323
%header_doc_include
2424

@@ -700,7 +700,7 @@ replace_frag_hash(Cs, FH) when record(FH, frag_state) ->
700700
true
701701
end
702702
end,
703-
Props = lists:zf(Fun, Cs#cstruct.frag_properties),
703+
Props = lists:filtermap(Fun, Cs#cstruct.frag_properties),
704704
Cs#cstruct{frag_properties = Props}.
705705

706706
%% Adjust table info before split

lib/dialyzer/test/r9c_SUITE_data/src/mnesia/mnesia_lib.erl

Lines changed: 16 additions & 16 deletions
Original file line numberDiff line numberDiff line change
@@ -1,4 +1,11 @@
1-
%% ``Licensed under the Apache License, Version 2.0 (the "License");
1+
%%
2+
%% %CopyrightBegin%
3+
%%
4+
%% SPDX-License-Identifier: Apache-2.0
5+
%%
6+
%% Copyright Ericsson AB 1996-2025. All Rights Reserved.
7+
%%
8+
%% Licensed under the Apache License, Version 2.0 (the "License");
29
%% you may not use this file except in compliance with the License.
310
%% You may obtain a copy of the License at
411
%%
@@ -10,14 +17,8 @@
1017
%% See the License for the specific language governing permissions and
1118
%% limitations under the License.
1219
%%
13-
%% The Initial Developer of the Original Code is Ericsson Utvecklings AB.
14-
%% Portions created by Ericsson are Copyright 1999, Ericsson Utvecklings
15-
%% AB. All Rights Reserved.''
20+
%% %CopyrightEnd%
1621
%%
17-
%% $Id: mnesia_lib.erl,v 1.3 2009/07/01 15:45:40 kostis Exp $
18-
%% This module contains all sorts of various which doesn't fit
19-
%% anywhere else. Basically everything is exported.
20-
2122
-module(mnesia_lib).
2223

2324
-include("mnesia.hrl").
@@ -30,7 +31,6 @@
3031
add/2,
3132
add_list/2,
3233
all_nodes/0,
33-
%% catch_val/1,
3434
cleanup_tmp_files/1,
3535
copy_file/2,
3636
copy_holders/1,
@@ -442,7 +442,7 @@ ensure_loaded(Appl) ->
442442

443443
local_active_tables() ->
444444
Tabs = val({schema, local_tables}),
445-
lists:zf(fun(Tab) -> active_here(Tab) end, Tabs).
445+
lists:filtermap(fun(Tab) -> active_here(Tab) end, Tabs).
446446

447447
active_tables() ->
448448
Tabs = val({schema, tables}),
@@ -452,7 +452,7 @@ active_tables() ->
452452
_ -> {true, Tab}
453453
end
454454
end,
455-
lists:zf(F, Tabs).
455+
lists:filtermap(F, Tabs).
456456

457457
etype(X) when integer(X) -> integer;
458458
etype([]) -> nil;
@@ -588,7 +588,7 @@ mkcore(CrashInfo) ->
588588
term_to_binary(Core).
589589

590590
procs() ->
591-
Fun = fun(P) -> {P, (catch lists:zf(fun proc_info/1, process_info(P)))} end,
591+
Fun = fun(P) -> {P, (catch lists:filtermap(fun proc_info/1, process_info(P)))} end,
592592
lists:map(Fun, processes()).
593593

594594
proc_info({registered_name, Val}) -> {true, Val};
@@ -626,7 +626,7 @@ relatives() ->
626626
Pid -> {true, {Name, Pid, catch process_info(Pid)}}
627627
end
628628
end,
629-
lists:zf(Info, mnesia:ms()).
629+
lists:filtermap(Info, mnesia:ms()).
630630

631631
workers({workers, Loader, Sender, Dumper}) ->
632632
Info = fun({Name, Pid}) ->
@@ -635,7 +635,7 @@ workers({workers, Loader, Sender, Dumper}) ->
635635
Pid -> {true, {Name, Pid, catch process_info(Pid)}}
636636
end
637637
end,
638-
lists:zf(Info, [{loader, Loader}, {sender, Sender}, {dumper, Dumper}]).
638+
lists:filtermap(Info, [{loader, Loader}, {sender, Sender}, {dumper, Dumper}]).
639639

640640
locking_procs(LockList) when list(LockList) ->
641641
Tids = [element(1, Lock) || Lock <- LockList],
@@ -649,7 +649,7 @@ locking_procs(LockList) when list(LockList) ->
649649
false
650650
end
651651
end,
652-
lists:zf(Info, UT).
652+
lists:filtermap(Info, UT).
653653

654654
view() ->
655655
Bin = mkcore({crashinfo, {"view only~n", []}}),
@@ -693,7 +693,7 @@ vcore() ->
693693
{ok, Cwd} = file:get_cwd(),
694694
case file:list_dir(Cwd) of
695695
{ok, Files}->
696-
CoreFiles = lists:sort(lists:zf(Filter, Files)),
696+
CoreFiles = lists:sort(lists:filtermap(Filter, Files)),
697697
show("Mnesia core files: ~p~n", [CoreFiles]),
698698
vcore(lists:last(CoreFiles));
699699
Error ->

lib/kernel/src/application_controller.erl

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -49,7 +49,7 @@
4949
%% Test exports, only to be used from the test suites
5050
-export([test_change_apps/2]).
5151

52-
-import(lists, [zf/2, map/2, foreach/2, foldl/3,
52+
-import(lists, [filtermap/2, map/2, foreach/2, foldl/3,
5353
keyfind/3, keydelete/3, keyreplace/4]).
5454

5555
-include("application_master.hrl").
@@ -889,7 +889,7 @@ handle_call({config_change, EnvBefore}, _From, S) ->
889889
{reply, R, S};
890890

891891
handle_call(which_applications, _From, S) ->
892-
Reply = zf(fun({Name, Id}) ->
892+
Reply = filtermap(fun({Name, Id}) ->
893893
case Id of
894894
{distributed, _Node} ->
895895
false;

lib/kernel/src/dist_ac.erl

Lines changed: 6 additions & 6 deletions
Original file line numberDiff line numberDiff line change
@@ -40,7 +40,7 @@
4040
code_change/3, send_timeout/3]).
4141
-export([info/0]).
4242

43-
-import(lists, [zf/2, filter/2, map/2, foreach/2, foldl/3, mapfoldl/3,
43+
-import(lists, [filtermap/2, filter/2, map/2, foreach/2, foldl/3, mapfoldl/3,
4444
keysearch/3, keydelete/3, keyreplace/4, member/2]).
4545

4646
-define(AC, application_controller).
@@ -508,7 +508,7 @@ handle_info({ac_application_stopped, AppName}, S) ->
508508
%%-----------------------------------------------------------------
509509
handle_info({dist_ac_new_node, _Vsn, Node, HisAppls, []}, S) ->
510510
Appls = S#state.appls,
511-
MyStarted = zf(fun(Appl) when Appl#appl.id =:= local ->
511+
MyStarted = filtermap(fun(Appl) when Appl#appl.id =:= local ->
512512
{true, {node(), Appl#appl.name}};
513513
(_) ->
514514
false
@@ -623,7 +623,7 @@ handle_info({nodedown, Node}, S) ->
623623
(_) -> false
624624
end,
625625
S#state.appls),
626-
Appls2 = zf(fun(Appl) when Appl#appl.id =:= {distributed, Node} ->
626+
Appls2 = filtermap(fun(Appl) when Appl#appl.id =:= {distributed, Node} ->
627627
case lists:member(Appl#appl.name, AppNames) of
628628
true ->
629629
{true, Appl#appl{id = {failover, Node}}};
@@ -1419,7 +1419,7 @@ do_dist_change_update(Appls, AppName, NewTime, NewNodes) ->
14191419

14201420
%% Merge his Permissions with mine.
14211421
dist_merge(MyAppls, HisAppls, HisNode) ->
1422-
zf(fun(Appl) ->
1422+
filtermap(fun(Appl) ->
14231423
#appl{name = AppName, run = Run} = Appl,
14241424
% #appl{name = AppName, nodes = Nodes, run = Run} = Appl,
14251425
% HeIsMember = lists:member(HisNode, flat_nodes(Nodes)),
@@ -1442,7 +1442,7 @@ dist_merge(MyAppls, HisAppls, HisNode) ->
14421442
dist_get_runnable_nodes(Appls, AppName) ->
14431443
case keysearch(AppName, #appl.name, Appls) of
14441444
{value, #appl{run = Run}} ->
1445-
zf(fun({Node, true}) -> {true, Node};
1445+
filtermap(fun({Node, true}) -> {true, Node};
14461446
(_) -> false
14471447
end, Run);
14481448
false ->
@@ -1473,7 +1473,7 @@ is_loaded(AppName, #state{appls = Appls}) ->
14731473
end.
14741474

14751475
dist_get_runnable(Appls) ->
1476-
zf(fun(#appl{name = AppName, run = Run}) ->
1476+
filtermap(fun(#appl{name = AppName, run = Run}) ->
14771477
case keysearch(node(), 1, Run) of
14781478
{value, {_, true}} -> {true, AppName};
14791479
_ -> false

lib/mnesia/src/mnesia_controller.erl

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -1597,15 +1597,15 @@ initial_safe_loads() ->
15971597
Downs = [],
15981598
Tabs = val({schema, local_tables}) -- [schema],
15991599
LastC = fun(T) -> last_consistent_replica(T, Downs) end,
1600-
lists:zf(LastC, Tabs);
1600+
lists:filtermap(LastC, Tabs);
16011601

16021602
disc_copies ->
16031603
Downs = mnesia_recover:get_mnesia_downs(),
16041604
dbg_out("mnesia_downs = ~p~n", [Downs]),
16051605

16061606
Tabs = val({schema, local_tables}) -- [schema],
16071607
LastC = fun(T) -> last_consistent_replica(T, Downs) end,
1608-
lists:zf(LastC, Tabs)
1608+
lists:filtermap(LastC, Tabs)
16091609
end.
16101610

16111611
last_consistent_replica(Tab, Downs) ->

lib/mnesia/src/mnesia_frag.erl

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -895,7 +895,7 @@ replace_frag_hash(Cs, FH) when is_record(FH, frag_state) ->
895895
true
896896
end
897897
end,
898-
Props = lists:zf(Fun, Cs#cstruct.frag_properties),
898+
Props = lists:filtermap(Fun, Cs#cstruct.frag_properties),
899899
Cs#cstruct{frag_properties = Props}.
900900

901901
%% Adjust table info before split

lib/mnesia/src/mnesia_lib.erl

Lines changed: 9 additions & 9 deletions
Original file line numberDiff line numberDiff line change
@@ -531,7 +531,7 @@ ensure_loaded(Appl) ->
531531

532532
local_active_tables() ->
533533
Tabs = val({schema, local_tables}),
534-
lists:zf(fun(Tab) -> active_here(Tab) end, Tabs).
534+
lists:filtermap(fun(Tab) -> active_here(Tab) end, Tabs).
535535

536536
active_tables() ->
537537
Tabs = val({schema, tables}),
@@ -541,7 +541,7 @@ active_tables() ->
541541
_ -> {true, Tab}
542542
end
543543
end,
544-
lists:zf(F, Tabs).
544+
lists:filtermap(F, Tabs).
545545

546546
etype(X) when is_integer(X) -> integer;
547547
etype([]) -> nil;
@@ -715,7 +715,7 @@ mkcore(CrashInfo) ->
715715
term_to_binary(Core).
716716

717717
procs() ->
718-
Fun = fun(P) -> {P, (?CATCH(lists:zf(fun proc_info/1, process_info(P))))} end,
718+
Fun = fun(P) -> {P, (?CATCH(lists:filtermap(fun proc_info/1, process_info(P))))} end,
719719
lists:map(Fun, processes()).
720720

721721
proc_info({registered_name, Val}) -> {true, Val};
@@ -765,7 +765,7 @@ relatives() ->
765765
Pid -> {true, {Name, Pid, proc_dbg_info(Pid)}}
766766
end
767767
end,
768-
lists:zf(Info, mnesia:ms()).
768+
lists:filtermap(Info, mnesia:ms()).
769769

770770
workers({workers, Loaders, Senders, Dumper}) ->
771771
Info = fun({Pid, {send_table, Tab, _Receiver, _St}}) ->
@@ -781,9 +781,9 @@ workers({workers, Loaders, Senders, Dumper}) ->
781781
Pid -> {true, {Name, Pid, proc_dbg_info(Pid)}}
782782
end
783783
end,
784-
SInfo = lists:zf(Info, Senders),
785-
Linfo = lists:zf(Info, Loaders),
786-
[{senders, SInfo},{loader, Linfo}|lists:zf(Info, [{dumper, Dumper}])].
784+
SInfo = lists:filtermap(Info, Senders),
785+
Linfo = lists:filtermap(Info, Loaders),
786+
[{senders, SInfo},{loader, Linfo}|lists:filtermap(Info, [{dumper, Dumper}])].
787787

788788
locking_procs(LockList) when is_list(LockList) ->
789789
Tids = [element(3, Lock) || Lock <- LockList],
@@ -797,7 +797,7 @@ locking_procs(LockList) when is_list(LockList) ->
797797
false
798798
end
799799
end,
800-
lists:zf(Info, UT).
800+
lists:filtermap(Info, UT).
801801

802802
proc_dbg_info(Pid) ->
803803
try
@@ -849,7 +849,7 @@ vcore() ->
849849
{ok, Cwd} = file:get_cwd(),
850850
case file:list_dir(Cwd) of
851851
{ok, Files}->
852-
CoreFiles = lists:sort(lists:zf(Filter, Files)),
852+
CoreFiles = lists:sort(lists:filtermap(Filter, Files)),
853853
show("Mnesia core files: ~tp~n", [CoreFiles]),
854854
vcore(lists:last(CoreFiles));
855855
Error ->

lib/mnesia/test/mnesia_install_test.erl

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -291,7 +291,7 @@ transform_some_records(Tab1, _Tab2, Old) ->
291291
Filter = fun(Rec) when element(1, Rec) == Tab1 -> {true, Fun(Rec)};
292292
(_) -> true
293293
end,
294-
lists:sort(lists:zf(Filter, Old)).
294+
lists:sort(lists:filtermap(Filter, Old)).
295295

296296
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
297297

0 commit comments

Comments
 (0)