File 2582-observer-Fixes-for-html-viewers.patch of Package erlang

From 1274131e7dbfe0d351b7bc6a99bdd8198a673385 Mon Sep 17 00:00:00 2001
From: Dan Gudmundsson <dgud@erlang.org>
Date: Tue, 25 Jun 2019 16:22:13 +0200
Subject: [PATCH 2/2] observer: Fixes for html viewers

---
 lib/observer/src/cdv_bin_cb.erl        | 37 +++++++++--------
 lib/observer/src/cdv_html_wx.erl       | 12 ++++--
 lib/observer/src/cdv_mod_cb.erl        |  3 +-
 lib/observer/src/cdv_persistent_cb.erl |  5 +--
 lib/observer/src/cdv_proc_cb.erl       |  2 +-
 lib/observer/src/cdv_term_cb.erl       | 23 +++++-----
 lib/observer/src/cdv_wx.erl            |  3 +-
 lib/observer/src/observer_defs.hrl     |  1 +
 lib/observer/src/observer_html_lib.erl | 76 +++++++++++++++++++---------------
 lib/observer/src/observer_lib.erl      | 13 ++++--
 lib/observer/src/observer_procinfo.erl | 19 ++++++---
 11 files changed, 111 insertions(+), 83 deletions(-)

diff --git a/lib/observer/src/cdv_bin_cb.erl b/lib/observer/src/cdv_bin_cb.erl
index 91d33474c8..819596b483 100644
--- a/lib/observer/src/cdv_bin_cb.erl
+++ b/lib/observer/src/cdv_bin_cb.erl
@@ -33,42 +33,43 @@ detail_pages() ->
     [{"Binary", fun init_bin_page/2}].
 
 init_bin_page(Parent,{Type,Bin}) ->
+    Cs = observer_lib:colors(Parent),
     cdv_multi_wx:start_link(
       Parent,
-      [{"Format \~p",cdv_html_wx,{Type,format_bin_fun("~p",Bin)}},
-       {"Format \~tp",cdv_html_wx,{Type,format_bin_fun("~tp",Bin)}},
-       {"Format \~w",cdv_html_wx,{Type,format_bin_fun("~w",Bin)}},
-       {"Format \~tw",cdv_html_wx,{Type,format_bin_fun("~tw",Bin)}},
-       {"Format \~s",cdv_html_wx,{Type,format_bin_fun("~s",Bin)}},
-       {"Format \~ts",cdv_html_wx,{Type,format_bin_fun("~ts",Bin)}},
-       {"Hex",cdv_html_wx,{Type,hex_binary_fun(Bin)}},
-       {"Term",cdv_html_wx,{Type,binary_to_term_fun(Bin)}}]).
+      [{"Format \~p",cdv_html_wx,{Type,format_bin_fun("~p",Bin,Cs)}},
+       {"Format \~tp",cdv_html_wx,{Type,format_bin_fun("~tp",Bin,Cs)}},
+       {"Format \~w",cdv_html_wx,{Type,format_bin_fun("~w",Bin,Cs)}},
+       {"Format \~tw",cdv_html_wx,{Type,format_bin_fun("~tw",Bin,Cs)}},
+       {"Format \~s",cdv_html_wx,{Type,format_bin_fun("~s",Bin,Cs)}},
+       {"Format \~ts",cdv_html_wx,{Type,format_bin_fun("~ts",Bin,Cs)}},
+       {"Hex",cdv_html_wx,{Type,hex_binary_fun(Bin,Cs)}},
+       {"Term",cdv_html_wx,{Type,binary_to_term_fun(Bin,Cs)}}]).
 
-format_bin_fun(Format,Bin) ->
+format_bin_fun(Format,Bin,Cs) ->
     fun() ->
 	    try io_lib:format(Format,[Bin]) of
-		Str -> plain_html(lists:flatten(Str))
+		Str -> plain_html(lists:flatten(Str),Cs)
 	    catch error:badarg ->
 		    Warning = "This binary cannot be formatted with " ++ Format,
-		    observer_html_lib:warning(Warning)
+		    observer_html_lib:warning(Warning,Cs)
 	    end
     end.
 
