File 1761-Eliminate-exports-from-expression-arguments.patch of Package erlang

From 9b00d0224e800dbb7e29ad03065b19ecb33f25a3 Mon Sep 17 00:00:00 2001
From: Richard Carlsson <carlsson.richard@gmail.com>
Date: Wed, 7 Jan 2026 15:20:01 +0100
Subject: [PATCH 1/2] Eliminate exports from expression arguments

---
 lib/asn1/src/asn1rtt_jer.erl              |  5 ++-
 lib/asn1/test/asn1_test_lib.erl           |  2 +-
 lib/common_test/src/test_server_ctrl.erl  |  8 ++---
 lib/dialyzer/src/dialyzer_dataflow.erl    |  8 ++---
 lib/dialyzer/src/dialyzer_typesig.erl     | 11 ++++---
 lib/dialyzer/src/dialyzer_utils.erl       |  8 ++---
 lib/edoc/src/edoc_specs.erl               |  5 ++-
 lib/et/src/et_wx_viewer.erl               |  9 +++---
 lib/kernel/src/application_controller.erl |  4 +--
 lib/kernel/src/dist_ac.erl                | 16 ++++++----
 lib/mnesia/src/mnesia_recover.erl         |  8 ++---
 lib/observer/src/crashdump_viewer.erl     |  5 ++-
 lib/parsetools/src/yecc.erl               |  5 ++-
 lib/snmp/src/agent/snmpa_agent.erl        |  5 ++-
 lib/snmp/src/compile/snmpc_lib.erl        | 11 ++++---
 lib/ssh/src/ssh_connection_handler.erl    |  5 ++-
 lib/stdlib/src/edlin_expand.erl           |  4 +--
 lib/stdlib/src/erl_lint.erl               | 10 +++---
 lib/stdlib/src/qlc.erl                    | 17 ++++++----
 lib/stdlib/src/qlc_pt.erl                 | 39 +++++++++++++----------
 lib/stdlib/src/sofs.erl                   |  4 +--
 lib/wx/src/wxe_server.erl                 |  5 ++-
 22 files changed, 97 insertions(+), 97 deletions(-)

diff --git a/lib/asn1/src/asn1rtt_jer.erl b/lib/asn1/src/asn1rtt_jer.erl
index e846040781..6ce547f1c9 100644
--- a/lib/asn1/src/asn1rtt_jer.erl
+++ b/lib/asn1/src/asn1rtt_jer.erl
@@ -28,8 +28,6 @@
 %% For typeinfo JER
 -export([encode_jer/3, decode_jer/3]).
 
--compile(nowarn_export_var_subexpr).
-
 %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 %% Common code for all JER encoding/decoding
 %%
@@ -123,7 +121,8 @@ encode_jer({typeinfo,{Module,Type}},Val) ->
 encode_jer({sof,Type},Vals) when is_list(Vals) ->
     [encode_jer(Type,Val)||Val <- Vals];
 encode_jer({choice,Choices},{Alt,Value}) ->
-    case is_map_key(AltBin = atom_to_binary(Alt,utf8),Choices) of
+    AltBin = atom_to_binary(Alt,utf8),
+    case is_map_key(AltBin,Choices) of
         true ->
             EncodedVal = encode_jer(maps:get(AltBin,Choices),Value),
             #{AltBin => EncodedVal};
diff --git a/lib/asn1/test/asn1_test_lib.erl b/lib/asn1/test/asn1_test_lib.erl
index 8f1cf2c897..aad7f57a6e 100644
--- a/lib/asn1/test/asn1_test_lib.erl
+++ b/lib/asn1/test/asn1_test_lib.erl
@@ -39,7 +39,7 @@ compile(File, Config, Options) -> compile_all([File], Config, Options).
 compile_all(Files, Config, Options0) ->
     DataDir = proplists:get_value(data_dir, Config),
     CaseDir = proplists:get_value(case_dir, Config),
-    Options = [{outdir,CaseDir},debug_info,nowarn_export_var_subexpr|Options0],
+    Options = [{outdir,CaseDir},debug_info|Options0],
 
     Comp = fun(F) ->
 		   compile_file(filename:join(DataDir, F), Options)
diff --git a/lib/common_test/src/test_server_ctrl.erl b/lib/common_test/src/test_server_ctrl.erl
index 59165da8bf..eeefc2af45 100644
--- a/lib/common_test/src/test_server_ctrl.erl
+++ b/lib/common_test/src/test_server_ctrl.erl
@@ -83,8 +83,6 @@
 
 %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
--compile(nowarn_export_var_subexpr).
-
 -include("test_server_internal.hrl").
 -include_lib("kernel/include/file.hrl").
 -define(suite_ext, "_SUITE").
@@ -5778,13 +5776,15 @@ write_html_file(File,Content) ->
 %% The 'major' log file, which is a pure text file is also written
 %% with utf8 encoding
 open_utf8_file(File) ->
