Skip to content

Commit 20244a6

Browse files
committed
Merge branch 'crashdump_viewer_allocators' of github.com:gomoripeti/otp into maint
* 'crashdump_viewer_allocators' of github.com:gomoripeti/otp: Crash dump viewer: ignore allocator type from blocks size keys OTP-19353
2 parents adb8bb0 + a5bdb2d commit 20244a6

File tree

3 files changed

+33
-3
lines changed

3 files changed

+33
-3
lines changed

lib/observer/src/cdv_mem_cb.erl

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -84,5 +84,5 @@ fix_alloc([]) ->
8484
[].
8585

8686
alloc_columns(Columns) ->
87-
[{"", ?wxLIST_FORMAT_LEFT, 180} |
87+
[{"", ?wxLIST_FORMAT_LEFT, 240} |
8888
[{Column, ?wxLIST_FORMAT_RIGHT, 140} || Column <- Columns]].

lib/observer/src/crashdump_viewer.erl

Lines changed: 2 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -2537,7 +2537,8 @@ sort_allocator_types([],Acc,DoTotal) ->
25372537

25382538
sort_type_data(Type,[?opt_e_false|Data],Acc,_) when Type=/=?sbmbc_alloc->
25392539
sort_type_data(Type,Data,Acc,false);
2540-
sort_type_data(Type,[{Key,Val0}|Data],Acc,DoTotal) ->
2540+
sort_type_data(Type,[{Key0,Val0}|Data],Acc,DoTotal) ->
2541+
Key = re:replace(Key0, "([^[]*)(\\[[^]]*\\])(.*)", "\\1\\3", [{return, list}]),
25412542
case lists:member(Key,?interesting_allocator_info) of
25422543
true ->
25432544
Val = list_to_integer(hd(Val0)),

lib/observer/test/crashdump_viewer_SUITE.erl

Lines changed: 30 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -364,7 +364,7 @@ browse_file(File) ->
364364
{ok,Mods,_ModsTW} = crashdump_viewer:loaded_modules(),
365365
{ok,_Mem,_MemTW} = crashdump_viewer:memory(),
366366
{ok,_AllocAreas,_AreaTW} = crashdump_viewer:allocated_areas(),
367-
{ok,_AllocINfo,_AllocInfoTW} = crashdump_viewer:allocator_info(),
367+
{ok,AllocInfo,_AllocInfoTW} = crashdump_viewer:allocator_info(),
368368
{ok,_HashTabs,_HashTabsTW} = crashdump_viewer:hash_tables(),
369369
{ok,_IndexTabs,_IndexTabsTW} = crashdump_viewer:index_tables(),
370370
{ok,_PTs,_PTsTW} = crashdump_viewer:persistent_terms(),
@@ -380,6 +380,9 @@ browse_file(File) ->
380380
lookat_all_nodes(Nodes),
381381
io:format(" nodes ok",[]),
382382

383+
lookat_alloc_info(AllocInfo,is_truncated(File)),
384+
io:format(" alloc info ok",[]),
385+
383386
Procs. % used as second arg to special/2
384387

385388
is_truncated(File) ->
@@ -733,6 +736,32 @@ lookat_all_nodes([#nod{channel=Channel0}|Nodes]) ->
733736
{ok,_Node=#nod{},_NodeTW} = crashdump_viewer:node_info(Channel),
734737
lookat_all_nodes(Nodes).
735738

739+
lookat_alloc_info(_,true) ->
740+
ok;
741+
lookat_alloc_info([AllocSummary|_],false) ->
742+
{"Allocator Summary",
743+
["blocks size", "carriers size", "mseg carriers size"],
744+
Data
745+
} = AllocSummary,
746+
747+
%% All values must be integer.
748+
Filter = filter_alloc_info_fun(),
749+
_ = [list_to_integer(IntStr) || {_,L} <- Data,
750+
IntStr <- Filter(L)],
751+
752+
ok.
753+
754+
filter_alloc_info_fun() ->
755+
case os:type() of
756+
{win32,_} ->
757+
fun([A,B,_]) ->
758+
%% The third column is never valid on Windows.
759+
[A,B]
760+
end;
761+
_ ->
762+
fun([_,_,_]=L) -> L end
763+
end.
764+
736765
%%%-----------------------------------------------------------------
737766
%%%
738767
create_dumps(DataDir,Rels) ->

0 commit comments

Comments
 (0)