File 0747-system-test-Monitor-the-worker.patch of Package erlang
From 05f2da5ea6c34dec7c778ef38dd6eadf4468e598 Mon Sep 17 00:00:00 2001
From: Micael Karlberg <bmk@erlang.org>
Date: Tue, 19 Oct 2021 15:06:31 +0200
Subject: [PATCH 3/3] [system|test] Monitor the worker
Monitor the worker node so we detect a nodedown asap.
---
erts/test/upgrade_SUITE.erl | 58 +++++++++++++++++++++----------------
1 file changed, 33 insertions(+), 25 deletions(-)
diff --git a/erts/test/upgrade_SUITE.erl b/erts/test/upgrade_SUITE.erl
index 121384e64a..72383725cf 100644
--- a/erts/test/upgrade_SUITE.erl
+++ b/erts/test/upgrade_SUITE.erl
@@ -516,38 +516,46 @@ start_node(Start,ExpStatus,ExpVsn,ExpApps) ->
wait_node_up(ExpStatus,ExpVsn,ExpApps0) ->
ExpApps = [{A,V} || {A,V,_T} <- ExpApps0],
- Node = node_name(?upgr_sname),
+ Node = node_name(?upgr_sname),
+ erlang:monitor_node(Node, true),
wait_node_up(Node,ExpStatus,ExpVsn,lists:keysort(1,ExpApps),60).
wait_node_up(Node,ExpStatus,ExpVsn,ExpApps,0) ->
p("wait_node_up -> fail"),
+ erlang:monitor_node(Node, false),
ct:fail({app_check_failed,ExpVsn,ExpApps,
- rpc:call(Node,release_handler,which_releases,[ExpStatus]),
- rpc:call(Node,application,which_applications,[])});
+ rpc:call(Node, release_handler, which_releases, [ExpStatus]),
+ rpc:call(Node, application, which_applications, [])});
wait_node_up(Node,ExpStatus,ExpVsn,ExpApps,N) ->
- timer:sleep(2000),
- p("wait_node_up -> [~w] get release vsn and apps", [N]),
- case {rpc:call(Node,release_handler,which_releases,[ExpStatus]),
- rpc:call(Node, application, which_applications, [])} of
- {[{_,ExpVsn,_,_}],Apps} when is_list(Apps) ->
- p("wait_node_up -> [~w] expected release vsn", [N]),
- case [{A,V} || {A,_,V} <- lists:keysort(1,Apps)] of
- ExpApps ->
- p("wait_node_up -> [~w] expected apps", [N]),
- {ok, Node};
- UnexpApps ->
- p("wait_node_up -> [~w] still wrong apps:"
- "~n ~p", [N, UnexpApps]),
+ receive
+ {nodedown, Node} ->
+ p("wait_node_up -> [~w] got unexpected (~p) nodedown", [N, Node]),
+ ct:fail({app_check_failed, ExpVsn, ExpApps, nodedown, Node, N})
+ after 2000 ->
+ p("wait_node_up -> [~w] get release vsn and apps", [N]),
+ case {rpc:call(Node, release_handler, which_releases, [ExpStatus]),
+ rpc:call(Node, application, which_applications, [])} of
+ {[{_,ExpVsn,_,_}],Apps} when is_list(Apps) ->
+ p("wait_node_up -> [~w] expected release vsn", [N]),
+ case [{A,V} || {A,_,V} <- lists:keysort(1,Apps)] of
+ ExpApps ->
+ p("wait_node_up -> [~w] expected apps", [N]),
+ erlang:monitor_node(Node, false),
+ {ok, Node};
+ UnexpApps ->
+ p("wait_node_up -> [~w] still wrong apps:"
+ "~n ~p", [N, UnexpApps]),
+ wait_node_up(Node,ExpStatus,ExpVsn,ExpApps,N-1)
+ end;
+ {[{_,Vsn,_,_}],_} ->
+ p("wait_node_up -> [~w] still wrong release vsn:"
+ "~n ~p", [N, Vsn]),
+ wait_node_up(Node,ExpStatus,ExpVsn,ExpApps,N-1);
+ X ->
+ p("wait_node_up -> [~w] unexpected results:"
+ "~n ~p", [N, X]),
wait_node_up(Node,ExpStatus,ExpVsn,ExpApps,N-1)
- end;
- {[{_,Vsn,_,_}],_} ->
- p("wait_node_up -> [~w] still wrong release vsn:"
- "~n ~p", [N, Vsn]),
- wait_node_up(Node,ExpStatus,ExpVsn,ExpApps,N-1);
- X ->
- p("wait_node_up -> [~w] unexpected results:"
- "~n ~p", [N, X]),
- wait_node_up(Node,ExpStatus,ExpVsn,ExpApps,N-1)
+ end
end.
node_name(Sname) ->
--
2.31.1