-binary_to_term_fun(Bin) ->
+binary_to_term_fun(Bin,Cs) ->
     fun() ->
 	    try binary_to_term(Bin) of
-		Term -> plain_html(io_lib:format("~tp",[Term]))
+		Term -> plain_html(io_lib:format("~tp",[Term]),Cs)
 	    catch error:badarg ->
 		    Warning = "This binary cannot be converted to an Erlang term",
-		    observer_html_lib:warning(Warning)
+		    observer_html_lib:warning(Warning,Cs)
 	    end
     end.
 
 -define(line_break,25).
-hex_binary_fun(Bin) ->
+hex_binary_fun(Bin,Cs) ->
     fun() ->
 	    S = "<<" ++ format_hex(Bin,?line_break) ++ ">>",
-	    plain_html(io_lib:format("~s",[S]))
+	    plain_html(io_lib:format("~s",[S]), Cs)
     end.
 
 format_hex(<<>>,_) ->
@@ -82,5 +83,5 @@ format_hex(<<B1:4,B2:4,Bin/binary>>,N) ->
     [integer_to_list(B1,16),integer_to_list(B2,16),$,
      | format_hex(Bin,N-1)].
 
-plain_html(Text) ->
-    observer_html_lib:plain_page(Text).
+plain_html(Text,Cs) ->
+    observer_html_lib:plain_page(Text,Cs).
diff --git a/lib/observer/src/cdv_html_wx.erl b/lib/observer/src/cdv_html_wx.erl
index 8956173c93..33cd0c9fd1 100644
--- a/lib/observer/src/cdv_html_wx.erl
+++ b/lib/observer/src/cdv_html_wx.erl
@@ -30,7 +30,8 @@
 
 %% Records
 -record(state,
-	{panel,
+	{parent,
+         panel,
 	 app,         %% which tool is the user
 	 expand_table,
          expand_wins=[],
@@ -62,7 +63,7 @@ init(ParentWin, HtmlText, Tab, App) ->
     HtmlWin = observer_lib:html_window(ParentWin),
     wxHtmlWindow:setPage(HtmlWin,HtmlText),
     wx_misc:endBusyCursor(),
-    {HtmlWin, #state{panel=HtmlWin,expand_table=Tab,app=App}}.
+    {HtmlWin, #state{parent=ParentWin, panel=HtmlWin,expand_table=Tab,app=App}}.
 
 init(ParentWin, Callback) ->
     {HtmlWin, State} = init(ParentWin, "", undefined, cdv),
@@ -70,12 +71,15 @@ init(ParentWin, Callback) ->
 
 %%%%%%%%%%%%%%%%%%%%%%% Callbacks %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
-handle_info(active, #state{panel=HtmlWin,delayed_fetch=Callback}=State)
+handle_info(active, #state{parent=Parent, panel=HtmlWin,delayed_fetch=Callback}=State)
   when Callback=/=undefined ->
     observer_lib:display_progress_dialog(HtmlWin,
                                          "Crashdump Viewer",
                                          "Reading data"),
-    {{expand,HtmlText,Tab},TW} = Callback:get_info(),
+    {{expand,Title,Info,Tab},TW} = Callback:get_info(),
+    Cs = observer_lib:colors(Parent),
+    HtmlText = observer_html_lib:expandable_term(Title,Info,Tab,Cs),
+
     observer_lib:sync_destroy_progress_dialog(),
     wx_misc:beginBusyCursor(),
     wxHtmlWindow:setPage(HtmlWin,HtmlText),
diff --git a/lib/observer/src/cdv_mod_cb.erl b/lib/observer/src/cdv_mod_cb.erl
index 2183e1aa3d..7f2cd0cf87 100644
--- a/lib/observer/src/cdv_mod_cb.erl
+++ b/lib/observer/src/cdv_mod_cb.erl
@@ -85,7 +85,8 @@ init_old_comp_page(Parent, Info) ->
 init_info_page(Parent, undefined) ->
     init_info_page(Parent, "");
 init_info_page(Parent, String) ->
-    cdv_html_wx:start_link(Parent,observer_html_lib:plain_page(String)).
+    Cs = observer_lib:colors(Parent),
+    cdv_html_wx:start_link(Parent,observer_html_lib:plain_page(String,Cs)).
 
 format({Bin,q}) when is_binary(Bin) ->
     [$'|binary_to_list(Bin)];
diff --git a/lib/observer/src/cdv_persistent_cb.erl b/lib/observer/src/cdv_persistent_cb.erl
index d5da18f7fc..90abc6a4f5 100644
--- a/lib/observer/src/cdv_persistent_cb.erl
+++ b/lib/observer/src/cdv_persistent_cb.erl
@@ -26,7 +26,4 @@
 get_info() ->
     Tab = ets:new(pt_expand,[set,public]),
     {ok,PT,TW} = crashdump_viewer:persistent_terms(),
-    {{expand,
-      observer_html_lib:expandable_term("Persistent Terms",PT,Tab),
-      Tab},
-     TW}.
+    {{expand, "Persistent Terms", PT, Tab}, TW}.
diff --git a/lib/observer/src/cdv_proc_cb.erl b/lib/observer/src/cdv_proc_cb.erl
index 2497b4889e..61bd86f188 100644
--- a/lib/observer/src/cdv_proc_cb.erl
+++ b/lib/observer/src/cdv_proc_cb.erl
@@ -108,7 +108,7 @@ init_stack_page(Parent, Info) ->
 init_memory_page(Parent, Info0, Tag, Heading) ->
     Info = proplists:get_value(Tag,Info0),
     Tab = proplists:get_value(expand_table,Info0),
-    Html = observer_html_lib:expandable_term(Heading,Info,Tab),
+    Html = observer_html_lib:expandable_term(Heading,Info,Tab, observer_lib:colors(Parent)),
     cdv_html_wx:start_link(Parent,{expand,Html,Tab}).
 
 init_ets_page(Parent, Info) ->
diff --git a/lib/observer/src/cdv_term_cb.erl b/lib/observer/src/cdv_term_cb.erl
index 85da1d227a..a2a7a8750d 100644
--- a/lib/observer/src/cdv_term_cb.erl
+++ b/lib/observer/src/cdv_term_cb.erl
@@ -35,31 +35,32 @@ init_term_page(ParentWin, {Type, [Term, Tab]}) ->
     Expanded = expand(Term, true),
     BinSaved = expand(Term, Tab),
     observer_lib:report_progress({ok,stop_pulse}),
+    Cs = observer_lib:colors(ParentWin),
     cdv_multi_wx:start_link(
       ParentWin,
-      [{"Format \~p",cdv_html_wx,{Type, format_term_fun("~p",BinSaved,Tab)}},
-       {"Format \~tp",cdv_html_wx,{Type,format_term_fun("~tp",BinSaved,Tab)}},
-       {"Format \~w",cdv_html_wx,{Type,format_term_fun("~w",BinSaved,Tab)}},
-       {"Format \~tw",cdv_html_wx,{Type,format_term_fun("~tw",BinSaved,Tab)}},
-       {"Format \~s",cdv_html_wx,{Type,format_term_fun("~s",Expanded,Tab)}},
-       {"Format \~ts",cdv_html_wx,{Type,format_term_fun("~ts",Expanded,Tab)}}]).
+      [{"Format \~p",cdv_html_wx,{Type, format_term_fun("~p",BinSaved,Tab,Cs)}},
+       {"Format \~tp",cdv_html_wx,{Type,format_term_fun("~tp",BinSaved,Tab,Cs)}},
+       {"Format \~w",cdv_html_wx,{Type,format_term_fun("~w",BinSaved,Tab,Cs)}},
+       {"Format \~tw",cdv_html_wx,{Type,format_term_fun("~tw",BinSaved,Tab,Cs)}},
+       {"Format \~s",cdv_html_wx,{Type,format_term_fun("~s",Expanded,Tab,Cs)}},
+       {"Format \~ts",cdv_html_wx,{Type,format_term_fun("~ts",Expanded,Tab,Cs)}}]).
 
-format_term_fun(Format,Term,Tab) ->
+format_term_fun(Format,Term,Tab,Cs) ->
     fun() ->
             observer_lib:report_progress({ok,"Formatting term"}),
             observer_lib:report_progress({ok,start_pulse}),
 	    try io_lib:format(Format,[Term]) of
-		Str -> {expand, plain_html(Str), Tab}
+		Str -> {expand, plain_html(Str,Cs), Tab}
 	    catch error:badarg ->
 		    Warning = "This term cannot be formatted with " ++ Format,
-		    observer_html_lib:warning(Warning)
+		    observer_html_lib:warning(Warning,Cs)
             after
                     observer_lib:report_progress({ok,stop_pulse})
 	    end
     end.
 
-plain_html(Text) ->
-    observer_html_lib:plain_page(Text).
+plain_html(Text,Cs) ->
+    observer_html_lib:plain_page(Text,Cs).
 
 expand(['#CDVBin',Offset,Size,Pos], true) ->
     {ok,Bin} = crashdump_viewer:expand_binary({Offset,Size,Pos}),
diff --git a/lib/observer/src/cdv_wx.erl b/lib/observer/src/cdv_wx.erl
index 7100cc8790..8ad5da857e 100644
--- a/lib/observer/src/cdv_wx.erl
+++ b/lib/observer/src/cdv_wx.erl
@@ -197,8 +197,7 @@ setup(#state{frame=Frame, notebook=Notebook}=State) ->
     MemPanel = add_page(Notebook, ?MEM_STR, cdv_multi_wx, cdv_mem_cb),
 
     %% Persistent Terms Panel
-    PersistentPanel = add_page(Notebook, ?PERSISTENT_STR,
-                               cdv_html_wx, cdv_persistent_cb),
+    PersistentPanel = add_page(Notebook, ?PERSISTENT_STR, cdv_html_wx, cdv_persistent_cb),
 
     %% Memory Panel
     IntPanel = add_page(Notebook, ?INT_STR, cdv_multi_wx, cdv_int_tab_cb),
diff --git a/lib/observer/src/observer_defs.hrl b/lib/observer/src/observer_defs.hrl
index 504d0877d9..7902b32cba 100644
--- a/lib/observer/src/observer_defs.hrl
+++ b/lib/observer/src/observer_defs.hrl
@@ -36,6 +36,7 @@
 	 check = false
 	}).
 
+-record(colors, {fg, even, odd}).
 -record(attrs, {even, odd, searched, deleted, changed_odd, changed_even, new_odd, new_even}).
 -define(EVEN(Row), ((Row rem 2) =:= 0)).
 -define(BG_EVEN,    {230,230,250}).
diff --git a/lib/observer/src/observer_html_lib.erl b/lib/observer/src/observer_html_lib.erl
index c67fa28c6d..4c92a8faab 100644
--- a/lib/observer/src/observer_html_lib.erl
+++ b/lib/observer/src/observer_html_lib.erl
@@ -24,9 +24,9 @@
 %% viewer. No logic or states are kept by this module.
 %%
 
--export([plain_page/1,
-	 expandable_term/3,
-	 warning/1]).
+-export([plain_page/2,
+	 expandable_term/4,
+	 warning/2]).
 
 -include("crashdump_viewer.hrl").
 -include("observer_defs.hrl").
@@ -34,8 +34,9 @@
 %%%-----------------------------------------------------------------
 %%% Display the given information as is, no heading
 %%% Empty body if no info exists.
-warning(Info) ->
-    header(body(warning_body(Info))).
+warning(Info, Colors0) ->
+    Colors = convert(Colors0),
+    header(body(warning_body(Info), Colors)).
 
 warning_body(Info) ->
     [warn(Info)].
@@ -43,18 +44,22 @@ warning_body(Info) ->
 %%%-----------------------------------------------------------------
 %%% Display the given information as is, no heading
 %%% Empty body if no info exists.
-plain_page(Info) ->
-    header(body(plain_body(Info))).
+plain_page(Info, Colors0) ->
+    Colors = convert(Colors0),
+    header(body(plain_body(Info), Colors)).
 
 plain_body(Info) ->
     [pre(href_proc_port(lists:flatten(Info)))].
 
 %%%-----------------------------------------------------------------
 %%% Expanded memory
-expandable_term(Heading,Expanded,Tab) ->
-    header(Heading,body(expandable_term_body(Heading,Expanded,Tab))).
+expandable_term(Heading,Expanded,Tab, Colors0) ->
+    Colors = convert(Colors0),
+    header(Heading,
+           body(expandable_term_body(Heading,Expanded,Tab,Colors),
+                Colors)).
     
-expandable_term_body(Heading,[],_Tab) ->
+expandable_term_body(Heading,[],_Tab, _) ->
     [case Heading of
 	 "MsgQueue" -> "No messages were found";
 	 "Message Queue" -> "No messages were found";
@@ -65,7 +70,7 @@ expandable_term_body(Heading,[],_Tab) ->
          "SaslLog"    -> "No log entry was found";
          "Persistent Terms" -> "No persistent terms were found"
      end];
-expandable_term_body(Heading,Expanded,Tab) ->
+expandable_term_body(Heading,Expanded,Tab, Colors) ->
     Attr = "BORDER=0 CELLPADDING=0 CELLSPACING=1 WIDTH=100%",
     [case Heading of
 	 "MsgQueue" ->
@@ -74,7 +79,7 @@ expandable_term_body(Heading,Expanded,Tab) ->
 		      [th("WIDTH=70%","Message"),
 		       th("WIDTH=30%","SeqTraceToken")]) |
 		    element(1, lists:mapfoldl(fun(Msg, Even) ->
-						      {msgq_table(Tab, Msg, Even),
+						      {msgq_table(Tab, Msg, Even, Colors),
 						       not Even}
 					      end,
 					      true, Expanded))]);
@@ -84,7 +89,7 @@ expandable_term_body(Heading,Expanded,Tab) ->
 		      [th("WIDTH=10%","Id"),
 		       th("WIDTH=90%","Message")]) |
 		    element(1, lists:mapfoldl(fun(Msg, {Even,N}) ->
-						      {msgq_table(Tab, Msg, N, Even),
+						      {msgq_table(Tab, Msg, N, Even, Colors),
 						       {not Even, N+1}}
 					      end,
 					      {true,1}, Expanded))]);
@@ -94,7 +99,7 @@ expandable_term_body(Heading,Expanded,Tab) ->
 		      [th("WIDTH=20%","Label"),
 		       th("WIDTH=80%","Term")]) |
 		    element(1, lists:mapfoldl(fun(Entry, Even) ->
-						      {stackdump_table(Tab, Entry, Even),
+						      {stackdump_table(Tab, Entry, Even, Colors),
 						       not Even}
 					      end, true, Expanded))]);
 	 "ProcState" ->
@@ -103,7 +108,7 @@ expandable_term_body(Heading,Expanded,Tab) ->
 		      [th("WIDTH=20%","Label"),
 		       th("WIDTH=80%","Information")]) |
 		    element(1, lists:mapfoldl(fun(Entry, Even) ->
-						      {proc_state(Tab, Entry,Even),
+						      {proc_state(Tab, Entry,Even, Colors),
 						       not Even}
 					      end, true, Expanded))]);         
      "SaslLog"  ->
