Skip to content

Commit

Permalink
Implement a tab for persistent terms in crashdump viewer
Browse files Browse the repository at this point in the history
Co-authored-by: Siri Hansen <siri@erlang.org>
  • Loading branch information
bjorng and sirihansen committed Oct 19, 2018
1 parent 8d44568 commit a0b336e
Show file tree
Hide file tree
Showing 8 changed files with 148 additions and 14 deletions.
1 change: 1 addition & 0 deletions lib/observer/src/Makefile
Original file line number Diff line number Diff line change
Expand Up @@ -50,6 +50,7 @@ MODULES= \
cdv_mem_cb \
cdv_mod_cb \
cdv_multi_wx \
cdv_persistent_cb \
cdv_port_cb \
cdv_proc_cb \
cdv_sched_cb \
Expand Down
26 changes: 25 additions & 1 deletion lib/observer/src/cdv_html_wx.erl
Original file line number Diff line number Diff line change
Expand Up @@ -33,13 +33,17 @@
{panel,
app, %% which tool is the user
expand_table,
expand_wins=[]}).
expand_wins=[],
delayed_fetch,
trunc_warn=[]}).

start_link(ParentWin, Info) ->
wx_object:start_link(?MODULE, [ParentWin, Info], []).

%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%

init([ParentWin, Callback]) when is_atom(Callback) ->
init(ParentWin, Callback);
init([ParentWin, {App, Fun}]) when is_function(Fun) ->
init([ParentWin, {App, Fun()}]);
init([ParentWin, {expand,HtmlText,Tab}]) ->
Expand All @@ -60,9 +64,29 @@ init(ParentWin, HtmlText, Tab, App) ->
wx_misc:endBusyCursor(),
{HtmlWin, #state{panel=HtmlWin,expand_table=Tab,app=App}}.

init(ParentWin, Callback) ->
{HtmlWin, State} = init(ParentWin, "", undefined, cdv),
{HtmlWin, State#state{delayed_fetch=Callback}}.

%%%%%%%%%%%%%%%%%%%%%%% Callbacks %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%

handle_info(active, #state{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(),
observer_lib:sync_destroy_progress_dialog(),
wx_misc:beginBusyCursor(),
wxHtmlWindow:setPage(HtmlWin,HtmlText),
cdv_wx:set_status(TW),
wx_misc:endBusyCursor(),
{noreply, State#state{expand_table=Tab,
delayed_fetch=undefined,
trunc_warn=TW}};

handle_info(active, State) ->
cdv_wx:set_status(State#state.trunc_warn),
{noreply, State};

handle_info(Info, State) ->
Expand Down
32 changes: 32 additions & 0 deletions lib/observer/src/cdv_persistent_cb.erl
Original file line number Diff line number Diff line change
@@ -0,0 +1,32 @@
%%
%% %CopyrightBegin%
%%
%% Copyright Ericsson AB 2018. All Rights Reserved.
%%
%% Licensed under the Apache License, Version 2.0 (the "License");
%% you may not use this file except in compliance with the License.
%% You may obtain a copy of the License at
%%
%% http://www.apache.org/licenses/LICENSE-2.0
%%
%% Unless required by applicable law or agreed to in writing, software
%% distributed under the License is distributed on an "AS IS" BASIS,
%% WITHOUT WARRANTIES OR CONDITIONS OF ANY KIND, either express or implied.
%% See the License for the specific language governing permissions and
%% limitations under the License.
%%
%% %CopyrightEnd%

-module(cdv_persistent_cb).

-export([get_info/0]).

-include_lib("wx/include/wx.hrl").

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}.
16 changes: 13 additions & 3 deletions lib/observer/src/cdv_wx.erl
Original file line number Diff line number Diff line change
Expand Up @@ -51,6 +51,7 @@
-define(DIST_STR, "Nodes").
-define(MOD_STR, "Modules").
-define(MEM_STR, "Memory").
-define(PERSISTENT_STR, "Persistent Terms").
-define(INT_STR, "Internal Tables").

%% Records
Expand All @@ -74,6 +75,7 @@
dist_panel,
mod_panel,
mem_panel,
persistent_panel,
int_panel,
active_tab
}).
Expand Down Expand Up @@ -193,6 +195,10 @@ setup(#state{frame=Frame, notebook=Notebook}=State) ->
%% Memory Panel
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),

%% Memory Panel
IntPanel = add_page(Notebook, ?INT_STR, cdv_multi_wx, cdv_int_tab_cb),

