Skip to content

Commit 320ad94

Browse files
committed
Eliminate exports from expression arguments
1 parent 3c1e1ad commit 320ad94

File tree

21 files changed

+98
-59
lines changed

21 files changed

+98
-59
lines changed

lib/asn1/src/asn1rtt_jer.erl

Lines changed: 2 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -122,7 +122,8 @@ encode_jer({typeinfo,{Module,Type}},Val) ->
122122
encode_jer({sof,Type},Vals) when is_list(Vals) ->
123123
[encode_jer(Type,Val)||Val <- Vals];
124124
encode_jer({choice,Choices},{Alt,Value}) ->
125-
case is_map_key(AltBin = atom_to_binary(Alt,utf8),Choices) of
125+
AltBin = atom_to_binary(Alt,utf8),
126+
case is_map_key(AltBin,Choices) of
126127
true ->
127128
EncodedVal = encode_jer(maps:get(AltBin,Choices),Value),
128129
#{AltBin => EncodedVal};

lib/common_test/src/test_server_ctrl.erl

Lines changed: 4 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -5776,13 +5776,15 @@ write_html_file(File,Content) ->
57765776
%% The 'major' log file, which is a pure text file is also written
57775777
%% with utf8 encoding
57785778
open_utf8_file(File) ->
5779-
case file:open(File,AllOpts=[write,{encoding,utf8}]) of
5779+
AllOpts = [write,{encoding,utf8}],
5780+
case file:open(File,AllOpts) of
57805781
{error,Reason} -> {error,{Reason,{File,AllOpts}}};
57815782
Result -> Result
57825783
end.
57835784

57845785
open_utf8_file(File,Opts) ->
5785-
case file:open(File,AllOpts=[{encoding,utf8}|Opts]) of
5786+
AllOpts = [{encoding,utf8}|Opts],
5787+
case file:open(File,AllOpts) of
57865788
{error,Reason} -> {error,{Reason,{File,AllOpts}}};
57875789
Result -> Result
57885790
end.

lib/dialyzer/src/dialyzer_dataflow.erl

Lines changed: 4 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -1015,7 +1015,8 @@ handle_map(Tree,Map,State) ->
10151015
traverse_map_pairs(Pairs, Map1, State1, t_none(), [], []),
10161016
InsertPair = fun({KV,assoc,_},Acc) -> erl_types:t_map_put(KV,Acc);
10171017
({KV,exact,KVTree},Acc) ->
1018-
case t_is_none(T=erl_types:t_map_update(KV,Acc)) of
1018+
T = erl_types:t_map_update(KV,Acc),
1019+
case t_is_none(T) of
10191020
true -> throw({none, Acc, KV, KVTree});
10201021
false -> T
10211022
end
@@ -1734,7 +1735,8 @@ bind_guard(Guard, Map, Env, Eval, State0) ->
17341735
{{Map1, t_none(), State1}, BE}
17351736
end,
17361737
Map3 = join_maps_end([BodyMap, HandlerMap], Map1),
1737-
case t_is_none(Sup = t_sup(BodyType, HandlerType)) of
1738+
Sup = t_sup(BodyType, HandlerType),
1739+
case t_is_none(Sup) of
17381740
true ->
17391741
%% Pick a reason. N.B. We assume that the handler is always
17401742
%% compiler-generated if the body is; that way, we won't need to

lib/dialyzer/src/dialyzer_typesig.erl

Lines changed: 6 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -1146,7 +1146,8 @@ get_safe_underapprox_1([Pat0|Left], Acc, Map) ->
11461146
%% Some assertions in case the syntax gets more premissive in the future
11471147
true = #{} =:= cerl:concrete(cerl:map_arg(Pat)),
11481148
true = lists:all(fun(P) ->
1149-
cerl:is_literal(Op = cerl:map_pair_op(P)) andalso
1149+
Op = cerl:map_pair_op(P),
1150+
cerl:is_literal(Op) andalso
11501151
exact =:= cerl:concrete(Op)
11511152
end, cerl:map_es(Pat)),
11521153
KeyTrees = lists:map(fun cerl:map_pair_key/1, cerl:map_es(Pat)),
@@ -1162,7 +1163,8 @@ get_safe_underapprox_1([Pat0|Left], Acc, Map) ->
11621163
%% We need to deal with duplicates ourselves
11631164
SquashDuplicates =
11641165
fun SquashDuplicates([{K,First},{K,Second}|List]) ->
1165-
case t_is_none(Inf = t_inf(First, Second)) of
1166+
Inf = t_inf(First, Second),
1167+
case t_is_none(Inf) of
11661168
true -> throw(dont_know);
11671169
false -> [{K, Inf}|SquashDuplicates(List)]
11681170
end;
@@ -1190,7 +1192,8 @@ get_safe_overapprox(Pats) ->
11901192
lists:map(fun get_safe_overapprox_1/1, Pats).
11911193