@@ -115,24 +120,24 @@ expandable_term_body(Heading,Expanded,Tab) ->
 		      [th("WIDTH=30%","Key"),
 		       th("WIDTH=70%","Value")]) |
 		    element(1, lists:mapfoldl(fun(Entry, Even) ->
-						      {dict_table(Tab, Entry,Even),
+						      {dict_table(Tab, Entry, Even, Colors),
 						       not Even}
 					      end, true, Expanded))])
      end].
 
-msgq_table(Tab,{Msg0,Token0}, Even) ->
+msgq_table(Tab,{Msg0,Token0}, Even, Colors) ->
     Token = case Token0 of
 		[] -> "";
 		_ -> io_lib:fwrite("~w",[Token0])
 	    end,
     Msg = all_or_expand(Tab,Msg0),
-    tr(color(Even),[td(pre(Msg)), td(Token)]).
+    tr(color(Even, Colors),[td(pre(Msg)), td(Token)]).
 
-msgq_table(Tab,Msg0, Id, Even) ->
+msgq_table(Tab,Msg0, Id, Even, Colors) ->
     Msg = all_or_expand(Tab,Msg0),
-    tr(color(Even),[td(integer_to_list(Id)), td(pre(Msg))]).
+    tr(color(Even, Colors),[td(integer_to_list(Id)), td(pre(Msg))]).
 
