File 2226-observer-Use-event-info-to-get-active-tab.patch of Package erlang

From 398a47ccf8dc25cdf1bc40a9df1f20e31145ac9d Mon Sep 17 00:00:00 2001
From: Dan Gudmundsson <dgud@erlang.org>
Date: Tue, 21 Mar 2017 14:36:33 +0100
Subject: [PATCH 4/5] observer: Use event info to get active tab

Previously changing tabs during high cpu-load, could make the
change go unnoticed, and thus the graphs did not get updated.
---
 lib/observer/src/observer_wx.erl | 101 ++++++++++++++-------------------------
 1 file changed, 35 insertions(+), 66 deletions(-)

diff --git a/lib/observer/src/observer_wx.erl b/lib/observer/src/observer_wx.erl
index 83de4fa64..83038620c 100644
--- a/lib/observer/src/observer_wx.erl
+++ b/lib/observer/src/observer_wx.erl
@@ -54,14 +54,7 @@
 	 status_bar,
 	 notebook,
 	 main_panel,
-	 pro_panel,
-	 port_panel,
-	 tv_panel,
-	 sys_panel,
-	 trace_panel,
-	 app_panel,
-	 perf_panel,
-	 allc_panel,
+         panels,
 	 active_tab,
 	 node,
 	 nodes,
