Skip to content

Commit 92cf315

Browse files
committed
Eliminate exports from expression arguments
1 parent 1432a18 commit 92cf315

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
@@ -120,7 +120,8 @@ encode_jer({typeinfo,{Module,Type}},Val) ->
120120
encode_jer({sof,Type},Vals) when is_list(Vals) ->
121121
[encode_jer(Type,Val)||Val <- Vals];
122122
encode_jer({choice,Choices},{Alt,Value}) ->
123-
case is_map_key(AltBin = atom_to_binary(Alt,utf8),Choices) of
123+
AltBin = atom_to_binary(Alt,utf8),
124+
case is_map_key(AltBin,Choices) of
124125
true ->
125126
EncodedVal = encode_jer(maps:get(AltBin,Choices),Value),
126127
#{AltBin => EncodedVal};

lib/common_test/src/test_server_ctrl.erl

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

57825783
open_utf8_file(File,Opts) ->
5783-
case file:open(File,AllOpts=[{encoding,utf8}|Opts]) of
5784+
AllOpts = [{encoding,utf8}|Opts],
5785+
case file:open(File,AllOpts) of
57845786
{error,Reason} -> {error,{Reason,{File,AllOpts}}};
57855787
Result -> Result
57865788
end.

lib/dialyzer/src/dialyzer_dataflow.erl

Lines changed: 4 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -1006,7 +1006,8 @@ handle_map(Tree,Map,State) ->
10061006
traverse_map_pairs(Pairs, Map1, State1, t_none(), [], []),
10071007
InsertPair = fun({KV,assoc,_},Acc) -> erl_types:t_map_put(KV,Acc);
10081008
({KV,exact,KVTree},Acc) ->
1009-
case t_is_none(T=erl_types:t_map_update(KV,Acc)) of
1009+
T = erl_types:t_map_update(KV,Acc),
1010+
case t_is_none(T) of
10101011
true -> throw({none, Acc, KV, KVTree});
10111012
false -> T
10121013
end
@@ -1725,7 +1726,8 @@ bind_guard(Guard, Map, Env, Eval, State0) ->
17251726
{{Map1, t_none(), State1}, BE}
17261727
end,
17271728
Map3 = join_maps_end([BodyMap, HandlerMap], Map1),
1728-
case t_is_none(Sup = t_sup(BodyType, HandlerType)) of
1729+
Sup = t_sup(BodyType, HandlerType),
1730+
case t_is_none(Sup) of
17291731
true ->
17301732
%% Pick a reason. N.B. We assume that the handler is always
17311733
%% 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
@@ -1137,7 +1137,8 @@ get_safe_underapprox_1([Pat0|Left], Acc, Map) ->
11371137
%% Some assertions in case the syntax gets more premissive in the future
11381138
true = #{} =:= cerl:concrete(cerl:map_arg(Pat)),
11391139
true = lists:all(fun(P) ->
1140-
cerl:is_literal(Op = cerl:map_pair_op(P)) andalso
1140+
Op = cerl:map_pair_op(P),
1141+
cerl:is_literal(Op) andalso
11411142
exact =:= cerl:concrete(Op)
11421143
end, cerl:map_es(Pat)),
11431144
KeyTrees = lists:map(fun cerl:map_pair_key/1, cerl:map_es(Pat)),
@@ -1153,7 +1154,8 @@ get_safe_underapprox_1([Pat0|Left], Acc, Map) ->
11531154
%% We need to deal with duplicates ourselves
11541155
SquashDuplicates =
11551156
fun SquashDuplicates([{K,First},{K,Second}|List]) ->
1156-
case t_is_none(Inf = t_inf(First, Second)) of
1157+
Inf = t_inf(First, Second),
1158+
case t_is_none(Inf) of
11571159
true -> throw(dont_know);
11581160
false -> [{K, Inf}|SquashDuplicates(List)]
11591161
end;
@@ -1181,7 +1183,8 @@ get_safe_overapprox(Pats) ->
11811183
lists:map(fun get_safe_overapprox_1/1, Pats).
11821184