-stackdump_table(Tab,{Label0,Term0},Even) ->
+stackdump_table(Tab,{Label0,Term0},Even, Colors) ->
     Label = io_lib:format("~ts",[Label0]),
     Term = case atom_to_list(Label0) of
                "y" ++ _ ->
@@ -144,17 +149,17 @@ stackdump_table(Tab,{Label0,Term0},Even) ->
                    %% greater than 255.
                    href_proc_port(Term0)
            end,
-    tr(color(Even), [td("VALIGN=center",pre(Label)), td(pre(Term))]).
+    tr(color(Even, Colors), [td("VALIGN=center",pre(Label)), td(pre(Term))]).
 
-dict_table(Tab,{Key0,Value0}, Even) ->
+dict_table(Tab,{Key0,Value0}, Even, Colors) ->
     Key = all_or_expand(Tab,Key0),
     Value = all_or_expand(Tab,Value0),
-    tr(color(Even), [td("VALIGN=center",pre(Key)), td(pre(Value))]).
+    tr(color(Even, Colors), [td("VALIGN=center",pre(Key)), td(pre(Value))]).
 
-proc_state(Tab,{Key0,Value0}, Even) ->
+proc_state(Tab,{Key0,Value0}, Even, Colors) ->
     Key = lists:flatten(io_lib:format("~ts",[Key0])),
     Value = all_or_expand(Tab,Value0),