@@ -145,13 +138,14 @@ setup(#state{frame = Frame} = State) ->
     wxFrame:setTitle(Frame, atom_to_list(node())),
     wxStatusBar:setStatusText(StatusBar, atom_to_list(node())),
 
-    wxNotebook:connect(Notebook, command_notebook_page_changing),
-    wxFrame:connect(Frame, close_window, [{skip, true}]),
+    wxNotebook:connect(Notebook, command_notebook_page_changed, [{skip, true}]),
+    wxFrame:connect(Frame, close_window, []),
     wxMenu:connect(Frame, command_menu_selected),
     wxFrame:show(Frame),
 
     %% Freeze and thaw is buggy currently
-    DoFreeze = [?wxMAJOR_VERSION,?wxMINOR_VERSION] < [2,9],
+    DoFreeze = [?wxMAJOR_VERSION,?wxMINOR_VERSION] < [2,9]
+        orelse element(1, os:type()) =:= win32,
     DoFreeze andalso wxWindow:freeze(Panel),
     %% I postpone the creation of the other tabs so they can query/use
     %% the window size
@@ -193,19 +187,21 @@ setup(#state{frame = Frame} = State) ->
 
     SysPid = wx_object:get_pid(SysPanel),
     SysPid ! {active, node()},
+    Panels = [{sys_panel, SysPanel, "System"},   %% In order
+              {perf_panel, PerfPanel, "Load Charts"},
+              {allc_panel, AllcPanel, ?ALLOC_STR},
+              {app_panel,  AppPanel, "Applications"},
+              {pro_panel, ProPanel, "Processes"},
+              {port_panel, PortPanel, "Ports"},
+              {tv_panel, TVPanel, "Table Viewer"},
+              {trace_panel, TracePanel, ?TRACE_STR}],
+
     UpdState = State#state{main_panel = Panel,
 			   notebook = Notebook,
 			   menubar = MenuBar,
 			   status_bar = StatusBar,
-			   sys_panel = SysPanel,
-			   pro_panel = ProPanel,
-			   port_panel = PortPanel,
-			   tv_panel  = TVPanel,
-			   trace_panel = TracePanel,
-			   app_panel = AppPanel,
-			   perf_panel = PerfPanel,
-			   allc_panel = AllcPanel,
 			   active_tab = SysPid,
+                           panels = Panels,
 			   node  = node(),
 			   nodes = Nodes
 			  },
@@ -228,10 +224,12 @@ setup(#state{frame = Frame} = State) ->
 %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
 %%Callbacks
-handle_event(#wx{event=#wxNotebook{type=command_notebook_page_changing}},
-	     #state{active_tab=Previous, node=Node} = State) ->
-    case get_active_pid(State) of
-	Previous -> {noreply, State};
+handle_event(#wx{event=#wxNotebook{type=command_notebook_page_changed, nSel=Next}},
+	     #state{active_tab=Previous, node=Node, panels=Panels} = State) ->
+    {_, Obj, _} = lists:nth(Next+1, Panels),
+    case wx_object:get_pid(Obj) of
+	Previous ->
+            {noreply, State};
 	Pid ->
 	    Previous ! not_active,
 	    Pid ! {active, Node},
@@ -362,8 +360,7 @@ handle_event(#wx{id = Id, event = #wxCommand{type = command_menu_selected}},
              end,
     {noreply, change_node_view(Node, LState)};
 
-handle_event(Event, State) ->
-    Pid = get_active_pid(State),
+handle_event(Event, #state{active_tab=Pid} = State) ->
     Pid ! Event,
     {noreply, State}.
 
@@ -388,7 +385,8 @@ handle_call({create_menus, TabMenus}, _From,
 handle_call({get_attrib, Attrib}, _From, State) ->
     {reply, get(Attrib), State};
 
-handle_call(get_tracer, _From, State=#state{trace_panel=TraceP}) ->
+handle_call(get_tracer, _From, State=#state{panels=Panels}) ->
+    {_, TraceP, _} = lists:keyfind(trace_panel, 1, Panels),
     {reply, TraceP, State};
 
 handle_call(get_active_node, _From, State=#state{node=Node}) ->
@@ -424,9 +422,7 @@ handle_info({nodedown, Node},
     create_txt_dialog(Frame, Msg, "Node down", ?wxICON_EXCLAMATION),
     {noreply, State3};
 
-handle_info({open_link, Id0}, State = #state{pro_panel=ProcViewer,
-					     port_panel=PortViewer,
-					     frame=Frame}) ->
+handle_info({open_link, Id0}, State = #state{panels=Panels,frame=Frame}) ->
     Id = case Id0 of
 	      [_|_] -> try list_to_pid(Id0) catch _:_ -> Id0 end;
 	      _ -> Id0
@@ -434,8 +430,10 @@ handle_info({open_link, Id0}, State = #state{pro_panel=ProcViewer,
     %% Forward to process tab
     case Id of
 	Pid when is_pid(Pid) ->
+            {pro_panel, ProcViewer, _} = lists:keyfind(pro_panel, 1, Panels),
 	    wx_object:get_pid(ProcViewer) ! {procinfo_open, Pid};
 	"#Port" ++ _ = Port ->
+            {port_panel, PortViewer, _} = lists:keyfind(port_panel, 1, Panels),
 	    wx_object:get_pid(PortViewer) ! {portinfo_open, Port};
 	_ ->
 	    Msg = io_lib:format("Information about ~p is not available or implemented",[Id]),
@@ -465,15 +463,12 @@ handle_info({stop, Me}, State) when Me =:= self() ->
 handle_info(_Info, State) ->
     {noreply, State}.
 
-stop_servers(#state{node=Node, log=LogOn, sys_panel=Sys, pro_panel=Procs, tv_panel=TVs,
-		    trace_panel=Trace, app_panel=Apps, perf_panel=Perfs,
-		    allc_panel=Alloc, port_panel=Ports} = _State) ->
+stop_servers(#state{node=Node, log=LogOn, panels=Panels} = _State) ->
     LogOn andalso rpc:block_call(Node, rb, stop, []),
     Me = self(),
-    Tabs = [Sys, Procs, Ports, TVs, Trace, Apps, Perfs, Alloc],
     Stop = fun() ->
 		   try
-		       _ = [wx_object:stop(Panel) || Panel <- Tabs],
+		       _ = [wx_object:stop(Panel) || {_, Panel, _} <- Panels],
 		       ok
 		   catch _:_ -> ok
 		   end,
@@ -549,8 +544,7 @@ connect2(NodeName, Opts, Cookie) ->
 	    {error, net_kernel, Reason}
     end.
 
-change_node_view(Node, State) ->
-    Tab = get_active_pid(State),
+change_node_view(Node, #state{active_tab=Tab} = State) ->
     Tab ! not_active,
     Tab ! {active, Node},
     StatusText = ["Observer - " | atom_to_list(Node)],
@@ -562,38 +556,13 @@ check_page_title(Notebook) ->
     Selection = wxNotebook:getSelection(Notebook),
     wxNotebook:getPageText(Notebook, Selection).
 
-get_active_pid(#state{notebook=Notebook, pro_panel=Pro, sys_panel=Sys,
-		      tv_panel=Tv, trace_panel=Trace, app_panel=App,
-		      perf_panel=Perf, allc_panel=Alloc, port_panel=Port
-		     }) ->
-    Panel = case check_page_title(Notebook) of
-		"Processes" -> Pro;
-		"Ports" -> Port;
-		"System" -> Sys;
-		"Table Viewer" -> Tv;
-		?TRACE_STR -> Trace;
-		"Load Charts" -> Perf;
-		"Applications" -> App;
-		?ALLOC_STR -> Alloc
-	    end,
-    wx_object:get_pid(Panel).
-
-pid2panel(Pid, #state{pro_panel=Pro, sys_panel=Sys,
-		      tv_panel=Tv, trace_panel=Trace, app_panel=App,
-		      perf_panel=Perf, allc_panel=Alloc, port_panel=Port}) ->
-    case Pid of
-	Pro -> "Processes";
-        Port -> "Ports";
-	Sys -> "System";
-	Tv -> "Table Viewer" ;
-	Trace -> ?TRACE_STR;
-	Perf -> "Load Charts";
-	App -> "Applications";
-	Alloc -> ?ALLOC_STR;
-	_ -> "unknown"
+pid2panel(Pid, #state{panels=Panels}) ->
+    PanelPids = [{Name, wx_object:get_pid(Obj)} || {Name, Obj, _} <- Panels],
+    case lists:keyfind(Pid, 2, PanelPids) of
+        false -> "unknown";
+        {Name,_} -> Name
     end.
 
-
 create_connect_dialog(ping, #state{frame = Frame, prev_node=Prev}) ->
     Dialog = wxTextEntryDialog:new(Frame, "Connect to node", [{value, Prev}]),
     case wxDialog:showModal(Dialog) of
-- 
2.12.2

openSUSE Build Service is sponsored by