11921194
get_safe_overapprox_1(Pat) ->
1193-
case cerl:is_literal(Lit = cerl:fold_literal(Pat)) of
1195+
Lit = cerl:fold_literal(Pat),
1196+
case cerl:is_literal(Lit) of
11941197
true -> t_from_term(cerl:concrete(Lit));
11951198
false -> t_any()
11961199
end.

lib/dialyzer/src/dialyzer_utils.erl

Lines changed: 3 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -1116,9 +1116,9 @@ refold_concrete_pat(Val) ->
11161116
false -> label(cerl:c_tuple_skel(Els))
11171117
end;
11181118
[H|T] ->
1119-
case cerl:is_literal(HP=refold_concrete_pat(H))
1120-
and cerl:is_literal(TP=refold_concrete_pat(T))
1121-
of
1119+
HP = refold_concrete_pat(H),
1120+
TP = refold_concrete_pat(T),
1121+
case cerl:is_literal(HP) and cerl:is_literal(TP) of
11221122
true -> cerl:abstract(Val);
11231123
false -> label(cerl:c_cons_skel(HP, TP))
11241124
end;

lib/edoc/src/edoc_specs.erl

Lines changed: 2 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -510,7 +510,8 @@ expand_records(Entries, TypeDefs, DT, Opts, File, Module) ->
510510
{export_type,Ts} <- Module#module.attributes,
511511
is_list(Ts),
512512
{N,I} <- Ts,
513-
ets:member(DT, Name = {#t_name{name = N}, I})],
513+
Name <- [{#t_name{name = N}, I}],
514+
ets:member(DT, Name)],
514515
_ = lists:foreach(fun({N,A}) -> true = seen_type(N, A, P)
515516
end, ExportedTypes),
516517
entries(Entries, P, Opts).

lib/et/src/et_wx_viewer.erl

Lines changed: 4 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -1412,18 +1412,19 @@ create_filter_menu(S=#state{filter_menu = {Menu,Data}}, ActiveFilterName, Filter
14121412
Label = lists:concat([pad_string(F#filter.name, 20), "(", N, ")"]),
14131413
{N+1, [menuitem(Menu, ?wxID_ANY, Label, {data, F})|Acc]}
14141414
end,
1415-
D1 = [I1 = wxMenu:append(Menu, ?wxID_ANY, "Same Filter New Scale"),
1416-
wxMenu:appendSeparator(Menu)],
1415+
I1 = wxMenu:append(Menu, ?wxID_ANY, "Same Filter New Scale"),
1416+
D1 = [I1, wxMenu:appendSeparator(Menu)],
14171417
wxMenuItem:enable(I1, [{enable,false}]),
14181418
{value, Filter} = lists:keysearch(ActiveFilterName, #filter.name, Filters),
14191419
Same = lists:concat([pad_string(ActiveFilterName, 20), "(=) same scale"]),
14201420
Larger = lists:concat([pad_string(ActiveFilterName, 20), "(+) bigger scale"]),
14211421
Smaller = lists:concat([pad_string(ActiveFilterName, 20), "(-) smaller scale"]),
1422+
I2 = wxMenu:append(Menu, ?wxID_ANY, "New Filter Same Scale"),
14221423
D2 = [menuitem(Menu, ?wxID_ANY, Same, {data, Filter, 0}),
14231424
menuitem(Menu, ?wxID_ANY, Smaller, {data, Filter, -1}),
14241425
menuitem(Menu, ?wxID_ANY, Larger, {data, Filter, 1}),
14251426
wxMenu:appendSeparator(Menu),
1426-
I2 = wxMenu:append(Menu, ?wxID_ANY, "New Filter Same Scale"),
1427+
I2,
14271428
wxMenu:appendSeparator(Menu)],
14281429
_ = wxMenuItem:enable(I2, [{enable,false}]),
14291430
{_,D3} = lists:foldl(Item, {1,[]}, Filters),

lib/kernel/src/application_controller.erl

Lines changed: 2 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -1070,7 +1070,8 @@ handle_info({ac_load_application_reply, AppName, Res}, S) ->
10701070

10711071
handle_info({ac_start_application_reply, AppName, Res}, S) ->
10721072
Start_req = S#state.start_req,
1073-
case lists:keyfind(AppName, 1, Starting = S#state.starting) of
1073+
Starting = S#state.starting,
1074+
case lists:keyfind(AppName, 1, Starting) of
10741075
{_AppName, RestartType, Type, From} ->
10751076
case Res of
10761077
start_it ->

lib/kernel/src/dist_ac.erl

Lines changed: 10 additions & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -446,7 +446,8 @@ handle_info({ac_application_run, AppName, Res}, S) ->
446446

447447
handle_info({ac_application_not_run, AppName}, S) ->
448448
%% We ordered a stop, and now it has stopped
449-
{value, Appl} = keysearch(AppName, #appl.name, Appls = S#state.appls),
449+
Appls = S#state.appls,
450+
{value, Appl} = keysearch(AppName, #appl.name, Appls),
450451
%% Check if we have somebody waiting for the takeover result;
451452
%% if somebody called stop just before takeover was handled,
452453
NTReqs = del_t_reqs(AppName, S#state.t_reqs, {error, stopped}),
@@ -474,7 +475,8 @@ handle_info({ac_application_not_run, AppName}, S) ->
474475
handle_info({ac_application_stopped, AppName}, S) ->
475476
%% Somebody called application:stop - reset state as it was before
476477
%% the application was started.
477-
{value, Appl} = keysearch(AppName, #appl.name, Appls = S#state.appls),
478+
Appls = S#state.appls,
479+
{value, Appl} = keysearch(AppName, #appl.name, Appls),
478480
%% Check if we have somebody waiting for the takeover result;
479481
%% if somebody called stop just before takeover was handled,
480482
NTReqs = del_t_reqs(AppName, S#state.t_reqs, {error, stopped}),
@@ -650,7 +652,8 @@ handle_info({nodedown, Node}, S) ->
650652

651653
handle_info({dist_ac_app_loaded, Node, Name, HisNodes, Permission, HeKnowsMe},
652654
S) ->
653-
Nodes = dist_find_nodes(Appls = S#state.appls, Name),
655+
Appls = S#state.appls,
656+
Nodes = dist_find_nodes(Appls, Name),
654657
case is_loaded(Name, S) of
655658
true ->
656659
case equal_nodes(Nodes, HisNodes) of
@@ -723,7 +726,8 @@ code_change(_OldVsn, State, _Extra) ->
723726
load(AppName, S) ->
724727
Appls0 = S#state.appls,
725728
%% Get the dist specification for the app on other nodes
726-
DistLoaded = get_dist_loaded(AppName, Load1 = S#state.dist_loaded),
729+
Load1 = S#state.dist_loaded,
730+
DistLoaded = get_dist_loaded(AppName, Load1),
727731
%% Get the local dist specification
728732
Nodes = dist_find_nodes(Appls0, AppName),
729733
FNodes = flat_nodes(Nodes),
@@ -785,7 +789,8 @@ start_appl(AppName, S, Type) ->
785789
%% Get nodes, and check if App is loaded on all involved nodes.
786790
%% If it is loaded everywhere, we know that we have the same picture
787791
%% of the nodes; otherwise the load wouldn't have succeeded.
788-
Appl = case keysearch(AppName, #appl.name, Appls = S#state.appls) of
792+
Appls = S#state.appls,
793+
Appl = case keysearch(AppName, #appl.name, Appls) of
789794
{value, A} -> A;
790795
_ -> throw({error, {unknown_application, AppName}})
791796
end,

lib/mnesia/src/mnesia_recover.erl

Lines changed: 6 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -777,7 +777,9 @@ handle_call(Msg, _From, State) ->
777777
{noreply, State}.
778778

779779
do_log_mnesia_up(Node) ->
780-
Yoyo = {mnesia_up, Node, Date = date(), Time = time()},
780+
Date = date(),
781+
Time = time(),
782+
Yoyo = {mnesia_up, Node, Date, Time},
781783
case mnesia_monitor:use_dir() of
782784
true ->
783785
mnesia_log:append(latest_log, Yoyo),
@@ -788,7 +790,9 @@ do_log_mnesia_up(Node) ->
788790
note_up(Node, Date, Time).
789791

790792
do_log_mnesia_down(Node) ->
791-
Yoyo = {mnesia_down, Node, Date = date(), Time = time()},
793+
Date = date(),
794+
Time = time(),
795+
Yoyo = {mnesia_down, Node, Date, Time},
792796
case mnesia_monitor:use_dir() of
793797
true ->
794798
mnesia_log:append(latest_log, Yoyo),

0 commit comments

Comments
 (0)