-    case file:open(File,AllOpts=[write,{encoding,utf8}]) of
+    AllOpts = [write,{encoding,utf8}],
+    case file:open(File,AllOpts) of
 	{error,Reason} -> {error,{Reason,{File,AllOpts}}};
 	Result         -> Result
     end.
 
 open_utf8_file(File,Opts) ->
-    case file:open(File,AllOpts=[{encoding,utf8}|Opts]) of
+    AllOpts = [{encoding,utf8}|Opts],
+    case file:open(File,AllOpts) of
 	{error,Reason} -> {error,{Reason,{File,AllOpts}}};
 	Result         -> Result
     end.
diff --git a/lib/dialyzer/src/dialyzer_dataflow.erl b/lib/dialyzer/src/dialyzer_dataflow.erl
index aa751610bd..ad18673d7e 100644
--- a/lib/dialyzer/src/dialyzer_dataflow.erl
+++ b/lib/dialyzer/src/dialyzer_dataflow.erl
@@ -34,8 +34,6 @@
 
 -export([get_fun_types/5, get_warnings/5, format_args/3]).
 
--compile(nowarn_export_var_subexpr).
-
 -include("dialyzer.hrl").
 
 -import(erl_types,
@@ -1017,7 +1015,8 @@ handle_map(Tree,Map,State) ->
 	traverse_map_pairs(Pairs, Map1, State1, t_none(), [], []),
       InsertPair = fun({KV,assoc,_},Acc) -> erl_types:t_map_put(KV,Acc);
 		      ({KV,exact,KVTree},Acc) ->
-		       case t_is_none(T=erl_types:t_map_update(KV,Acc)) of
+                       T = erl_types:t_map_update(KV,Acc),
+		       case t_is_none(T) of
 			 true -> throw({none, Acc, KV, KVTree});
 			 false -> T
 		       end
@@ -1736,7 +1735,8 @@ bind_guard(Guard, Map, Env, Eval, State0) ->
 		{{Map1, t_none(), State1}, BE}
 	    end,
 	  Map3 = join_maps_end([BodyMap, HandlerMap], Map1),
-	  case t_is_none(Sup = t_sup(BodyType, HandlerType)) of
+          Sup = t_sup(BodyType, HandlerType),
+	  case t_is_none(Sup) of
 	    true ->
 	      %% Pick a reason. N.B. We assume that the handler is always
 	      %% compiler-generated if the body is; that way, we won't need to
diff --git a/lib/dialyzer/src/dialyzer_typesig.erl b/lib/dialyzer/src/dialyzer_typesig.erl
index 811201cfdc..33fc6768f1 100644
--- a/lib/dialyzer/src/dialyzer_typesig.erl
+++ b/lib/dialyzer/src/dialyzer_typesig.erl
@@ -32,8 +32,6 @@
 -module(dialyzer_typesig).
 -moduledoc false.
 
--compile(nowarn_export_var_subexpr).
-
 -export([analyze_scc/7]).
 -export([get_safe_underapprox/2]).
 
@@ -1148,7 +1146,8 @@ get_safe_underapprox_1([Pat0|Left], Acc, Map) ->
       %% Some assertions in case the syntax gets more premissive in the future
       true = #{} =:= cerl:concrete(cerl:map_arg(Pat)),
       true = lists:all(fun(P) ->
-			   cerl:is_literal(Op = cerl:map_pair_op(P)) andalso
+                           Op = cerl:map_pair_op(P),
+			   cerl:is_literal(Op) andalso
 			     exact =:= cerl:concrete(Op)
 		       end, cerl:map_es(Pat)),
       KeyTrees = lists:map(fun cerl:map_pair_key/1, cerl:map_es(Pat)),
@@ -1164,7 +1163,8 @@ get_safe_underapprox_1([Pat0|Left], Acc, Map) ->
       %% We need to deal with duplicates ourselves
       SquashDuplicates =
 	fun SquashDuplicates([{K,First},{K,Second}|List]) ->
-	    case t_is_none(Inf = t_inf(First, Second)) of
+            Inf = t_inf(First, Second),
+	    case t_is_none(Inf) of
 	      true -> throw(dont_know);
 	      false -> [{K, Inf}|SquashDuplicates(List)]
 	    end;
@@ -1192,7 +1192,8 @@ get_safe_overapprox(Pats) ->
   lists:map(fun get_safe_overapprox_1/1, Pats).
 
 get_safe_overapprox_1(Pat) ->
-  case cerl:is_literal(Lit = cerl:fold_literal(Pat)) of
+  Lit = cerl:fold_literal(Pat),
+  case cerl:is_literal(Lit) of
     true  -> t_from_term(cerl:concrete(Lit));
     false -> t_any()
   end.
diff --git a/lib/dialyzer/src/dialyzer_utils.erl b/lib/dialyzer/src/dialyzer_utils.erl
index 5dc9d14fba..d1bfdd5531 100644
--- a/lib/dialyzer/src/dialyzer_utils.erl
+++ b/lib/dialyzer/src/dialyzer_utils.erl
@@ -31,8 +31,6 @@
 -module(dialyzer_utils).
 -moduledoc false.
 
--compile(nowarn_export_var_subexpr).
-
 -export([
 	 format_sig/1,
 	 format_sig/2,
@@ -1118,9 +1116,9 @@ refold_concrete_pat(Val) ->
 	false -> label(cerl:c_tuple_skel(Els))
       end;
     [H|T] ->
-      case  cerl:is_literal(HP=refold_concrete_pat(H))
-	and cerl:is_literal(TP=refold_concrete_pat(T))
-      of
+      HP = refold_concrete_pat(H),
+      TP = refold_concrete_pat(T),
+      case  cerl:is_literal(HP) and cerl:is_literal(TP) of
 	true -> cerl:abstract(Val);
 	false -> label(cerl:c_cons_skel(HP, TP))
       end;
diff --git a/lib/edoc/src/edoc_specs.erl b/lib/edoc/src/edoc_specs.erl
index e10b10314b..4b1ef339e7 100644
--- a/lib/edoc/src/edoc_specs.erl
+++ b/lib/edoc/src/edoc_specs.erl
@@ -37,8 +37,6 @@
 
 -export([add_type_data/4, tag/1, is_tag/1]).
 
--compile(nowarn_export_var_subexpr).
-
 -include("edoc.hrl").
 -include("edoc_types.hrl").
 
@@ -512,7 +510,8 @@ expand_records(Entries, TypeDefs, DT, Opts, File, Module) ->
                         {export_type,Ts} <- Module#module.attributes,
                         is_list(Ts),
                         {N,I} <- Ts,
-                        ets:member(DT, Name = {#t_name{name = N}, I})],
+                        Name <- [{#t_name{name = N}, I}],
+                        ets:member(DT, Name)],
     _ = lists:foreach(fun({N,A}) -> true = seen_type(N, A, P)
                       end, ExportedTypes),
     entries(Entries, P, Opts).
diff --git a/lib/et/src/et_wx_viewer.erl b/lib/et/src/et_wx_viewer.erl
index 6d43aec84b..db8df363e3 100644
--- a/lib/et/src/et_wx_viewer.erl
+++ b/lib/et/src/et_wx_viewer.erl
@@ -26,8 +26,6 @@
 -module(et_wx_viewer).
 -moduledoc false.
 
--compile(nowarn_export_var_subexpr).
-
 -behaviour(gen_server).
 
 %% External exports
@@ -1414,18 +1412,19 @@ create_filter_menu(S=#state{filter_menu = {Menu,Data}}, ActiveFilterName, Filter
 		    Label = lists:concat([pad_string(F#filter.name, 20), "(", N, ")"]),
 		    {N+1, [menuitem(Menu, ?wxID_ANY, Label, {data, F})|Acc]}
 	    end,
-     D1 = [I1 = wxMenu:append(Menu, ?wxID_ANY, "Same Filter New Scale"),
-	   wxMenu:appendSeparator(Menu)],
+     I1 = wxMenu:append(Menu, ?wxID_ANY, "Same Filter New Scale"),
+     D1 = [I1, wxMenu:appendSeparator(Menu)],
      wxMenuItem:enable(I1, [{enable,false}]),
      {value, Filter} = lists:keysearch(ActiveFilterName, #filter.name, Filters),
      Same    = lists:concat([pad_string(ActiveFilterName, 20), "(=) same    scale"]),
      Larger  = lists:concat([pad_string(ActiveFilterName, 20), "(+) bigger  scale"]),
      Smaller = lists:concat([pad_string(ActiveFilterName, 20), "(-) smaller scale"]),
+     I2 = wxMenu:append(Menu, ?wxID_ANY, "New Filter Same Scale"),
      D2 = [menuitem(Menu, ?wxID_ANY, Same, {data, Filter, 0}),
 	   menuitem(Menu, ?wxID_ANY, Smaller, {data, Filter, -1}),
 	   menuitem(Menu, ?wxID_ANY, Larger, {data, Filter, 1}),
 	   wxMenu:appendSeparator(Menu),
-	   I2 = wxMenu:append(Menu, ?wxID_ANY, "New Filter Same Scale"),
+	   I2,
 	   wxMenu:appendSeparator(Menu)],
      _ = wxMenuItem:enable(I2, [{enable,false}]),
      {_,D3} = lists:foldl(Item, {1,[]}, Filters),
diff --git a/lib/kernel/src/application_controller.erl b/lib/kernel/src/application_controller.erl
index 9e6cf16b56..22a8d6ea25 100644
--- a/lib/kernel/src/application_controller.erl
+++ b/lib/kernel/src/application_controller.erl
@@ -23,7 +23,6 @@
 -moduledoc false.
 
 -compile(nowarn_deprecated_catch).
--compile(nowarn_export_var_subexpr).
 
 %% External exports
 -export([start/1, 
@@ -1071,7 +1070,8 @@ handle_info({ac_load_application_reply, AppName, Res}, S) ->
 
 handle_info({ac_start_application_reply, AppName, Res}, S) ->
     Start_req = S#state.start_req,
-    case lists:keyfind(AppName, 1, Starting = S#state.starting) of
+    Starting = S#state.starting,
+    case lists:keyfind(AppName, 1, Starting) of
 	{_AppName, RestartType, Type, From} ->
 	    case Res of
 		start_it ->
diff --git a/lib/kernel/src/dist_ac.erl b/lib/kernel/src/dist_ac.erl
index 6e8925d0b2..54db94db79 100644
--- a/lib/kernel/src/dist_ac.erl
+++ b/lib/kernel/src/dist_ac.erl
@@ -23,7 +23,6 @@
 -moduledoc false.
 
 -compile(nowarn_deprecated_catch).
--compile(nowarn_export_var_subexpr).
 
 -behaviour(gen_server).
 
@@ -447,7 +446,8 @@ handle_info({ac_application_run, AppName, Res}, S) ->
 
 handle_info({ac_application_not_run, AppName}, S) ->
     %% We ordered a stop, and now it has stopped
-    {value, Appl} = keysearch(AppName, #appl.name, Appls = S#state.appls),
+    Appls = S#state.appls,
+    {value, Appl} = keysearch(AppName, #appl.name, Appls),
     %% Check if we have somebody waiting for the takeover result;
     %% if somebody called stop just before takeover was handled,
     NTReqs = del_t_reqs(AppName, S#state.t_reqs, {error, stopped}),
@@ -475,7 +475,8 @@ handle_info({ac_application_not_run, AppName}, S) ->
 handle_info({ac_application_stopped, AppName}, S) ->
     %% Somebody called application:stop - reset state as it was before
     %% the application was started.
-    {value, Appl} = keysearch(AppName, #appl.name, Appls = S#state.appls),
+    Appls = S#state.appls,
+    {value, Appl} = keysearch(AppName, #appl.name, Appls),
     %% Check if we have somebody waiting for the takeover result;
     %% if somebody called stop just before takeover was handled,
     NTReqs = del_t_reqs(AppName, S#state.t_reqs, {error, stopped}),
@@ -651,7 +652,8 @@ handle_info({nodedown, Node}, S) ->
 
 handle_info({dist_ac_app_loaded, Node, Name, HisNodes, Permission, HeKnowsMe},
 	    S) ->
-    Nodes = dist_find_nodes(Appls = S#state.appls, Name),
+    Appls = S#state.appls,
+    Nodes = dist_find_nodes(Appls, Name),
     case is_loaded(Name, S) of
 	true ->
 	    case equal_nodes(Nodes, HisNodes) of
@@ -724,7 +726,8 @@ code_change(_OldVsn, State, _Extra) ->
 load(AppName, S) ->
     Appls0 = S#state.appls,
     %% Get the dist specification for the app on other nodes
-    DistLoaded = get_dist_loaded(AppName, Load1 = S#state.dist_loaded),
+    Load1 = S#state.dist_loaded,
+    DistLoaded = get_dist_loaded(AppName, Load1),
     %% Get the local dist specification
     Nodes = dist_find_nodes(Appls0, AppName),
     FNodes = flat_nodes(Nodes),
@@ -786,7 +789,8 @@ start_appl(AppName, S, Type) ->
     %% Get nodes, and check if App is loaded on all involved nodes.
     %% If it is loaded everywhere, we know that we have the same picture
     %% of the nodes; otherwise the load wouldn't have succeeded.
-    Appl = case keysearch(AppName, #appl.name, Appls = S#state.appls) of
+    Appls = S#state.appls,
+    Appl = case keysearch(AppName, #appl.name, Appls) of
 	       {value, A} -> A;
 	       _ -> throw({error, {unknown_application, AppName}})
 	   end,
diff --git a/lib/mnesia/src/mnesia_recover.erl b/lib/mnesia/src/mnesia_recover.erl
index d3ba3f1002..4a6c7fa200 100644
--- a/lib/mnesia/src/mnesia_recover.erl
+++ b/lib/mnesia/src/mnesia_recover.erl
@@ -24,8 +24,6 @@
 -module(mnesia_recover).
 -moduledoc false.
 
--compile(nowarn_export_var_subexpr).
-
 -behaviour(gen_server).
 
 -export([
@@ -779,7 +777,8 @@ handle_call(Msg, _From, State) ->
     {noreply, State}.
 
 do_log_mnesia_up(Node) ->
-    Yoyo = {mnesia_up, Node, Date = date(), Time = time()},
+    {Date, Time} = erlang:localtime(),
+    Yoyo = {mnesia_up, Node, Date, Time},
     case mnesia_monitor:use_dir() of
 	true ->
 	    mnesia_log:append(latest_log, Yoyo),
@@ -790,7 +789,8 @@ do_log_mnesia_up(Node) ->
     note_up(Node, Date, Time).
 
 do_log_mnesia_down(Node) ->
-    Yoyo = {mnesia_down, Node, Date = date(), Time = time()},
+    {Date, Time} = erlang:localtime(),
+    Yoyo = {mnesia_down, Node, Date, Time},
     case mnesia_monitor:use_dir() of
 	true ->
 	    mnesia_log:append(latest_log, Yoyo),
diff --git a/lib/observer/src/crashdump_viewer.erl b/lib/observer/src/crashdump_viewer.erl
index 618b0699a0..9b4eb514db 100644
--- a/lib/observer/src/crashdump_viewer.erl
+++ b/lib/observer/src/crashdump_viewer.erl
@@ -61,8 +61,6 @@ For details about how to get started with the Crashdump Viewer, see the
 %% wordsize: 4 | 8, the number of bytes in a word.
 %%
 
--compile(nowarn_export_var_subexpr).
-
 %% User API
 -export([start/0,start/1,stop/0,script_start/0,script_start/1]).
 
@@ -902,7 +900,8 @@ do_read_file(File) ->
                             case check_dump_version(Id) of
                                 {ok,DumpVsn} ->
                                     reset_tables(),
-                                    insert_index(Tag,Id,Pos=N1+1),
+                                    Pos = N1+1,
+                                    insert_index(Tag,Id,Pos),
                                     put_last_tag(Tag,"",Pos),
                                     DecodeOpts = get_decode_opts(DumpVsn),
                                     indexify(Fd,DecodeOpts,Rest,N1),
diff --git a/lib/parsetools/src/yecc.erl b/lib/parsetools/src/yecc.erl
index 371f30dd04..8782d29e6d 100644
--- a/lib/parsetools/src/yecc.erl
+++ b/lib/parsetools/src/yecc.erl
@@ -499,8 +499,6 @@ lib/parsetools/include/yeccpre.hrl
                 keysort/2, last/1, map/2, member/2, reverse/1,
                 sort/1, usort/1]).
 
--compile(nowarn_export_var_subexpr).
-
 -include("erl_compile.hrl").
 -include("ms_transform.hrl").
 
@@ -2417,7 +2415,8 @@ select_parts(PartDataL) ->
             NL = [D#part_data{states = NewS} || 
                      {W1, #part_data{states = S0}=D} <- Ws,
                      W1 > 0,
-                     (NewS = ordsets:subtract(S0, S)) =/= []],
+                     NewS <- [ordsets:subtract(S0, S)],
+                     NewS =/= []],
             if 
                 length(S) =:= 1; NActions =:= 1 ->
                     select_parts(NL);
diff --git a/lib/snmp/src/agent/snmpa_agent.erl b/lib/snmp/src/agent/snmpa_agent.erl
index 5036aed2e5..f2a481ec4c 100644
--- a/lib/snmp/src/agent/snmpa_agent.erl
+++ b/lib/snmp/src/agent/snmpa_agent.erl
@@ -22,8 +22,6 @@
 -module(snmpa_agent).
 -moduledoc false.
 
--compile(nowarn_export_var_subexpr).
-
 -include_lib("kernel/include/file.hrl").
 -include("snmpa_internal.hrl").
 -include("snmp_types.hrl").
@@ -2539,7 +2537,8 @@ validate_next_v1_2([], _MibView, Res) ->
 %% problems.
 %%-----------------------------------------------------------------
 mk_next_oid(Vb) ->
-    case snmpa_mib:lookup(get(mibserver), Oid = Vb#varbind.oid) of
+    Oid = Vb#varbind.oid,
+    case snmpa_mib:lookup(get(mibserver), Oid) of
 	{table_column, _MibEntry, TableEntryOid} ->
 	    [Col | _] = Oid -- TableEntryOid,
 	    Vb#varbind{oid = TableEntryOid ++ [Col+1]};
diff --git a/lib/snmp/src/compile/snmpc_lib.erl b/lib/snmp/src/compile/snmpc_lib.erl
index 5b7b756464..d21926bee9 100644
--- a/lib/snmp/src/compile/snmpc_lib.erl
+++ b/lib/snmp/src/compile/snmpc_lib.erl
@@ -23,8 +23,6 @@
 -module(snmpc_lib).
 -moduledoc false.
 
--compile(nowarn_export_var_subexpr).
-
 %% Avoid warning for local functions error/2,3 clashing
 %% with autoimported BIFs.
 -compile({no_auto_import, [error/2, error/3]}).
@@ -93,7 +91,8 @@ make_ASN1type({{type,Type},Line}) ->
 make_ASN1type({{type_with_size,Type,{range,Lo,Hi}},Line}) ->
     case lookup_vartype(Type) of
         {value,ASN1type} ->  
-	    case allow_size_rfc1902(BaseType = ASN1type#asn1_type.bertype) of
+            BaseType = ASN1type#asn1_type.bertype,
+	    case allow_size_rfc1902(BaseType) of
 		true ->
 		    ok;
 		false ->
@@ -130,7 +129,8 @@ test_kibbles([], Line) ->
     print_error("No kibbles found.",[],Line),
     [];
 test_kibbles(Kibbles,Line) ->
-    test_kibbles2(R = lists:keysort(2,Kibbles),0,Line),
+    R = lists:keysort(2,Kibbles),
+    test_kibbles2(R,0,Line),
     R.
 
 test_kibbles2([],_,_) ->
@@ -411,7 +411,8 @@ read_mib(_Line, _Filename, []) ->
     error;
 read_mib(Line, Filename, [Dir|Path]) ->
     Dir2 = snmpc_misc:ensure_trailing_dir_delimiter(Dir),
-    case snmpc_misc:read_mib(AbsFile=lists:append(Dir2, Filename)) of
+    AbsFile = lists:append(Dir2, Filename),
+    case snmpc_misc:read_mib(AbsFile) of
 	{ok, MIB} -> MIB;
 	{error, enoent} ->
 	    read_mib(Line, Filename, Path);
diff --git a/lib/ssh/src/ssh_connection_handler.erl b/lib/ssh/src/ssh_connection_handler.erl
index ba2f7f3115..d7cb8dc381 100644
--- a/lib/ssh/src/ssh_connection_handler.erl
+++ b/lib/ssh/src/ssh_connection_handler.erl
@@ -33,8 +33,6 @@
 
 -behaviour(gen_statem).
 
--compile(nowarn_export_var_subexpr).
-
 -include("ssh.hrl").
 -include("ssh_transport.hrl").
 -include("ssh_auth.hrl").
@@ -617,7 +615,8 @@ handle_event(cast, socket_control, {wait_for_socket, Role},
 handle_event(internal, socket_ready, {hello,_}=StateName, #data{ssh_params = Ssh0} = D) ->
     VsnMsg = ssh_transport:hello_version_msg(string_version(Ssh0)),
     send_bytes(VsnMsg, D),
-    case inet:getopts(Socket=D#data.socket, [buffer]) of
+    Socket=D#data.socket,
+    case inet:getopts(Socket, [buffer]) of
 	{ok, [{buffer,Size}]} ->
 	    %% Set the socket to the hello text line handling mode:
 	    inet:setopts(Socket, [{packet, line},
diff --git a/lib/stdlib/src/edlin_expand.erl b/lib/stdlib/src/edlin_expand.erl
index c2d048b83c..2bfa880f12 100644
--- a/lib/stdlib/src/edlin_expand.erl
+++ b/lib/stdlib/src/edlin_expand.erl
@@ -33,8 +33,6 @@ This module provides an expand_fun for the erlang shell
 %% record fields and map keys and record field values.
 -include_lib("kernel/include/eep48.hrl").
 
--compile(nowarn_export_var_subexpr).
-
 -export([expand/1, expand/2, expand/3, format_matches/2, number_matches/1, get_exports/1,
          shell_default_or_bif/1, bif/1, over_word/1]).
 -export([is_type/3, match_arguments1/3]).
@@ -1020,7 +1018,7 @@ match(Prefix, Alts, Extra0) ->
     Len = string:length(Prefix),
     Matches = lists:sort(
                 [{S, A} || {H, A} <- Alts2,
-                           lists:prefix(Prefix, S=flat_write(H))]),
+                           S <- [flat_write(H)], lists:prefix(Prefix, S)]),
     Matches2 = lists:usort(
                  case Extra0 of
                      [] -> [{S,[]} || {S,_} <- Matches];
diff --git a/lib/stdlib/src/erl_lint.erl b/lib/stdlib/src/erl_lint.erl
index 3c73675ac4..34f8c6e515 100644
--- a/lib/stdlib/src/erl_lint.erl
+++ b/lib/stdlib/src/erl_lint.erl
@@ -70,8 +70,6 @@ Module:format_error(ErrorDescriptor)
 `m:epp`, `m:erl_parse`
 """.
 
--compile(nowarn_export_var_subexpr).
-
 -export([module/1,module/2,module/3,format_error/1]).
 -export([exprs/2,exprs_opt/3,used_vars/2]). % Used from erl_eval.erl.
 -export([is_pattern_expr/1,is_guard_test/1,is_guard_test/2,is_guard_test/3]).
@@ -3806,8 +3804,8 @@ add_missing_spec_warnings(Forms, St0, Type) ->
     Warns = %% functions + line numbers for which we should warn
 	case Type of
 	    all ->
-		[{FA,Anno} || {function,Anno,F,A,_} <- Forms,
-			   not lists:member(FA = {F,A}, Specs)];
+		[{{F,A},Anno} || {function,Anno,F,A,_} <- Forms,
+                                 not lists:member({F,A}, Specs)];
 	    _ ->
                 Exps0 = gb_sets:to_list(exports(St0)) -- pseudolocals(),
                 Exps1 =
@@ -3817,8 +3815,8 @@ add_missing_spec_warnings(Forms, St0, Type) ->
                             Exps0
                     end,
                 Exps = Exps1 -- Specs,
-		[{FA,Anno} || {function,Anno,F,A,_} <- Forms,
-			   member(FA = {F,A}, Exps)]
+		[{{F,A},Anno} || {function,Anno,F,A,_} <- Forms,
+                                 member({F,A}, Exps)]
 	end,
     foldl(fun ({FA,Anno}, St) ->
 		  add_warning(Anno, {missing_spec,FA}, St)
diff --git a/lib/stdlib/src/qlc.erl b/lib/stdlib/src/qlc.erl
index 4c1bd2be66..e4fd42df44 100644
--- a/lib/stdlib/src/qlc.erl
+++ b/lib/stdlib/src/qlc.erl
@@ -29,7 +29,6 @@
 %% External exports 
 
 -compile(nowarn_deprecated_catch).
--compile(nowarn_export_var_subexpr).
 
 %% Avoid warning for local function error/1 clashing with autoimported BIF.
 -compile({no_auto_import,[error/1]}).
@@ -1280,8 +1279,9 @@ For the various options recognized by `table/1,2` in respective module, see
       Args :: [term()],
       QH :: query_handle().
 table(TraverseFun, Options) when is_function(TraverseFun) ->
-    case {is_function(TraverseFun, 0), 
-          IsFun1 = is_function(TraverseFun, 1)} of
+    IsFun0 = is_function(TraverseFun, 0),
+    IsFun1 = is_function(TraverseFun, 1),
+    case {IsFun0, IsFun1} of
         {false, false} ->
             erlang:error(badarg, [TraverseFun, Options]);
         _ ->
@@ -2508,10 +2508,12 @@ qlc_sort_info(Qdata0, QOpt) ->
 
 sort_info(#prepared{sort_info = SI, sorted = S} = Prep, QNum, QOpt) ->
     SI1 = [{{C,Ord},[]} || 
-              S =/= no, 
-              is_integer(Sz = size_of_qualifier(QOpt, QNum)), 
+              S =/= no,
+              Sz <- [size_of_qualifier(QOpt, QNum)],
+              is_integer(Sz), 
               Sz > 0, % the size of the pattern
-              (NConstCols = size_of_constant_prefix(QOpt, QNum)) < Sz, 
+              NConstCols <- [size_of_constant_prefix(QOpt, QNum)],
+              NConstCols < Sz, 
               C <- [NConstCols+1],
               Ord <- orders(S)]
        ++ [{{Pos,Ord},[]} || Pos <- constant_columns(QOpt, QNum),
@@ -2593,7 +2595,8 @@ pos_vals(_Pos, _KeyEquality, _T, _Max) ->
 nub([]) ->
     [];
 nub([E | L]) ->
-    case lists:member(E, Es=nub(L)) of
+    Es=nub(L),
+    case lists:member(E, Es) of
         true ->
             Es;
         false ->
diff --git a/lib/stdlib/src/qlc_pt.erl b/lib/stdlib/src/qlc_pt.erl
index 512e4b643c..188e63846c 100644
--- a/lib/stdlib/src/qlc_pt.erl
+++ b/lib/stdlib/src/qlc_pt.erl
@@ -23,7 +23,6 @@
 -moduledoc false.
 
 -compile(nowarn_deprecated_catch).
--compile(nowarn_export_var_subexpr).
 
 %%% Purpose: Implements the qlc Parse Transform.
 
@@ -913,8 +912,8 @@ join_quals(JoinInfo, QCs, Anno, LcNo, ExtraConstants, AllVars) ->
                 H2 = join_handle(AP2, Anno, Aux, Cs2),
                 %% Op is not used.
                 Join = {join,Op,QId1#qid.no,QId2#qid.no,H1,H2,Cs1,Cs2},
-                G = {NQId=QId#qid{no = QId#qid.no + 1},
-                     {QIVs,{{gen,{cons,Anno,P1,P2},Join,GV1},GoI,SI}}},
+                NQId=QId#qid{no = QId#qid.no + 1},
+                G = {NQId, {QIVs,{{gen,{cons,Anno,P1,P2},Join,GV1},GoI,SI}}},
                 A = {NQId, GoI + 3, SI + 2},
                 {G, A}
         end,
@@ -1057,7 +1056,8 @@ template_cols(ColumnClasses) ->
                    Class <- ColumnClasses,
                    {IdNo,Col} <- Class,
                    IdNo =/= ?TNO,
-                   [] =/= (Cs = [C || {?TNO,C} <- Class])]).
+                   Cs <- [[C || {?TNO,C} <- Class]],
+                   [] =/= Cs]).
 
 template_as_pattern(E) ->
     P = simple_template(E),
@@ -1317,21 +1317,22 @@ lu_skip(ColConstants, FilterData, PatternFrame, PatternVars,
     ColFil = [{Column, FId#qid.no} ||
                  {FId,{fil,Fil}} <-
                      filter_list(FilterData, Dependencies, State),
-                 [] =/= (SFs = safe_filter(reset_anno(Fil), PatternFrames,
-                                           BindFun, State, Imported)),
+                 SFs <- [safe_filter(reset_anno(Fil), PatternFrames,
+                                     BindFun, State, Imported)],
+                 [] =/= SFs,
                  {GId,PV} <- PatternVars,
-                 [] =/=
-                    (Cols = hd(frames_to_columns(SFs, [{GId, PV}],
-                                                 deref_lu_skip(LookupOp,
-                                                               Imported),
-                                                 const_selector(Imported),
-                                                 Imported, LookupOp))),
+                 Cols <- [hd(frames_to_columns(SFs, [{GId, PV}],
+                                               deref_lu_skip(LookupOp, Imported),
+                                               const_selector(Imported),
+                                               Imported, LookupOp))],
+                 [] =/= Cols,
                  %% The filter must not test more than one column (unless the
                  %% pattern has already done the test):
                  %% Note: if the pattern and the filter test the same
                  %% column, the filter will not be skipped.
                  %% (an example: {X=1} <- ..., X =:= 1).
-                 length(D = Cols -- PatternColumns) =:= 1,
+                 D <- [Cols -- PatternColumns],
+                 length(D) =:= 1,
                  {{_,Col} = Column, Constants} <- D,
                  %% Check that the following holds for all frames.
                  lists:all(
@@ -1828,8 +1829,10 @@ frames2cols(Fs, PatN, PatSizes, Vars, DerefFun, SelectorFun, CompOp) ->
                         %% seen as a bug.) Note: matching tables
                         %% cannot skip the filter, but looking up
                         %% one of the values should be OK.
-                        tl(Consts = DerefFun(V, F)) =:= [],
-                        (Const = (SelectorFun(F))(hd(Consts))) =/= no],
+                        Consts <- [DerefFun(V, F)],
+                        tl(Consts) =:= [],
+                        Const <- [(SelectorFun(F))(hd(Consts))],
+                        Const =/= no],
                sofs:relation(RL) % possibly empty
             end || F <- Fs && PatSz <- PatSizes],
     Ss = sofs:from_sets(Rs),
@@ -1858,7 +1861,8 @@ col_ignore(Vs, '==') ->
 pattern_sizes(PatternVars, Fs) ->
     [{QId#qid.no, Size} ||
         {QId,PV} <- PatternVars,
-        undefined =/= (Size = pattern_size(Fs, {var,anno0(),PV}, true))].
+        Size <- [pattern_size(Fs, {var,anno0(),PV}, true)],
+        undefined =/= (Size)].
 
 pattern_size(Fs, PatternVar, Exact) ->
     Fun = fun(F) -> (deref_pattern(_Imported = []))(PatternVar, F) end,
@@ -2177,7 +2181,8 @@ deref_binding(Bind, Frame, BFun, Imp) ->
     #bind{value = Value, op = Op0} = Bind,
     [{Val, Op} ||
         {Val, _Op}=ValOp <- deref(Value, Frame, BFun, Imp),
-        BFun(Val, Op = value_op(ValOp, Op0, Imp))].
+        Op <- [value_op(ValOp, Op0, Imp)],
+        BFun(Val, Op)].
 
 deref_list(L) ->
     Op = case lists:usort([Op || {_Val, Op} <- L]) of
diff --git a/lib/stdlib/src/sofs.erl b/lib/stdlib/src/sofs.erl
index 043a95e1c4..e0b2be7f9c 100644
--- a/lib/stdlib/src/sofs.erl
+++ b/lib/stdlib/src/sofs.erl
@@ -23,7 +23,6 @@
 -moduledoc({file, "../doc/src/sofs.md"}).
 
 -compile(nowarn_deprecated_catch).
--compile(nowarn_export_var_subexpr).
 
 -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,
@@ -4114,7 +4113,8 @@ setfun(T, Fun, Type, NType) ->
 		NT -> {?LIST(NS), NT}
 	    end;
 	NS when ?IS_ORDSET(NS) ->
-	    case unify_types(NType, NT = ?ORDTYPE(NS)) of
+            NT = ?ORDTYPE(NS),
+	    case unify_types(NType, NT) of
 		[] -> type_mismatch;
 		NT -> {?ORDDATA(NS), NT}
 	    end;
diff --git a/lib/wx/src/wxe_server.erl b/lib/wx/src/wxe_server.erl
index f84a8b13c3..b4b96bbf25 100644
--- a/lib/wx/src/wxe_server.erl
+++ b/lib/wx/src/wxe_server.erl
@@ -32,8 +32,6 @@
 -moduledoc false.
 -behaviour(gen_server).
 
--compile(nowarn_export_var_subexpr).
-
 %% API
 -export([start/1, stop/0, register_me/1, set_debug/2]).
 
@@ -64,7 +62,8 @@ start(SilentStart) ->
 	    case gen_server:start(?MODULE, [SilentStart], []) of
 		{ok, Pid}  ->
 		    {ok, Ref} = gen_server:call(Pid, get_env, infinity),
-		    wx:set_env(Env = #wx_env{ref=Ref,sv=Pid}),
+                    Env = #wx_env{ref=Ref,sv=Pid},
+		    wx:set_env(Env),
 		    Env;
 		{error, {Reason, _Stack}} ->
 		    erlang:error(Reason)
-- 
2.51.0

openSUSE Build Service is sponsored by