Expand All @@ -215,6 +221,7 @@ setup(#state{frame=Frame, notebook=Notebook}=State) ->
dist_panel = DistPanel,
mod_panel = ModPanel,
mem_panel = MemPanel,
persistent_panel = PersistentPanel,
int_panel = IntPanel,
active_tab = GenPid
}}.
Expand Down Expand Up @@ -250,6 +257,7 @@ handle_event(#wx{id = ?wxID_OPEN,
State#state.dist_panel,
State#state.mod_panel,
State#state.mem_panel,
State#state.persistent_panel,
State#state.int_panel],
_ = [wx_object:call(Panel,new_dump) || Panel<-Panels],
wxNotebook:setSelection(State#state.notebook,0),
Expand Down Expand Up @@ -343,8 +351,8 @@ check_page_title(Notebook) ->
get_active_pid(#state{notebook=Notebook, gen_panel=Gen, pro_panel=Pro,
port_panel=Ports, ets_panel=Ets, timer_panel=Timers,
fun_panel=Funs, atom_panel=Atoms, dist_panel=Dist,
mod_panel=Mods, mem_panel=Mem, int_panel=Int,
sched_panel=Sched
mod_panel=Mods, mem_panel=Mem, persistent_panel=Persistent,
int_panel=Int, sched_panel=Sched
}) ->
Panel = case check_page_title(Notebook) of
?GEN_STR -> Gen;
Expand All @@ -358,14 +366,15 @@ get_active_pid(#state{notebook=Notebook, gen_panel=Gen, pro_panel=Pro,
?DIST_STR -> Dist;
?MOD_STR -> Mods;
?MEM_STR -> Mem;
?PERSISTENT_STR -> Persistent;
?INT_STR -> Int
end,
wx_object:get_pid(Panel).

pid2panel(Pid, #state{gen_panel=Gen, pro_panel=Pro, port_panel=Ports,
ets_panel=Ets, timer_panel=Timers, fun_panel=Funs,
atom_panel=Atoms, dist_panel=Dist, mod_panel=Mods,
mem_panel=Mem, int_panel=Int}) ->
mem_panel=Mem, persistent_panel=Persistent, int_panel=Int}) ->
case Pid of
Gen -> ?GEN_STR;
Pro -> ?PRO_STR;
Expand All @@ -377,6 +386,7 @@ pid2panel(Pid, #state{gen_panel=Gen, pro_panel=Pro, port_panel=Ports,
Dist -> ?DIST_STR;
Mods -> ?MOD_STR;
Mem -> ?MEM_STR;
?PERSISTENT_STR -> Persistent;
Int -> ?INT_STR;
_ -> "unknown"
end.
Expand Down
82 changes: 73 additions & 9 deletions lib/observer/src/crashdump_viewer.erl
Original file line number Diff line number Diff line change
Expand Up @@ -74,6 +74,7 @@
loaded_modules/0,
loaded_mod_details/1,
memory/0,
persistent_terms/0,
allocated_areas/0,
allocator_info/0,
hash_tables/0,
Expand Down Expand Up @@ -139,6 +140,7 @@
-define(node,node).
-define(not_connected,not_connected).
-define(old_instr_data,old_instr_data).
-define(persistent_terms,persistent_terms).
-define(port,port).
-define(proc,proc).
-define(proc_dictionary,proc_dictionary).
Expand Down Expand Up @@ -293,6 +295,8 @@ loaded_mod_details(Mod) ->
call({loaded_mod_details,Mod}).
memory() ->
call(memory).
persistent_terms() ->
call(persistent_terms).
allocated_areas() ->
call(allocated_areas).
allocator_info() ->
Expand Down Expand Up @@ -471,6 +475,11 @@ handle_call(memory,_From,State=#state{file=File}) ->
Memory=memory(File),
TW = truncated_warning([?memory]),
{reply,{ok,Memory,TW},State};
handle_call(persistent_terms,_From,State=#state{file=File,dump_vsn=DumpVsn}) ->
TW = truncated_warning([?persistent_terms,?literals]),
DecodeOpts = get_decode_opts(DumpVsn),
Terms = persistent_terms(File, DecodeOpts),
{reply,{ok,Terms,TW},State};
handle_call(allocated_areas,_From,State=#state{file=File}) ->
AllocatedAreas=allocated_areas(File),
TW = truncated_warning([?allocated_areas]),
Expand Down Expand Up @@ -1444,15 +1453,7 @@ maybe_other_node2(Channel) ->
expand_memory(Fd,Pid,DumpVsn) ->
DecodeOpts = get_decode_opts(DumpVsn),
put(fd,Fd),
Dict0 = case get(?literals) of
undefined ->
Literals = read_literals(Fd,DecodeOpts),
put(?literals,Literals),
put(fd,Fd),
Literals;
Literals ->
Literals
end,
Dict0 = get_literals(Fd,DecodeOpts),
Dict = read_heap(Fd,Pid,DecodeOpts,Dict0),
Expanded = {read_stack_dump(Fd,Pid,DecodeOpts,Dict),
read_messages(Fd,Pid,DecodeOpts,Dict),
Expand All @@ -1468,6 +1469,18 @@ expand_memory(Fd,Pid,DumpVsn) ->
end,
{Expanded,IncompleteWarning}.

get_literals(Fd,DecodeOpts) ->
case get(?literals) of
undefined ->
OldFd = put(fd,Fd),
Literals = read_literals(Fd,DecodeOpts),
put(fd,OldFd),
put(?literals,Literals),
Literals;
Literals ->
Literals
end.

read_literals(Fd,DecodeOpts) ->
case lookup_index(?literals,[]) of
[{_,Start}] ->
Expand Down Expand Up @@ -2141,6 +2154,56 @@ get_atom(<<"\'",Atom/binary>>) ->
get_atom(Atom) when is_binary(Atom) ->
{Atom,nq}. % not quoted

%%-----------------------------------------------------------------
%% Page with list of all persistent terms
persistent_terms(File, DecodeOpts) ->
case lookup_index(?persistent_terms) of
[{_Id,Start}] ->
Fd = open(File),
pos_bof(Fd,Start),
Terms = get_persistent_terms(Fd),
Dict = get_literals(Fd,DecodeOpts),
parse_persistent_terms(Terms,DecodeOpts,Dict);
_ ->
[]
end.

parse_persistent_terms([[Name0,Val0]|Terms],DecodeOpts,Dict) ->
{Name,_,_} = parse_term(binary_to_list(Name0),DecodeOpts,Dict),
{Val,_,_} = parse_term(binary_to_list(Val0),DecodeOpts,Dict),
[{Name,Val}|parse_persistent_terms(Terms,DecodeOpts,Dict)];
parse_persistent_terms([],_,_) -> [].

get_persistent_terms(Fd) ->
case get_chunk(Fd) of
{ok,Bin} ->
get_persistent_terms(Fd,Bin,[]);
eof ->
[]
end.


%% Persistent_Terms are written one per line in the crash dump.
get_persistent_terms(Fd,Bin,PersistentTerms) ->
Bins = binary:split(Bin,<<"\n">>,[global]),
get_persistent_terms1(Fd,Bins,PersistentTerms).

get_persistent_terms1(_Fd,[<<"=",_/binary>>|_],PersistentTerms) ->
PersistentTerms;
get_persistent_terms1(Fd,[LastBin],PersistentTerms) ->
case get_chunk(Fd) of
{ok,Bin0} ->
get_persistent_terms(Fd,<<LastBin/binary,Bin0/binary>>,PersistentTerms);
eof ->
[get_persistent_term(LastBin)|PersistentTerms]
end;
get_persistent_terms1(Fd,[Bin|Bins],Persistent_Terms) ->
get_persistent_terms1(Fd,Bins,[get_persistent_term(Bin)|Persistent_Terms]).

get_persistent_term(Bin) ->
binary:split(Bin,<<"|">>).


%%-----------------------------------------------------------------
%% Page with memory information
memory(File) ->
Expand Down Expand Up @@ -3119,6 +3182,7 @@ tag_to_atom("literals") -> ?literals;
tag_to_atom("loaded_modules") -> ?loaded_modules;
tag_to_atom("memory") -> ?memory;
tag_to_atom("mod") -> ?mod;
tag_to_atom("persistent_terms") -> ?persistent_terms;
tag_to_atom("no_distribution") -> ?no_distribution;
tag_to_atom("node") -> ?node;
tag_to_atom("not_connected") -> ?not_connected;
Expand Down
1 change: 1 addition & 0 deletions lib/observer/src/observer.app.src
Original file line number Diff line number Diff line change
Expand Up @@ -34,6 +34,7 @@
cdv_mem_cb,
cdv_mod_cb,
cdv_multi_wx,
cdv_persistent_cb,
cdv_port_cb,
cdv_proc_cb,
cdv_table_wx,
Expand Down
3 changes: 2 additions & 1 deletion lib/observer/src/observer_html_lib.erl
Original file line number Diff line number Diff line change
Expand Up @@ -62,7 +62,8 @@ expandable_term_body(Heading,[],_Tab) ->
"Dictionary" -> "No dictionary was found";
"ProcState" -> "Information could not be retrieved,"
" system messages may not be handled by this process.";
"SaslLog" -> "No log entry was found"
"SaslLog" -> "No log entry was found";
"Persistent Terms" -> "No persistent terms were found"
end];
expandable_term_body(Heading,Expanded,Tab) ->
Attr = "BORDER=0 CELLPADDING=0 CELLSPACING=1 WIDTH=100%",
Expand Down
1 change: 1 addition & 0 deletions lib/observer/test/crashdump_viewer_SUITE.erl
Original file line number Diff line number Diff line change
Expand Up @@ -345,6 +345,7 @@ browse_file(File) ->
{ok,_AllocINfo,_AllocInfoTW} = crashdump_viewer:allocator_info(),
{ok,_HashTabs,_HashTabsTW} = crashdump_viewer:hash_tables(),
{ok,_IndexTabs,_IndexTabsTW} = crashdump_viewer:index_tables(),
{ok,_PTs,_PTsTW} = crashdump_viewer:persistent_terms(),

io:format(" info read",[]),

Expand Down

0 comments on commit a0b336e

Please sign in to comment.