11831185
get_safe_overapprox_1(Pat) ->
1184-
case cerl:is_literal(Lit = cerl:fold_literal(Pat)) of
1186+
Lit = cerl:fold_literal(Pat),
1187+
case cerl:is_literal(Lit) of
11851188
true -> t_from_term(cerl:concrete(Lit));
11861189
false -> t_any()
11871190
end.

lib/dialyzer/src/dialyzer_utils.erl

Lines changed: 3 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -1107,9 +1107,9 @@ refold_concrete_pat(Val) ->
11071107
false -> label(cerl:c_tuple_skel(Els))
11081108
end;
11091109
[H|T] ->
1110-
case cerl:is_literal(HP=refold_concrete_pat(H))
1111-
and cerl:is_literal(TP=refold_concrete_pat(T))
1112-
of
1110+
HP = refold_concrete_pat(H),
1111+
TP = refold_concrete_pat(T),
1112+
case cerl:is_literal(HP) and cerl:is_literal(TP) of
11131113
true -> cerl:abstract(Val);
11141114
false -> label(cerl:c_cons_skel(HP, TP))
11151115
end;

lib/edoc/src/edoc_specs.erl

Lines changed: 2 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -498,7 +498,8 @@ expand_records(Entries, TypeDefs, DT, Opts, File, Module) ->
498498
{export_type,Ts} <- Module#module.attributes,
499499
is_list(Ts),
500500
{N,I} <- Ts,
501-
ets:member(DT, Name = {#t_name{name = N}, I})],
501+
Name <- [{#t_name{name = N}, I}],
502+
ets:member(DT, Name)],
502503
_ = lists:foreach(fun({N,A}) -> true = seen_type(N, A, P)
503504
end, ExportedTypes),
504505
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
@@ -1410,18 +1410,19 @@ create_filter_menu(S=#state{filter_menu = {Menu,Data}}, ActiveFilterName, Filter
14101410
Label = lists:concat([pad_string(F#filter.name, 20), "(", N, ")"]),
14111411
{N+1, [menuitem(Menu, ?wxID_ANY, Label, {data, F})|Acc]}
14121412
end,
1413-
D1 = [I1 = wxMenu:append(Menu, ?wxID_ANY, "Same Filter New Scale"),
1414-
wxMenu:appendSeparator(Menu)],
1413+
I1 = wxMenu:append(Menu, ?wxID_ANY, "Same Filter New Scale"),
1414+
D1 = [I1, wxMenu:appendSeparator(Menu)],
14151415
wxMenuItem:enable(I1, [{enable,false}]),
14161416
{value, Filter} = lists:keysearch(ActiveFilterName, #filter.name, Filters),
14171417
Same = lists:concat([pad_string(ActiveFilterName, 20), "(=) same scale"]),
14181418
Larger = lists:concat([pad_string(ActiveFilterName, 20), "(+) bigger scale"]),
14191419
Smaller = lists:concat([pad_string(ActiveFilterName, 20), "(-) smaller scale"]),
1420+
I2 = wxMenu:append(Menu, ?wxID_ANY, "New Filter Same Scale"),
14201421
D2 = [menuitem(Menu, ?wxID_ANY, Same, {data, Filter, 0}),
14211422
menuitem(Menu, ?wxID_ANY, Smaller, {data, Filter, -1}),
14221423
menuitem(Menu, ?wxID_ANY, Larger, {data, Filter, 1}),
14231424
wxMenu:appendSeparator(Menu),
1424-
I2 = wxMenu:append(Menu, ?wxID_ANY, "New Filter Same Scale"),
1425+
I2,
14251426
wxMenu:appendSeparator(Menu)],
14261427
_ = wxMenuItem:enable(I2, [{enable,false}]),
14271428
{_,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
@@ -1068,7 +1068,8 @@ handle_info({ac_load_application_reply, AppName, Res}, S) ->
10681068

10691069
handle_info({ac_start_application_reply, AppName, Res}, S) ->
10701070
Start_req = S#state.start_req,
1071-
case lists:keyfind(AppName, 1, Starting = S#state.starting) of
1071+
Starting = S#state.starting,
1072+
case lists:keyfind(AppName, 1, Starting) of
10721073
{_AppName, RestartType, Type, From} ->
10731074
case Res of
10741075
start_it ->

lib/kernel/src/dist_ac.erl

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

445445
handle_info({ac_application_not_run, AppName}, S) ->
446446
%% We ordered a stop, and now it has stopped
447-
{value, Appl} = keysearch(AppName, #appl.name, Appls = S#state.appls),
447+
Appls = S#state.appls,
448+
{value, Appl} = keysearch(AppName, #appl.name, Appls),
448449
%% Check if we have somebody waiting for the takeover result;
449450
%% if somebody called stop just before takeover was handled,
450451
NTReqs = del_t_reqs(AppName, S#state.t_reqs, {error, stopped}),
@@ -472,7 +473,8 @@ handle_info({ac_application_not_run, AppName}, S) ->
472473
handle_info({ac_application_stopped, AppName}, S) ->
473474
%% Somebody called application:stop - reset state as it was before
474475
%% the application was started.
475-
{value, Appl} = keysearch(AppName, #appl.name, Appls = S#state.appls),
476+
Appls = S#state.appls,
477+
{value, Appl} = keysearch(AppName, #appl.name, Appls),
476478
%% Check if we have somebody waiting for the takeover result;
477479
%% if somebody called stop just before takeover was handled,
478480
NTReqs = del_t_reqs(AppName, S#state.t_reqs, {error, stopped}),
@@ -648,7 +650,8 @@ handle_info({nodedown, Node}, S) ->
648650

649651
handle_info({dist_ac_app_loaded, Node, Name, HisNodes, Permission, HeKnowsMe},
650652
S) ->
651-
Nodes = dist_find_nodes(Appls = S#state.appls, Name),
653+
Appls = S#state.appls,
654+
Nodes = dist_find_nodes(Appls, Name),
652655
case is_loaded(Name, S) of
653656
true ->
654657
case equal_nodes(Nodes, HisNodes) of
@@ -721,7 +724,8 @@ code_change(_OldVsn, State, _Extra) ->
721724
load(AppName, S) ->
722725
Appls0 = S#state.appls,
723726
%% Get the dist specification for the app on other nodes
724-
DistLoaded = get_dist_loaded(AppName, Load1 = S#state.dist_loaded),
727+
Load1 = S#state.dist_loaded,
728+
DistLoaded = get_dist_loaded(AppName, Load1),
725729
%% Get the local dist specification
726730
Nodes = dist_find_nodes(Appls0, AppName),
727731
FNodes = flat_nodes(Nodes),
@@ -783,7 +787,8 @@ start_appl(AppName, S, Type) ->
783787
%% Get nodes, and check if App is loaded on all involved nodes.
784788
%% If it is loaded everywhere, we know that we have the same picture
785789
%% of the nodes; otherwise the load wouldn't have succeeded.
786-
Appl = case keysearch(AppName, #appl.name, Appls = S#state.appls) of
790+
Appls = S#state.appls,
791+
Appl = case keysearch(AppName, #appl.name, Appls) of
787792
{value, A} -> A;
788793
_ -> throw({error, {unknown_application, AppName}})
789794
end,

lib/mnesia/src/mnesia_recover.erl

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

769769
do_log_mnesia_up(Node) ->
770-
Yoyo = {mnesia_up, Node, Date = date(), Time = time()},
770+
Date = date(),
771+
Time = time(),
772+
Yoyo = {mnesia_up, Node, Date, Time},
771773
case mnesia_monitor:use_dir() of
772774
true ->
773775
mnesia_log:append(latest_log, Yoyo),
@@ -778,7 +780,9 @@ do_log_mnesia_up(Node) ->
778780
note_up(Node, Date, Time).
779781

780782
do_log_mnesia_down(Node) ->
781-
Yoyo = {mnesia_down, Node, Date = date(), Time = time()},
783+
Date = date(),
784+
Time = time(),
785+
Yoyo = {mnesia_down, Node, Date, Time},
782786
case mnesia_monitor:use_dir() of
783787
true ->
784788
mnesia_log:append(latest_log, Yoyo),

0 commit comments

Comments
 (0)