-    tr(color(Even), [td("VALIGN=center",Key), td(pre(Value))]).
+    tr(color(Even, Colors), [td("VALIGN=center",Key), td(pre(Value))]).
 
 all_or_expand(Tab,Term) ->
     Preview = io_lib:format("~tP",[Term,8]),
@@ -180,8 +185,8 @@ all_or_expand(Tab,Bin,_PreviewStr,_Expand)
     Term = io_lib:format("~tp", [OBSBin]),
     href_proc_port(lists:flatten(Term), true).
 
-color(true) -> io_lib:format("BGCOLOR=\"#~2.16.0B~2.16.0B~2.16.0B\"", tuple_to_list(?BG_EVEN));
-color(false) -> io_lib:format("BGCOLOR=\"#~2.16.0B~2.16.0B~2.16.0B\"", tuple_to_list(?BG_ODD)).
+color(true, #colors{even=Even}) -> "BGCOLOR="++Even;
+color(false,#colors{odd=Odd})   -> "BGCOLOR="++Odd.
 
 %%%-----------------------------------------------------------------
 %%% Internal library
@@ -189,10 +194,10 @@ start_html() ->
     "<HTML>\n".
 stop_html() ->
     "</HTML>".
-start_html_body() ->
-    "<BODY BGCOLOR=\"#FFFFFF\">\n".
+start_html_body(#colors{even=Even, fg=Fg}) ->
+    "<BODY BGCOLOR=" ++ Even ++ ">\n <FONT COLOR=" ++ Fg ++ ">\n".
 stop_html_body() ->
-    "</BODY>\n".
+    "</FONT> </BODY>\n".
 
 header(Body) ->
     header("","",Body).
@@ -214,8 +219,8 @@ only_html_header(Title,JavaScript) ->
      JavaScript,
      "</HEAD>\n"].
 
-body(Text) ->
-    [start_html_body(),
+body(Text, Colors) ->
+    [start_html_body(Colors),
      Text,
      stop_html_body()].
 
@@ -426,3 +431,8 @@ warn([]) ->
     [];
 warn(Warning) ->
     font("COLOR=\"#FF0000\"",p([Warning,br(),br()])).
+
+convert(#colors{fg={FR,FB,FG}, even={ER,EB,EG}, odd={OR,OG,OB}}) ->
+    #colors{fg   = io_lib:format("\"#~2.16.0B~2.16.0B~2.16.0B\"", [FR,FB,FG]),
+            even = io_lib:format("\"#~2.16.0B~2.16.0B~2.16.0B\"", [ER,EB,EG]),
+            odd  = io_lib:format("\"#~2.16.0B~2.16.0B~2.16.0B\"", [OR,OG,OB])}.
diff --git a/lib/observer/src/observer_lib.erl b/lib/observer/src/observer_lib.erl
index 5cb6645cb9..7d115306bd 100644
--- a/lib/observer/src/observer_lib.erl
+++ b/lib/observer/src/observer_lib.erl
@@ -28,7 +28,7 @@
 	 interval_dialog/4, start_timer/1, start_timer/2, stop_timer/1, timer_config/1,
 	 display_info/2, display_info/3, fill_info/2, update_info/2, to_str/1,
 	 create_menus/3, create_menu_item/3,
-	 is_darkmode/1, create_attrs/1,
+	 is_darkmode/1, colors/1, create_attrs/1,
 	 set_listctrl_col_size/2, mix/3,
 	 create_status_bar/1,
 	 html_window/1, html_window/2,
@@ -373,15 +373,19 @@ create_menu_item(separator, Menu, Index) ->
     wxMenu:insertSeparator(Menu, Index),
     Index+1.
 
-create_attrs(Window) ->
+colors(Window) ->
     DarkMode = is_darkmode(wxWindow:getBackgroundColour(Window)),
-    Font = wxSystemSettings:getFont(?wxSYS_DEFAULT_GUI_FONT),
     Text = case wxSystemSettings:getColour(?wxSYS_COLOUR_LISTBOXTEXT) of
                {255,255,255,_} when not DarkMode -> {10,10,10}; %% Is white on Mac for some reason
                Color -> Color
            end,
     Even = wxSystemSettings:getColour(?wxSYS_COLOUR_LISTBOX),
     Odd = mix(Even, wxSystemSettings:getColour(?wxSYS_COLOUR_HIGHLIGHT), 0.8),
+    #colors{fg=rgb(Text), even=rgb(Even), odd=rgb(Odd)}.
+
+create_attrs(Window) ->
+    Font = wxSystemSettings:getFont(?wxSYS_DEFAULT_GUI_FONT),
+    #colors{fg=Text, even=Even, odd=Odd} = colors(Window),
     #attrs{even = wxListItemAttr:new(Text, Even, Font),
            odd  = wxListItemAttr:new(Text, Odd, Font),
            deleted = wxListItemAttr:new(?FG_DELETED, ?BG_DELETED, Font),
@@ -392,6 +396,9 @@ create_attrs(Window) ->
            searched = wxListItemAttr:new(Text, ?BG_SEARCHED, Font)
           }.
 
+rgb({R,G,B,_}) -> {R,G,B};
+rgb({_,_,_}=RGB) -> RGB.
+
 mix(RGB,{MR,MG,MB,_}, V) ->
     mix(RGB, {MR,MG,MB}, V);
 mix({R,G,B,_}, RGB, V) ->
diff --git a/lib/observer/src/observer_procinfo.erl b/lib/observer/src/observer_procinfo.erl
index bd5fed0951..637a090a15 100644
--- a/lib/observer/src/observer_procinfo.erl
+++ b/lib/observer/src/observer_procinfo.erl
@@ -214,12 +214,14 @@ init_process_page(Panel, Pid) ->
 
 init_message_page(Parent, Pid, Table) ->
     Win = observer_lib:html_window(Parent),
+    Cs = observer_lib:colors(Parent),
     Update = fun() ->
 		     case observer_wx:try_rpc(node(Pid), erlang, process_info,
 					      [Pid, messages])
 		     of
 			 {messages, Messages} ->
-			     Html = observer_html_lib:expandable_term("Message Queue", Messages, Table),
+			     Html = observer_html_lib:expandable_term("Message Queue", Messages,
+                                                                      Table, Cs),
 			     wxHtmlWindow:setPage(Win, Html);
 			 _ ->
 			     throw(process_undefined)
@@ -230,11 +232,12 @@ init_message_page(Parent, Pid, Table) ->
 
 init_dict_page(Parent, Pid, Table) ->
     Win = observer_lib:html_window(Parent),
+    Cs = observer_lib:colors(Parent),
     Update = fun() ->
 		     case observer_wx:try_rpc(node(Pid), erlang, process_info, [Pid, dictionary])
 		     of
 			 {dictionary,Dict} ->
-			     Html = observer_html_lib:expandable_term("Dictionary", Dict, Table),
+			     Html = observer_html_lib:expandable_term("Dictionary", Dict, Table, Cs),
 			     wxHtmlWindow:setPage(Win, Html);
 			 _ ->
 			     throw(process_undefined)
@@ -254,6 +257,8 @@ init_stack_page(Parent, Pid) ->
     wxListCtrl:insertColumn(LCtrl, 1, Li),
     wxListCtrl:setColumnWidth(LCtrl, 1, Scale * 300),
     wxListItem:destroy(Li),
+    Even = wxSystemSettings:getColour(?wxSYS_COLOUR_LISTBOX),
+    Odd = observer_lib:mix(Even, wxSystemSettings:getColour(?wxSYS_COLOUR_HIGHLIGHT), 0.8),
     Update = fun() ->
 		     case observer_wx:try_rpc(node(Pid), erlang, process_info,
 					      [Pid, current_stacktrace])
@@ -262,8 +267,8 @@ init_stack_page(Parent, Pid) ->
 			     wxListCtrl:deleteAllItems(LCtrl),
 			     wx:foldl(fun({M, F, A, Info}, Row) ->
 					      _Item = wxListCtrl:insertItem(LCtrl, Row, ""),
-					      ?EVEN(Row) andalso
-						  wxListCtrl:setItemBackgroundColour(LCtrl, Row, ?BG_EVEN),
+					      ?EVEN(Row) orelse
+						  wxListCtrl:setItemBackgroundColour(LCtrl, Row, Odd),
 					      wxListCtrl:setItem(LCtrl, Row, 0, observer_lib:to_str({M,F,A})),
 					      FileLine = case Info of
 							     [{file,File},{line,Line}] ->
@@ -288,9 +293,10 @@ init_stack_page(Parent, Pid) ->
 
 init_state_page(Parent, Pid, Table) ->
     Win = observer_lib:html_window(Parent),
+    Cs = observer_lib:colors(Parent),
     Update = fun() ->
 		     StateInfo = fetch_state_info(Pid),
-		     Html = observer_html_lib:expandable_term("ProcState", StateInfo, Table),
+		     Html = observer_html_lib:expandable_term("ProcState", StateInfo, Table, Cs),
 		     wxHtmlWindow:setPage(Win, Html)
 	     end,
     Update(),
@@ -341,6 +347,7 @@ fetch_state_info2(Pid, M) ->
 
 init_log_page(Parent, Pid, Table) ->
     Win = observer_lib:html_window(Parent),
+    Cs = observer_lib:colors(Parent),
     Update = fun() ->
 		     Fd = spawn_link(fun() -> io_server() end),
 		     rpc:call(node(Pid), rb, rescan, [[{start_log, Fd}]]),
@@ -353,7 +360,7 @@ init_log_page(Parent, Pid, Table) ->
 		     NbBlanks = length(Pref) - 1,
 		     Re = "(<" ++ Pref ++ "\.[^>]{1,}>)[ ]{"++ integer_to_list(NbBlanks) ++ "}",
 		     Look = re:replace(ExpPid, Re, "\\1", [global, {return, list}]),
-		     Html = observer_html_lib:expandable_term("SaslLog", Look, Table),
+		     Html = observer_html_lib:expandable_term("SaslLog", Look, Table, Cs),
 		     wxHtmlWindow:setPage(Win, Html)
 	     end,
     Update(),
-- 
2.16.4

openSUSE Build Service is sponsored by