Sign Up
Log In
Log In
or
Sign Up
Places
All Projects
Status Monitor
Collapse sidebar
home:Ledest:erlang:23
erlang
4211-Eliminate-warnings-for-underscore-variable...
Overview
Repositories
Revisions
Requests
Users
Attributes
Meta
File 4211-Eliminate-warnings-for-underscore-variables-multiply.patch of Package erlang
From de24c93770a5321393058b4c5dfea870f5701950 Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Bj=C3=B6rn=20Gustavsson?= <bjorn@erlang.org> Date: Thu, 18 Feb 2021 12:36:22 +0100 Subject: [PATCH 1/9] Eliminate warnings for underscore variables multiply bound --- erts/emulator/test/binary_SUITE.erl | 8 ++++---- erts/emulator/test/map_SUITE.erl | 10 +++++----- lib/compiler/test/compilation_SUITE.erl | 6 +++--- lib/debugger/test/int_eval_SUITE.erl | 4 ++-- lib/kernel/test/code_SUITE.erl | 4 ++-- lib/parsetools/test/yecc_SUITE.erl | 10 +++++----- lib/runtime_tools/test/dbg_SUITE.erl | 24 ++++++++++++------------ lib/sasl/test/release_handler_SUITE.erl | 12 ++++++------ lib/sasl/test/systools_SUITE.erl | 4 ++-- lib/stdlib/test/gen_fsm_SUITE.erl | 12 ++++++------ lib/stdlib/test/gen_server_SUITE.erl | 12 +++++++----- lib/stdlib/test/gen_statem_SUITE.erl | 10 +++++----- 12 files changed, 59 insertions(+), 57 deletions(-) diff --git a/erts/emulator/test/binary_SUITE.erl b/erts/emulator/test/binary_SUITE.erl index c2c88d59a6..46434a8c1f 100644 --- a/erts/emulator/test/binary_SUITE.erl +++ b/erts/emulator/test/binary_SUITE.erl @@ -377,12 +377,12 @@ t_split_binary(Config) when is_list(Config) -> %% Sub binary of heap binary. split(L, make_sub_binary(B), size(B)), - {X,_Y} = split_binary(B, size(B) div 2), + {X,Y} = split_binary(B, size(B) div 2), split(binary_to_list(X), X, size(X)), %% Unaligned sub binary of heap binary. split(L, make_unaligned_sub_binary(B), size(B)), - {X,_Y} = split_binary(B, size(B) div 2), + {X,Y} = split_binary(B, size(B) div 2), split(binary_to_list(X), X, size(X)), %% Reference-counted binary. @@ -392,12 +392,12 @@ t_split_binary(Config) when is_list(Config) -> %% Sub binary of reference-counted binary. split(L2, make_sub_binary(B2), size(B2)), - {X2,_Y2} = split_binary(B2, size(B2) div 2), + {X2,Y2} = split_binary(B2, size(B2) div 2), split(binary_to_list(X2), X2, size(X2)), %% Unaligned sub binary of reference-counted binary. split(L2, make_unaligned_sub_binary(B2), size(B2)), - {X2,_Y2} = split_binary(B2, size(B2) div 2), + {X2,Y2} = split_binary(B2, size(B2) div 2), split(binary_to_list(X2), X2, size(X2)), ok. diff --git a/erts/emulator/test/map_SUITE.erl b/erts/emulator/test/map_SUITE.erl index dbf6fa58ed..457c84cf11 100644 --- a/erts/emulator/test/map_SUITE.erl +++ b/erts/emulator/test/map_SUITE.erl @@ -1702,7 +1702,7 @@ do_compare([Gen1, Gen2]) -> maps_lessthan(M1, M2) -> case {maps:size(M1),maps:size(M2)} of - {_S,_S} -> + {S,S} -> {K1,V1} = lists:unzip(term_sort(maps:to_list(M1))), {K2,V2} = lists:unzip(term_sort(maps:to_list(M2))), @@ -1721,9 +1721,9 @@ term_sort(L) -> L). -cmp(T1, T2, Exact) when is_tuple(T1) and is_tuple(T2) -> - case {size(T1),size(T2)} of - {_S,_S} -> cmp(tuple_to_list(T1), tuple_to_list(T2), Exact); +cmp(T1, T2, Exact) when is_tuple(T1), is_tuple(T2) -> + case {tuple_size(T1),tuple_size(T2)} of + {S,S} -> cmp(tuple_to_list(T1), tuple_to_list(T2), Exact); {S1,S2} when S1 < S2 -> -1; {S1,S2} when S1 > S2 -> 1 end; @@ -1741,7 +1741,7 @@ cmp(M1, M2, Exact) -> cmp_maps(M1, M2, Exact) -> case {maps:size(M1),maps:size(M2)} of - {_S,_S} -> + {S,S} -> {K1,V1} = lists:unzip(cmp_key_sort(maps:to_list(M1))), {K2,V2} = lists:unzip(cmp_key_sort(maps:to_list(M2))), diff --git a/lib/compiler/test/compilation_SUITE.erl b/lib/compiler/test/compilation_SUITE.erl index 8b3846bade..51a9775b76 100644 --- a/lib/compiler/test/compilation_SUITE.erl +++ b/lib/compiler/test/compilation_SUITE.erl @@ -178,7 +178,7 @@ try_it(Module, Conf) -> CompRc0 = compile:file(Src, [clint0,clint,ssalint,{outdir,Out},report, bin_opt_info|OtherOpts]), io:format("Result: ~p\n",[CompRc0]), - {ok,_Mod} = CompRc0, + {ok,Mod} = CompRc0, load_and_call(Out, Module), @@ -189,7 +189,7 @@ try_it(Module, Conf) -> {outdir,Out},report|OtherOpts]), io:format("Result: ~p\n",[CompRc1]), - {ok,_Mod} = CompRc1, + {ok,Mod} = CompRc1, load_and_call(Out, Module), ct:timetrap(Timetrap), @@ -198,7 +198,7 @@ try_it(Module, Conf) -> {outdir,Out},report,bin_opt_info, {inline,1000}|OtherOpts]), io:format("Result: ~p\n",[CompRc2]), - {ok,_Mod} = CompRc2, + {ok,Mod} = CompRc2, load_and_call(Out, Module), ct:timetrap(Timetrap), diff --git a/lib/debugger/test/int_eval_SUITE.erl b/lib/debugger/test/int_eval_SUITE.erl index 324a44bad8..456110a399 100644 --- a/lib/debugger/test/int_eval_SUITE.erl +++ b/lib/debugger/test/int_eval_SUITE.erl @@ -179,7 +179,7 @@ apply_interpreted_fun(Config) when is_list(Config) -> %% Called from uninterpreted code, error in fun F3 = spawn_eval(fun() -> ?IM:give_me_a_bad_fun() end), - {'EXIT',{snape,[{?IM,_FunName,_,_}|_]}} = + {'EXIT',{snape,[{?IM,_,_,_}|_]}} = spawn_eval(fun() -> F3(snape) end), %% Called from within interpreted code @@ -190,7 +190,7 @@ apply_interpreted_fun(Config) when is_list(Config) -> spawn_eval(fun() -> ?IM:do_apply(F1, snape) end), %% Called from within interpreted code, error in fun - {'EXIT',{snape,[{?IM,_FunName,_,_}|_]}} = + {'EXIT',{snape,[{?IM,_,_,_}|_]}} = spawn_eval(fun() -> ?IM:do_apply(F3, snape) end), %% Try some more complex funs. diff --git a/lib/kernel/test/code_SUITE.erl b/lib/kernel/test/code_SUITE.erl index 8ccf6e260e..855a2276ba 100644 --- a/lib/kernel/test/code_SUITE.erl +++ b/lib/kernel/test/code_SUITE.erl @@ -531,7 +531,7 @@ all_available_1(Config) -> Loaded = [{atom_to_list(M),P,true} || {M,P} <- code:all_loaded()], [] = Loaded -- Available, - {value, {ModStr,_Path,false} = NotLoaded} = + {value, {ModStr,_,false} = NotLoaded} = lists:search(fun({Name,_,Loaded}) -> not is_atom(Name) end, Available), ct:log("Testing with ~p",[NotLoaded]), @@ -543,7 +543,7 @@ all_available_1(Config) -> %% Load it Mod:module_info(), - {value, {ModStr,_Path,true}} = + {value, {ModStr,_,true}} = lists:search(fun({Name,_,_}) -> Name =:= ModStr end, code:all_available()), ok. diff --git a/lib/parsetools/test/yecc_SUITE.erl b/lib/parsetools/test/yecc_SUITE.erl index 8ad95f2b7f..e4747d8513 100644 --- a/lib/parsetools/test/yecc_SUITE.erl +++ b/lib/parsetools/test/yecc_SUITE.erl @@ -277,7 +277,7 @@ syntax(Config) when is_list(Config) -> ok = file:write_file(Filename, <<"Nonterminals nt. Terminals t. Rootsymbol nt. Endsymbol e. a - a.">>), - {error,[{_,[{2,yecc,{error,_yeccparser,_}}]}],[]} = + {error,[{_,[{2,yecc,{error,_,_}}]}],[]} = yecc:file(Filename, Ret), %% Syntax error: unknown nonterminal. @@ -2034,7 +2034,7 @@ otp_11286(Config) when is_list(Config) -> ok = rpc:call(Node, file, write_file, [Filename, Mini1]), {ok,ErlFile,[]} = rpc:call(Node, yecc, file, [Filename, Ret]), Opts = [return, warn_unused_vars,{outdir,Dir}], - {ok,_,_Warnings} = rpc:call(Node, compile, file, [ErlFile, Opts]), + {ok,_,_} = rpc:call(Node, compile, file, [ErlFile, Opts]), Mini2 = <<"Terminals t. Nonterminals nt. @@ -2043,7 +2043,7 @@ otp_11286(Config) when is_list(Config) -> ok = rpc:call(Node, file, write_file, [Filename, Mini2]), {ok,ErlFile,[]} = rpc:call(Node, yecc, file, [Filename, Ret]), Opts = [return, warn_unused_vars,{outdir,Dir}], - {ok,_,_Warnings} = rpc:call(Node, compile, file, [ErlFile, Opts]), + {ok,_,_} = rpc:call(Node, compile, file, [ErlFile, Opts]), Mini3 = <<"%% coding: latin-1 Terminals t. @@ -2053,7 +2053,7 @@ otp_11286(Config) when is_list(Config) -> ok = rpc:call(Node, file, write_file, [Filename, Mini3]), {ok,ErlFile,[]} = rpc:call(Node, yecc, file, [Filename, Ret]), Opts = [return, warn_unused_vars,{outdir,Dir}], - {ok,_,_Warnings} = rpc:call(Node, compile, file, [ErlFile, Opts]), + {ok,_,_} = rpc:call(Node, compile, file, [ErlFile, Opts]), true = test_server:stop_node(Node), ok. diff --git a/lib/runtime_tools/test/dbg_SUITE.erl b/lib/runtime_tools/test/dbg_SUITE.erl index 4d319c29c1..f28681ef05 100644 --- a/lib/runtime_tools/test/dbg_SUITE.erl +++ b/lib/runtime_tools/test/dbg_SUITE.erl @@ -72,7 +72,7 @@ big(Config) when is_list(Config) -> Pid = spawn_link(dbg_test, loop, [Config]), true = register(dbg_test_loop, Pid), {ok,_} = dbg:tracer(), - {ok,[{matched, _node, 1}]} = dbg:p(dbg_test_loop, [m,p,c]), + {ok,[{matched, _, 1}]} = dbg:p(dbg_test_loop, [m,p,c]), ok = dbg:c(dbg_test, test, [Config]), ok = dbg:i(), dbg_test_loop ! {dbg_test, stop}, @@ -82,7 +82,7 @@ big(Config) when is_list(Config) -> %% run/debug a Pid. Pid2=spawn_link(dbg_test,loop,[Config]), {ok,_} = dbg:tracer(), - {ok,[{matched, _node, 1}]} = dbg:p(Pid2,[s,r,p]), + {ok,[{matched, _, 1}]} = dbg:p(Pid2,[s,r,p]), ok = dbg:c(dbg_test, test, [Config]), ok = dbg:i(), Pid2 ! {dbg_test, stop}, @@ -182,7 +182,7 @@ send(Config) when is_list(Config) -> send_test(Rcvr, [{[self(),'_'],[],[]}]), %% Test that self() is not the receiving process - {ok, [{matched, _node, 1}, {saved, 2}]} = + {ok, [{matched, _, 1}, {saved, 2}]} = dbg:tpe(send, [{['$1','_'],[{'==','$1',{self}}],[]}]), send_test(Rcvr, make_ref(), false), @@ -197,7 +197,7 @@ send(Config) when is_list(Config) -> send_test(Rcvr, 2, make_ref(), false), %% Test clearing of trace pattern - {ok, [{matched, _node, 1}]} = dbg:ctpe(send), + {ok, [{matched, _, 1}]} = dbg:ctpe(send), send_test(Rcvr, make_ref(), true), %% Test complex message inspection @@ -291,7 +291,7 @@ recv(Config) when is_list(Config) -> recv_test(Rcvr, [{[node(), self(), '_'],[],[]}]), %% Test that self() is the not sending process - {ok, [{matched, _node, 1}, {saved, 2}]} = + {ok, [{matched, _, 1}, {saved, 2}]} = dbg:tpe('receive', [{[node(), '$1','_'],[{'==','$1',{self}}],[]}]), recv_test(Rcvr, make_ref(), false), @@ -306,7 +306,7 @@ recv(Config) when is_list(Config) -> recv_test(Rcvr, 2, make_ref(), false), %% Test clearing of trace pattern - {ok, [{matched, _node, 1}]} = dbg:ctpe('receive'), + {ok, [{matched, _, 1}]} = dbg:ctpe('receive'), recv_test(Rcvr, make_ref(), true), %% Test complex message inspection @@ -433,13 +433,13 @@ local_trace(Config) when is_list(Config) -> Z = list_to_integer(LZ), XYZ = {X, Y, Z}, io:format("Self = ~w = ~w~n", [S,XYZ]), - {ok, [{matched, _node, 1}]} = dbg:p(S,call), - {ok, [{matched, _node, 1}]} = dbg:p(XYZ,call), + {ok, [{matched, _, 1}]} = dbg:p(S,call), + {ok, [{matched, _, 1}]} = dbg:p(XYZ,call), if Z =:= 0 -> - {ok, [{matched, _node, 1}]} = dbg:p(Y,call); + {ok, [{matched, _, 1}]} = dbg:p(Y,call); true -> ok end, - {ok, [{matched, _node, 1}]} = dbg:p(L,call), + {ok, [{matched, _, 1}]} = dbg:p(L,call), {ok, _} = dbg:tpl(?MODULE,not_exported,[]), 4 = not_exported(2), [{trace,S,call,{?MODULE,not_exported,[2]}}] = flush(), @@ -506,8 +506,8 @@ saved_patterns(Config) when is_list(Config) -> {ok, _} = start(), try dbg:rtp(File), - {ok,[{matched,_node,1},{saved,1}]} = dbg:tp(dbg,ltp,0,1), - {ok, [{matched, _node, 1}]} = dbg:p(self(),call), + {ok, [{matched, _, 1},{saved,1}]} = dbg:tp(dbg,ltp,0,1), + {ok, [{matched, _, 1}]} = dbg:p(self(),call), dbg:ltp(), S = self(), [{trace,S,call,{dbg,ltp,[]},blahonga}] = flush() diff --git a/lib/sasl/test/release_handler_SUITE.erl b/lib/sasl/test/release_handler_SUITE.erl index d1bcc40049..23dc7d5c1d 100644 --- a/lib/sasl/test/release_handler_SUITE.erl +++ b/lib/sasl/test/release_handler_SUITE.erl @@ -1043,14 +1043,14 @@ otp_9395_check_and_purge(Conf) when is_list(Conf) -> [RelVsn2, filename:join(Rel2Dir, "sys.config")]), %% Do check_install_release, and check that old code still exists - {ok, _RelVsn1, []} = + {ok, _, []} = rpc:call(Node, release_handler, check_install_release, [RelVsn2]), true = rpc:call(Node,erlang,check_old_code,[b_lib]), true = rpc:call(Node,erlang,check_old_code,[b_server]), %% Do check_install_release with option 'purge' and check that old %% code is gone - {ok, _RelVsn1, []} = + {ok, _, []} = rpc:call(Node, release_handler, check_install_release, [RelVsn2,[purge]]), false = rpc:call(Node,erlang,check_old_code,[b_lib]), false = rpc:call(Node,erlang,check_old_code,[b_server]), @@ -1130,7 +1130,7 @@ otp_9395_update_many_mods(Conf) when is_list(Conf) -> true = rpc:call(Node,erlang,check_old_code,[m10]), %% Run check_install_release with purge before install this time - {_TCheck,{ok, _RelVsn1, []}} = + {_TCheck,{ok, _, []}} = timer:tc(rpc,call,[Node, release_handler, check_install_release, [RelVsn2,[purge]]]), % ct:log("check_install_release with purge: ~.2f",[_TCheck/1000000]), @@ -1140,7 +1140,7 @@ otp_9395_update_many_mods(Conf) when is_list(Conf) -> SWTFlag0 ! die, rpc:call(Node,?MODULE,garbage_collect,[]), _SWTFlag1 = spawn_link(Node, ?MODULE, scheduler_wall_time, []), - {TInst2,{ok, _RelVsn1, []}} = + {TInst2,{ok, _, []}} = timer:tc(rpc,call,[Node, release_handler, install_release, [RelVsn2]]), SWT2 = rpc:call(Node,erlang,statistics,[scheduler_wall_time]), % ct:log("install_release: ~.2f",[TInst2/1000000]), @@ -1245,7 +1245,7 @@ otp_9395_rm_many_mods(Conf) when is_list(Conf) -> true = rpc:call(Node,erlang,check_old_code,[m10]), %% Run check_install_release with purge before install this time - {_TCheck,{ok, _RelVsn1, []}} = + {_TCheck,{ok, _, []}} = timer:tc(rpc,call,[Node, release_handler, check_install_release, [RelVsn2,[purge]]]), % ct:log("check_install_release with purge: ~.2f",[_TCheck/1000000]), @@ -1255,7 +1255,7 @@ otp_9395_rm_many_mods(Conf) when is_list(Conf) -> SWTFlag0 ! die, rpc:call(Node,?MODULE,garbage_collect,[]), _SWTFlag1 = spawn_link(Node, ?MODULE, scheduler_wall_time, []), - {TInst2,{ok, _RelVsn1, []}} = + {TInst2,{ok, _, []}} = timer:tc(rpc,call,[Node, release_handler, install_release, [RelVsn2]]), SWT2 = rpc:call(Node,erlang,statistics,[scheduler_wall_time]), % ct:log("install_release: ~.2f",[TInst2/1000000]), diff --git a/lib/sasl/test/systools_SUITE.erl b/lib/sasl/test/systools_SUITE.erl index b9d8ff2e02..e934513d52 100644 --- a/lib/sasl/test/systools_SUITE.erl +++ b/lib/sasl/test/systools_SUITE.erl @@ -1999,8 +1999,8 @@ replace_app_relup(Config) when is_list(Config) -> check_start_stop_order(UpOrder, DownOrder) -> - {ok, [{_V0, [{_V1, [], Up}], - [{_V1, [], Down}] + {ok, [{_V0, [{V1, [], Up}], + [{V1, [], Down}] }]} = file:consult(relup), GetAppStartStop = fun(Instr) -> diff --git a/lib/stdlib/test/gen_fsm_SUITE.erl b/lib/stdlib/test/gen_fsm_SUITE.erl index 539dbe3edc..7f7a5d721b 100644 --- a/lib/stdlib/test/gen_fsm_SUITE.erl +++ b/lib/stdlib/test/gen_fsm_SUITE.erl @@ -470,7 +470,7 @@ sys1(Config) when is_list(Config) -> call_format_status(Config) when is_list(Config) -> {ok, Pid} = gen_fsm:start(gen_fsm_SUITE, [], []), Status = sys:get_status(Pid), - {status, Pid, _Mod, [_PDict, running, _, _, Data]} = Status, + {status, Pid, Mod, [_PDict, running, _, _, Data]} = Status, [format_status_called | _] = lists:reverse(Data), stop_it(Pid), @@ -478,7 +478,7 @@ call_format_status(Config) when is_list(Config) -> %% already checked by the previous test) {ok, Pid2} = gen_fsm:start({local, gfsm}, gen_fsm_SUITE, [], []), Status2 = sys:get_status(gfsm), - {status, Pid2, _Mod, [_PDict2, running, _, _, Data2]} = Status2, + {status, Pid2, Mod, [_PDict2, running, _, _, Data2]} = Status2, [format_status_called | _] = lists:reverse(Data2), stop_it(Pid2), @@ -487,13 +487,13 @@ call_format_status(Config) when is_list(Config) -> GlobalName1 = {global, "CallFormatStatus"}, {ok, Pid3} = gen_fsm:start(GlobalName1, gen_fsm_SUITE, [], []), Status3 = sys:get_status(GlobalName1), - {status, Pid3, _Mod, [_PDict3, running, _, _, Data3]} = Status3, + {status, Pid3, Mod, [_PDict3, running, _, _, Data3]} = Status3, [format_status_called | _] = lists:reverse(Data3), stop_it(Pid3), GlobalName2 = {global, {name, "term"}}, {ok, Pid4} = gen_fsm:start(GlobalName2, gen_fsm_SUITE, [], []), Status4 = sys:get_status(GlobalName2), - {status, Pid4, _Mod, [_PDict4, running, _, _, Data4]} = Status4, + {status, Pid4, Mod, [_PDict4, running, _, _, Data4]} = Status4, [format_status_called | _] = lists:reverse(Data4), stop_it(Pid4), @@ -503,13 +503,13 @@ call_format_status(Config) when is_list(Config) -> ViaName1 = {via, dummy_via, "CallFormatStatus"}, {ok, Pid5} = gen_fsm:start(ViaName1, gen_fsm_SUITE, [], []), Status5 = sys:get_status(ViaName1), - {status, Pid5, _Mod, [_PDict5, running, _, _, Data5]} = Status5, + {status, Pid5, Mod, [_PDict5, running, _, _, Data5]} = Status5, [format_status_called | _] = lists:reverse(Data5), stop_it(Pid5), ViaName2 = {via, dummy_via, {name, "term"}}, {ok, Pid6} = gen_fsm:start(ViaName2, gen_fsm_SUITE, [], []), Status6 = sys:get_status(ViaName2), - {status, Pid6, _Mod, [_PDict6, running, _, _, Data6]} = Status6, + {status, Pid6, Mod, [_PDict6, running, _, _, Data6]} = Status6, [format_status_called | _] = lists:reverse(Data6), stop_it(Pid6). diff --git a/lib/stdlib/test/gen_server_SUITE.erl b/lib/stdlib/test/gen_server_SUITE.erl index c9ebcef188..d5569586aa 100644 --- a/lib/stdlib/test/gen_server_SUITE.erl +++ b/lib/stdlib/test/gen_server_SUITE.erl @@ -1331,20 +1331,22 @@ do_otp_7669_stop() -> %% Verify that sys:get_status correctly calls our format_status/2 fun. call_format_status(Config) when is_list(Config) -> + Parent = self(), + {ok, Pid} = gen_server:start_link({local, call_format_status}, ?MODULE, [], []), Status1 = sys:get_status(call_format_status), - {status, Pid, _Mod, [_PDict, running, _Parent, _, Data1]} = Status1, + {status, Pid, Mod, [_Pdict1, running, Parent, _, Data1]} = Status1, [format_status_called | _] = lists:reverse(Data1), Status2 = sys:get_status(call_format_status, 5000), - {status, Pid, _Mod, [_PDict, running, _Parent, _, Data2]} = Status2, + {status, Pid, Mod, [_Pdict2, running, Parent, _, Data2]} = Status2, [format_status_called | _] = lists:reverse(Data2), %% check that format_status can handle a name being a pid (atom is %% already checked by the previous test) {ok, Pid3} = gen_server:start_link(gen_server_SUITE, [], []), Status3 = sys:get_status(Pid3), - {status, Pid3, _Mod, [_PDict3, running, _Parent, _, Data3]} = Status3, + {status, Pid3, Mod, [_PDict3, running, Parent, _, Data3]} = Status3, [format_status_called | _] = lists:reverse(Data3), %% check that format_status can handle a name being a term other than a @@ -1353,13 +1355,13 @@ call_format_status(Config) when is_list(Config) -> {ok, Pid4} = gen_server:start_link(GlobalName1, gen_server_SUITE, [], []), Status4 = sys:get_status(Pid4), - {status, Pid4, _Mod, [_PDict4, running, _Parent, _, Data4]} = Status4, + {status, Pid4, Mod, [_PDict4, running, Parent, _, Data4]} = Status4, [format_status_called | _] = lists:reverse(Data4), GlobalName2 = {global, {name, "term"}}, {ok, Pid5} = gen_server:start_link(GlobalName2, gen_server_SUITE, [], []), Status5 = sys:get_status(GlobalName2), - {status, Pid5, _Mod, [_PDict5, running, _Parent, _, Data5]} = Status5, + {status, Pid5, Mod, [_PDict5, running, Parent, _, Data5]} = Status5, [format_status_called | _] = lists:reverse(Data5), ok. diff --git a/lib/stdlib/test/gen_statem_SUITE.erl b/lib/stdlib/test/gen_statem_SUITE.erl index 4a593458e3..60844ce8ce 100644 --- a/lib/stdlib/test/gen_statem_SUITE.erl +++ b/lib/stdlib/test/gen_statem_SUITE.erl @@ -1251,7 +1251,7 @@ call_format_status(Config) -> gen_statem:start( {local, gstm}, ?MODULE, start_arg(Config, []), []), Status2 = sys:get_status(gstm), - {status,Pid2,_Mod,[_PDict2,running,_,_,Data2]} = Status2, + {status,Pid2,Mod,[_PDict2,running,_,_,Data2]} = Status2, [format_status_called|_] = lists:reverse(Data2), stop_it(Pid2), @@ -1262,7 +1262,7 @@ call_format_status(Config) -> gen_statem:start( GlobalName1, ?MODULE, start_arg(Config, []), []), Status3 = sys:get_status(GlobalName1), - {status,Pid3,_Mod,[_PDict3,running,_,_,Data3]} = Status3, + {status,Pid3,Mod,[_PDict3,running,_,_,Data3]} = Status3, [format_status_called|_] = lists:reverse(Data3), stop_it(Pid3), GlobalName2 = {global,{name, "term"}}, @@ -1270,7 +1270,7 @@ call_format_status(Config) -> gen_statem:start( GlobalName2, ?MODULE, start_arg(Config, []), []), Status4 = sys:get_status(GlobalName2), - {status,Pid4,_Mod,[_PDict4,running,_,_, Data4]} = Status4, + {status,Pid4,Mod,[_PDict4,running,_,_, Data4]} = Status4, [format_status_called|_] = lists:reverse(Data4), stop_it(Pid4), @@ -1280,7 +1280,7 @@ call_format_status(Config) -> ViaName1 = {via,dummy_via,"CallFormatStatus"}, {ok,Pid5} = gen_statem:start(ViaName1, ?MODULE, start_arg(Config, []), []), Status5 = sys:get_status(ViaName1), - {status,Pid5,_Mod, [_PDict5,running,_,_, Data5]} = Status5, + {status,Pid5,Mod, [_PDict5,running,_,_, Data5]} = Status5, [format_status_called|_] = lists:reverse(Data5), stop_it(Pid5), ViaName2 = {via,dummy_via,{name,"term"}}, @@ -1288,7 +1288,7 @@ call_format_status(Config) -> gen_statem:start( ViaName2, ?MODULE, start_arg(Config, []), []), Status6 = sys:get_status(ViaName2), - {status,Pid6,_Mod,[_PDict6,running,_,_,Data6]} = Status6, + {status,Pid6,Mod,[_PDict6,running,_,_,Data6]} = Status6, [format_status_called|_] = lists:reverse(Data6), stop_it(Pid6). -- 2.26.2
Locations
Projects
Search
Status Monitor
Help
OpenBuildService.org
Documentation
API Documentation
Code of Conduct
Contact
Support
@OBShq
Terms
openSUSE Build Service is sponsored by
The Open Build Service is an
openSUSE project
.
Sign Up
Log In
Places
Places
All Projects
Status Monitor