~clint-fewbar/ubuntu/precise/erlang/merge-15b

« back to all changes in this revision

Viewing changes to lib/observer/src/crashdump_viewer.erl

  • Committer: Package Import Robot
  • Author(s): Sergei Golovan
  • Date: 2011-12-15 19:20:10 UTC
  • mfrom: (1.1.18) (3.5.15 sid)
  • mto: (3.5.16 sid)
  • mto: This revision was merged to the branch mainline in revision 33.
  • Revision ID: package-import@ubuntu.com-20111215192010-jnxcfe3tbrpp0big
Tags: 1:15.b-dfsg-1
* New upstream release.
* Upload to experimental because this release breaks external drivers
  API along with ABI, so several applications are to be fixed.
* Removed SSL patch because the old SSL implementation is removed from
  the upstream distribution.
* Removed never used patch which added native code to erlang beam files.
* Removed the erlang-docbuilder binary package because the docbuilder
  application was dropped by upstream.
* Documented dropping ${erlang-docbuilder:Depends} substvar in
  erlang-depends(1) manpage.
* Made erlang-base and erlang-base-hipe provide virtual package
  erlang-abi-15.b (the number means the first erlang version, which
  provides current ABI).

Show diffs side-by-side

added added

removed removed

Lines of Context:
1
1
%%
2
2
%% %CopyrightBegin%
3
3
%% 
4
 
%% Copyright Ericsson AB 2003-2009. All Rights Reserved.
 
4
%% Copyright Ericsson AB 2003-2011. All Rights Reserved.
5
5
%% 
6
6
%% The contents of this file are subject to the Erlang Public License,
7
7
%% Version 1.1, (the "License"); you may not use this file except in
23
23
%% the server started by webtool and the API for the crashdump viewer tool.
24
24
%% 
25
25
%% All functions in the API except configData/0 and start_link/0 are 
26
 
%% called from HTML pages via erl_scheme.
 
26
%% called from HTML pages via erl_scheme (mod_esi).
27
27
%% 
28
28
%% Tables
29
29
%% ------
34
34
%% 
35
35
%% cdv_dump_index_table: This table holds all tags read from the crashdump.
36
36
%% Each tag indicates where the information about a specific item starts.
37
 
%% The table entry for a tag includes the start and end positions for
38
 
%% this item-information. All tags start with a "=" at the beginning of
 
37
%% The table entry for a tag includes the start position for this
 
38
%% item-information. All tags start with a "=" at the beginning of
39
39
%% a line.
40
40
%%
41
41
%% Process state
42
42
%% -------------
43
43
%% file: The name of the crashdump currently viewed.
44
44
%% procs_summary: Process summary represented by a list of 
45
 
%% #proc records. This is used for efficiency reasons when sorting
46
 
%% the process summary table instead of reading all processes from
47
 
%% the dump again.
48
 
%% sorted: atom(), indicated what item was last sorted in process summary.
 
45
%% #proc records. This is used for efficiency reasons when sorting the
 
46
%% process summary table instead of reading all processes from the
 
47
%% dump again. Note that if the dump contains more than
 
48
%% ?max_sort_process_num processes, the sort functionality is not
 
49
%% available, and the procs_summary field in the state will have the
 
50
%% value 'too_many'.
 
51
%% sorted: string(), indicated what item was last sorted in process summary.
49
52
%% This is needed so reverse sorting can be done.
50
53
%% shared_heap: 'true' if crashdump comes from a system running shared heap,
51
54
%% else 'false'.
54
57
%%
55
58
 
56
59
%% User API
57
 
-export([start/0,stop/0]).
 
60
-export([start/0,stop/0,script_start/0,script_start/1]).
58
61
 
59
62
%% Webtool API
60
63
-export([configData/0,
68
71
         initial_info_frame/2,
69
72
         toggle/2,
70
73
         general_info/2,
71
 
         processes/2,
 
74
         processes/3,
72
75
         proc_details/2,
73
 
         ports/2,
74
 
         ets_tables/2,
75
 
         timers/2,
76
 
         fun_table/2,
77
 
         atoms/2,
 
76
         port/2,
 
77
         ports/3,
 
78
         ets_tables/3,
 
79
         internal_ets_tables/2,
 
80
         timers/3,
 
81
         fun_table/3,
 
82
         atoms/3,
78
83
         dist_info/2,
79
 
         loaded_modules/2,
 
84
         loaded_modules/3,
80
85
         loaded_mod_details/2,
81
86
         memory/2,
82
87
         allocated_areas/2,
83
88
         allocator_info/2,
84
89
         hash_tables/2,
85
90
         index_tables/2,
86
 
         sort_procs/2,
 
91
         sort_procs/3,
87
92
         expand/2,
88
93
         expand_binary/2,
89
 
         expand_memory/2,
90
 
         next/2]).
 
94
         expand_memory/2]).
91
95
 
92
96
 
93
97
%% gen_server callbacks
113
117
                                % this, it must be explicitly expanded.
114
118
-define(max_display_binary_size,50). % max size of a binary that will be
115
119
                                      % directly displayed.
116
 
 
117
 
-define(initial_proc_record(Pid),
118
 
        #proc{pid=Pid,
119
 
              %% msg_q_len, reds and stack_heap are integers because it must 
120
 
              %% be possible to sort on them. All other fields are strings
121
 
              msg_q_len=0,reds=0,stack_heap=0,
122
 
              %% for old dumps start_time, parent and number of heap frament
123
 
              %% does not exist
124
 
              start_time="unknown",
125
 
              parent="unknown",
126
 
              num_heap_frag="unknown", 
127
 
              %% current_func can be both "current function" and
128
 
              %% "last scheduled in for"
129
 
              current_func={"Current Function",?space},
130
 
              %% stack_dump, message queue and dictionaries should only be 
131
 
              %% displayed as a link to "Expand" (if dump is from OTP R9B 
132
 
              %% or newer)
133
 
              _=?space}).
 
120
-define(max_sort_process_num,10000). % Max number of processes that allows
 
121
                                    % sorting. If more than this number of 
 
122
                                    % processes exist, they will be displayed
 
123
                                    % in the order they are found in the log.
 
124
-define(items_chunk_size,?max_sort_process_num). % Number of items per chunk 
 
125
                                                 % when page of many items
 
126
                                                 % is displayed, e.g. processes,
 
127
                                                 % timers, funs...
 
128
                                                 % Must be equal to 
 
129
                                                 % ?max_sort_process_num!
 
130
 
 
131
%% All possible tags - use macros in order to avoid misspelling in the code
 
132
-define(allocated_areas,allocated_areas).
 
133
-define(allocator,allocator).
 
134
-define(atoms,atoms).
 
135
-define(binary,binary).
 
136
-define(debug_proc_dictionary,debug_proc_dictionary).
 
137
-define(ende,ende).
 
138
-define(erl_crash_dump,erl_crash_dump).
 
139
-define(ets,ets).
 
140
-define(fu,fu).
 
141
-define(hash_table,hash_table).
 
142
-define(hidden_node,hidden_node).
 
143
-define(index_table,index_table).
 
144
-define(instr_data,instr_data).
 
145
-define(internal_ets,internal_ets).
 
146
-define(loaded_modules,loaded_modules).
 
147
-define(memory,memory).
 
148
-define(mod,mod).
 
149
-define(no_distribution,no_distribution).
 
150
-define(node,node).
 
151
-define(not_connected,not_connected).
 
152
-define(num_atoms,num_atoms).
 
153
-define(old_instr_data,old_instr_data).
 
154
-define(port,port).
 
155
-define(proc,proc).
 
156
-define(proc_dictionary,proc_dictionary).
 
157
-define(proc_heap,proc_heap).
 
158
-define(proc_messages,proc_messages).
 
159
-define(proc_stack,proc_stack).
 
160
-define(timer,timer).
 
161
-define(visible_node,visible_node).
 
162
 
134
163
 
135
164
-record(state,{file,procs_summary,sorted,shared_heap=false,
136
165
               wordsize=4,num_atoms="unknown",binaries,bg_status}).
177
206
    webtool:stop().
178
207
 
179
208
%%%-----------------------------------------------------------------
 
209
%%% Start crashdump_viewer via the cdv script located in
 
210
%%% $OBSERVER_PRIV_DIR/bin
 
211
script_start() ->
 
212
    usage().
 
213
script_start([File]) ->
 
214
    DefaultBrowser =
 
215
        case os:type() of
 
216
            {win32,_} -> iexplore;
 
217
            _ -> firefox
 
218
        end,
 
219
    script_start([File,DefaultBrowser]);
 
220
script_start([FileAtom,Browser]) ->
 
221
    File = atom_to_list(FileAtom),
 
222
    case filelib:is_regular(File) of
 
223
        true ->
 
224
            io:format("Starting crashdump_viewer...\n"),
 
225
            start(),
 
226
            io:format("Reading crashdump..."),
 
227
            read_file(File),
 
228
            redirect([],[]),
 
229
            io:format("done\n"),
 
230
            start_browser(Browser);
 
231
        false ->
 
232
            io:format("cdv error: the given file does not exist\n"),
 
233
            usage()
 
234
    end.
 
235
 
 
236
start_browser(Browser) ->
 
237
    PortStr = integer_to_list(gen_server:call(web_tool,get_port)),
 
238
    Url = "http://localhost:" ++ PortStr ++ ?START_PAGE,
 
239
    {OSType,_} = os:type(),
 
240
    case Browser of
 
241
        none ->
 
242
            ok;
 
243
        iexplore when OSType == win32->
 
244
            io:format("Starting internet explorer...\n"),
 
245
            {ok,R} = win32reg:open(""),
 
246
            Key="\\local_machine\\SOFTWARE\\Microsoft\\IE Setup\\Setup",
 
247
            win32reg:change_key(R,Key),
 
248
            {ok,Val} = win32reg:value(R,"Path"),
 
249
            IExplore=filename:join(win32reg:expand(Val),"iexplore.exe"),
 
250
            os:cmd("\"" ++ IExplore ++ "\" " ++ Url);
 
251
        _ when OSType == win32 ->
 
252
            io:format("Starting ~w...\n",[Browser]),
 
253
            os:cmd("\"" ++ atom_to_list(Browser) ++ "\" " ++ Url);
 
254
        B when B==firefox; B==mozilla ->
 
255
            io:format("Sending URL to ~w...",[Browser]),
 
256
            BStr = atom_to_list(Browser),
 
257
            SendCmd = BStr ++ " -raise -remote \'openUrl(" ++ Url ++ ")\'",
 
258
            Port = open_port({spawn,SendCmd},[exit_status]),
 
259
            receive
 
260
                {Port,{exit_status,0}} ->
 
261
                    io:format("done\n");
 
262
                {Port,{exit_status,_Error}} ->
 
263
                    io:format(" not running, starting ~w...\n",[Browser]),
 
264
                    os:cmd(BStr ++ " " ++ Url)
 
265
            after 5000 ->
 
266
                    io:format(" failed, starting ~w...\n",[Browser]),
 
267
                    erlang:port_close(Port),
 
268
                    os:cmd(BStr ++ " " ++ Url)
 
269
            end;
 
270
        _ ->
 
271
            io:format("Starting ~w...\n",[Browser]),
 
272
            os:cmd(atom_to_list(Browser) ++ " " ++ Url)
 
273
    end,
 
274
    ok.
 
275
 
 
276
usage() ->
 
277
    io:format(
 
278
      "\nusage: cdv file [ browser ]\n"
 
279
      "\tThe \'file\' must be an existing erlang crash dump.\n"
 
280
      "\tDefault browser is \'iexplore\' (Internet Explorer) on Windows\n"
 
281
      "\tor else \'firefox\'.\n",
 
282
      []).
 
283
 
 
284
 
 
285
 
 
286
 
 
287
%%%-----------------------------------------------------------------
180
288
%%% Return config data used by webtool
181
289
configData() ->
182
290
    Dir = filename:join(code:priv_dir(observer),"crashdump_viewer"),
266
374
%%% The following functions are called when menu items are clicked.
267
375
general_info(_Env,_Input) ->
268
376
    call(general_info).
269
 
processes(_Env,_Input) ->
270
 
    call(procs_summary).
271
 
ports(_Env,Input) -> % this is also called when a link to a port is clicked
272
 
    call({ports,Input}).
273
 
ets_tables(_Env,Input) ->
274
 
    call({ets_tables,Input}).
275
 
timers(_Env,Input) ->
276
 
    call({timers,Input}).
277
 
fun_table(_Env,_Input) ->
278
 
    call(funs).
279
 
atoms(_Env,_Input) ->
280
 
    call(atoms).
 
377
processes(SessionId,_Env,_Input) ->
 
378
    call({procs_summary,SessionId}).
 
379
ports(SessionId,_Env,_Input) ->
 
380
    call({ports,SessionId}).
 
381
ets_tables(SessionId,_Env,Input) ->
 
382
    call({ets_tables,SessionId,Input}).
 
383
internal_ets_tables(_Env,_Input) ->
 
384
    call(internal_ets_tables).
 
385
timers(SessionId,_Env,Input) ->
 
386
    call({timers,SessionId,Input}).
 
387
fun_table(SessionId,_Env,_Input) ->
 
388
    call({funs,SessionId}).
 
389
atoms(SessionId,_Env,_Input) ->
 
390
    call({atoms,SessionId}).
281
391
dist_info(_Env,_Input) ->
282
392
    call(dist_info).
283
 
loaded_modules(_Env,_Input) ->
284
 
    call(loaded_mods).
 
393
loaded_modules(SessionId,_Env,_Input) ->
 
394
    call({loaded_mods,SessionId}).
285
395
loaded_mod_details(_Env,Input) ->
286
396
    call({loaded_mod_details,Input}).
287
397
memory(_Env,_Input) ->
303
413
%%%-----------------------------------------------------------------
304
414
%%% Called when one of the headings in the process summary table are
305
415
%%% clicked. It sorts the processes by the clicked heading.
306
 
sort_procs(_Env,Input) ->
307
 
    call({sort_procs,Input}).
 
416
sort_procs(SessionId,_Env,Input) ->
 
417
    call({sort_procs,SessionId,Input}).
 
418
 
 
419
%%%-----------------------------------------------------------------
 
420
%%% Called when a link to a port is clicked.
 
421
port(_Env,Input) ->
 
422
    call({port,Input}).
308
423
 
309
424
%%%-----------------------------------------------------------------
310
425
%%% Called when the "Expand" link in a call stack (Last Calls) is
325
440
    call({expand_binary,Input}).
326
441
 
327
442
%%%-----------------------------------------------------------------
328
 
%%% Called when the "Next" link under atoms is clicked.
329
 
next(_Env,Input) ->
330
 
    call({next,Input}).
331
 
 
332
 
%%%-----------------------------------------------------------------
333
443
%%% Called on regular intervals while waiting for a dump to be read
334
444
redirect(_Env,_Input) ->
335
445
    call(redirect).
348
458
%%--------------------------------------------------------------------
349
459
init([]) ->
350
460
    ets:new(cdv_menu_table,[set,named_table,{keypos,#menu_item.index},public]),
351
 
    ets:new(cdv_dump_index_table,[bag,named_table,public]),
 
461
    ets:new(cdv_dump_index_table,[ordered_set,named_table,public]),
352
462
    {ok, #state{}}.
353
463
 
354
464
%%--------------------------------------------------------------------
373
483
    Reply = crashdump_viewer_html:start_page(),
374
484
    {reply,Reply,State};
375
485
handle_call({read_file,Input}, _From, _State) ->
376
 
    {ok,File0} = get_value("path",httpd:parse_query(Input)),
377
 
    File = 
378
 
        case File0 of
379
 
            [$"|FileAndSome] ->
380
 
                %% Opera adds \"\" around the filename!
381
 
                [$"|Elif] = lists:reverse(FileAndSome),
382
 
                lists:reverse(Elif);
383
 
            _ ->
384
 
                File0
385
 
        end,
 
486
    {ok,File} = get_value("path",httpd:parse_query(Input)),
386
487
    spawn_link(fun() -> read_file(File) end),
387
488
    Status = background_status(reading,File),
388
489
    Reply = crashdump_viewer_html:redirect(Status),
399
500
    GenInfo = general_info(File),
400
501
    NumAtoms = GenInfo#general_info.num_atoms,
401
502
    {WS,SH} = parse_vsn_str(GenInfo#general_info.system_vsn,4,false),
 
503
    NumProcs = list_to_integer(GenInfo#general_info.num_procs),
 
504
    ProcsSummary = 
 
505
        if NumProcs > ?max_sort_process_num -> too_many;
 
506
           true -> State#state.procs_summary
 
507
        end,
 
508
    NewState = State#state{shared_heap=SH,
 
509
                           wordsize=WS,
 
510
                           num_atoms=NumAtoms,
 
511
                           procs_summary=ProcsSummary},
402
512
    Reply = crashdump_viewer_html:general_info(GenInfo),
403
 
    {reply,Reply,State#state{shared_heap=SH,wordsize=WS,num_atoms=NumAtoms}};
 
513
    {reply,Reply,NewState};
404
514
handle_call({toggle,Input},_From,State) ->
405
515
    {ok,Index} = get_value("index",httpd:parse_query(Input)),
406
516
    do_toggle(list_to_integer(Index)),
429
539
handle_call({expand_memory,Input},_From,State=#state{file=File,binaries=B}) ->
430
540
    [{"pid",Pid},{"what",What}] = httpd:parse_query(Input),
431
541
    Reply = 
432
 
        case truncated_warning([{"=proc",Pid}]) of
 
542
        case truncated_warning([{?proc,Pid}]) of
433
543
            [] ->
434
544
                Expanded = expand_memory(File,What,Pid,B),
435
545
                crashdump_viewer_html:expanded_memory(What,Expanded);
450
560
    close(Fd),
451
561
    Reply=crashdump_viewer_html:expanded_binary(io_lib:format("~p",[Bin])),
452
562
    {reply,Reply,State};
453
 
handle_call({next,Input},_From,State=#state{file=File}) ->
454
 
    [{"pos",Pos},{"num",N},{"start",Start},{"what",What}] =
455
 
        httpd:parse_query(Input),
456
 
    Tags = related_tags(What),
457
 
    TW = truncated_warning(Tags),
458
 
    Next = get_next(File,list_to_integer(Pos),list_to_integer(N),
459
 
                    list_to_integer(Start),What),
460
 
    Reply = crashdump_viewer_html:next(Next,TW),
461
 
    {reply,Reply,State};
462
563
handle_call(general_info,_From,State=#state{file=File}) ->
463
564
    GenInfo=general_info(File),
464
565
    Reply = crashdump_viewer_html:general_info(GenInfo),
465
566
    {reply,Reply,State};
466
 
handle_call(procs_summary,_From,State=#state{file=File,shared_heap=SH}) ->
467
 
    ProcsSummary =
468
 
        case State#state.procs_summary of
469
 
            undefined -> procs_summary(File);
470
 
            PS -> PS
471
 
        end,
472
 
    TW = truncated_warning(["=proc"]),
473
 
    Reply = crashdump_viewer_html:procs_summary("pid",ProcsSummary,TW,SH),
474
 
    {reply,Reply,State#state{procs_summary=ProcsSummary,sorted="pid"}};
475
 
handle_call({sort_procs,Input}, _From, State=#state{shared_heap=SH}) ->
 
567
handle_call({procs_summary,SessionId},_From,State) ->
 
568
    TW = truncated_warning([?proc]),
 
569
    NewState = procs_summary(SessionId,TW,"pid",State#state{sorted=undefined}),
 
570
    {reply,ok,NewState};
 
571
handle_call({sort_procs,SessionId,Input}, _From, State) ->
476
572
    {ok,Sort} = get_value("sort",httpd:parse_query(Input)),
477
 
    {ProcsSummary,Sorted} = do_sort_procs(Sort,
478
 
                                          State#state.procs_summary,
479
 
                                          State#state.sorted),
480
 
    TW = truncated_warning(["=proc"]),
481
 
    Reply = crashdump_viewer_html:procs_summary(Sort,ProcsSummary,TW,SH),
482
 
    {reply,Reply,State#state{sorted=Sorted}};
 
573
    TW = truncated_warning([?proc]),
 
574
    NewState = procs_summary(SessionId,TW,Sort,State),
 
575
    {reply,ok,NewState};
483
576
handle_call({proc_details,Input},_From,State=#state{file=File,shared_heap=SH}) ->
484
577
    {ok,Pid} = get_value("pid",httpd:parse_query(Input)),
485
578
    Reply = 
486
579
        case get_proc_details(File,Pid) of
487
580
            {ok,Proc} -> 
488
 
                TW = truncated_warning([{"=proc",Pid}]),
 
581
                TW = truncated_warning([{?proc,Pid}]),
489
582
                crashdump_viewer_html:proc_details(Pid,Proc,TW,SH);
490
583
            {other_node,Node} -> 
491
 
                TW = truncated_warning(["=visible_node",
492
 
                                        "=hidden_node",
493
 
                                        "=not_connected"]),
 
584
                TW = truncated_warning([?visible_node,
 
585
                                        ?hidden_node,
 
586
                                        ?not_connected]),
494
587
                crashdump_viewer_html:nods(Node,TW);
495
588
            not_found -> 
496
589
                crashdump_viewer_html:info_page(["Could not find process: ",
497
590
                                                 Pid],?space)
498
591
        end,
499
592
    {reply, Reply, State};
500
 
handle_call({ports,Input},_From,State=#state{file=File}) ->
 
593
handle_call({port,Input},_From,State=#state{file=File}) ->
 
594
    {ok,P} = get_value("port",httpd:parse_query(Input)),
 
595
    Id = [$#|P],
501
596
    Reply = 
502
 
        case get_value("port",httpd:parse_query(Input)) of
503
 
            {ok,P} -> 
504
 
                Id = [$#|P],
505
 
                case get_port(File,Id) of
506
 
                    {ok,PortInfo} ->
507
 
                        TW = truncated_warning([{"=port",Id}]),
508
 
                        crashdump_viewer_html:ports(Id,[PortInfo],TW);
509
 
                    {other_node,Node} ->
510
 
                        TW = truncated_warning(["=visible_node",
511
 
                                                "=hidden_node",
512
 
                                                "=not_connected"]),
513
 
                        crashdump_viewer_html:nods(Node,TW);
514
 
                    not_found -> 
515
 
                        crashdump_viewer_html:info_page(
516
 
                          ["Could not find port: ",Id],?space)
517
 
                end;
518
 
            error -> % no port identity in Input - get all ports
519
 
                Ports=get_ports(File),
520
 
                TW = truncated_warning(["=port"]),
521
 
                crashdump_viewer_html:ports("Port Information",Ports,TW)
 
597
        case get_port(File,Id) of
 
598
            {ok,PortInfo} ->
 
599
                TW = truncated_warning([{?port,Id}]),
 
600
                crashdump_viewer_html:port(Id,PortInfo,TW);
 
601
            {other_node,Node} ->
 
602
                TW = truncated_warning([?visible_node,
 
603
                                        ?hidden_node,
 
604
                                        ?not_connected]),
 
605
                crashdump_viewer_html:nods(Node,TW);
 
606
            not_found -> 
 
607
                crashdump_viewer_html:info_page(
 
608
                  ["Could not find port: ",Id],?space)
522
609
        end,
523
610
    {reply,Reply,State};
524
 
handle_call({ets_tables,Input},_From,State=#state{file=File,wordsize=WS}) ->
525
 
    {Pid,Heading,InternalEts} = 
 
611
handle_call({ports,SessionId},_From,State=#state{file=File}) ->
 
612
    TW = truncated_warning([?port]),
 
613
    get_ports(SessionId,File,TW),
 
614
    {reply,ok,State};
 
615
handle_call({ets_tables,SessionId,Input},_From,State=#state{file=File,wordsize=WS}) ->
 
616
    {Pid,Heading} = 
526
617
        case get_value("pid",httpd:parse_query(Input)) of
527
618
            {ok,P} -> 
528
 
                {P,["ETS Tables for Process ",P],[]};
 
619
                {P,["ETS Tables for Process ",P]};
529
620
            error -> 
530
 
                I = get_internal_ets_tables(File,WS),
531
 
                {'_',"ETS Table Information",I}
 
621
                {'$2',"ETS Table Information"}
532
622
        end,
533
 
    EtsTables = get_ets_tables(File,Pid,WS),
534
 
    TW = truncated_warning(["=ets"]),
535
 
    Reply = crashdump_viewer_html:ets_tables(Heading,EtsTables,InternalEts,TW),
 
623
    TW = truncated_warning([?ets]),
 
624
    get_ets_tables(SessionId,File,Heading,TW,Pid,WS),
 
625
    {reply,ok,State};
 
626
handle_call(internal_ets_tables,_From,State=#state{file=File,wordsize=WS}) ->
 
627
    InternalEts = get_internal_ets_tables(File,WS),
 
628
    TW = truncated_warning([?internal_ets]),
 
629
    Reply = crashdump_viewer_html:internal_ets_tables(InternalEts,TW),
536
630
    {reply,Reply,State};
537
 
handle_call({timers,Input},_From,State=#state{file=File}) ->
 
631
handle_call({timers,SessionId,Input},_From,State=#state{file=File}) ->
538
632
    {Pid,Heading} = 
539
633
        case get_value("pid",httpd:parse_query(Input)) of
540
634
            {ok,P} -> {P,["Timers for Process ",P]};
541
 
            error -> {'_',"Timer Information"}
 
635
            error -> {'$2',"Timer Information"}
542
636
        end,
543
 
    Timers=get_timers(File,Pid),
544
 
    TW = truncated_warning(["=timer"]),
545
 
    Reply = crashdump_viewer_html:timers(Heading,Timers,TW),
546
 
    {reply,Reply,State};
 
637
    TW = truncated_warning([?timer]),
 
638
    get_timers(SessionId,File,Heading,TW,Pid),
 
639
    {reply,ok,State};
547
640
handle_call(dist_info,_From,State=#state{file=File}) ->
548
641
    Nods=nods(File),
549
 
    TW = truncated_warning(["=visible_node","=hidden_node","=not_connected"]),
 
642
    TW = truncated_warning([?visible_node,?hidden_node,?not_connected]),
550
643
    Reply = crashdump_viewer_html:nods(Nods,TW),
551
644
    {reply,Reply,State};
552
 
handle_call(loaded_mods,_From,State=#state{file=File}) ->
553
 
    LoadedMods=loaded_mods(File),
554
 
    TW = truncated_warning(["=mod"]),
555
 
    Reply = crashdump_viewer_html:loaded_mods(LoadedMods,TW),
556
 
    {reply,Reply,State};
 
645
handle_call({loaded_mods,SessionId},_From,State=#state{file=File}) ->
 
646
    TW = truncated_warning([?mod]),
 
647
    loaded_mods(SessionId,File,TW),
 
648
    {reply,ok,State};
557
649
handle_call({loaded_mod_details,Input},_From,State=#state{file=File}) ->
558
650
    {ok,Mod} = get_value("mod",httpd:parse_query(Input)),
559
651
    ModInfo = get_loaded_mod_details(File,Mod),
560
 
    TW = truncated_warning([{"=mod",Mod}]),
 
652
    TW = truncated_warning([{?mod,Mod}]),
561
653
    Reply = crashdump_viewer_html:loaded_mod_details(ModInfo,TW),
562
654
    {reply,Reply,State};
563
 
handle_call(funs,_From,State=#state{file=File}) ->
564
 
    Funs=funs(File),
565
 
    TW = truncated_warning(["=fun"]),
566
 
    Reply = crashdump_viewer_html:funs(Funs,TW),
567
 
    {reply,Reply,State};
568
 
handle_call(atoms,_From,State=#state{file=File,num_atoms=Num}) ->
569
 
    Atoms=atoms(File),
570
 
    TW = truncated_warning(["=atoms","=num_atoms"]),
571
 
    Reply = crashdump_viewer_html:atoms(Atoms,Num,TW),
572
 
    {reply,Reply,State};
 
655
handle_call({funs,SessionId},_From,State=#state{file=File}) ->
 
656
    TW = truncated_warning([?fu]),
 
657
    funs(SessionId,File,TW),
 
658
    {reply,ok,State};
 
659
handle_call({atoms,SessionId},_From,State=#state{file=File,num_atoms=Num}) ->
 
660
    TW = truncated_warning([?atoms,?num_atoms]),
 
661
    atoms(SessionId,File,TW,Num),
 
662
    {reply,ok,State};
573
663
handle_call(memory,_From,State=#state{file=File}) ->
574
664
    Memory=memory(File),
575
 
    TW = truncated_warning(["=memory"]),
 
665
    TW = truncated_warning([?memory]),
576
666
    Reply = crashdump_viewer_html:memory(Memory,TW),
577
667
    {reply,Reply,State};
578
668
handle_call(allocated_areas,_From,State=#state{file=File}) ->
579
669
    AllocatedAreas=allocated_areas(File),
580
 
    TW = truncated_warning(["=allocated_areas"]),
 
670
    TW = truncated_warning([?allocated_areas]),
581
671
    Reply = crashdump_viewer_html:allocated_areas(AllocatedAreas,TW),
582
672
    {reply,Reply,State};
583
673
handle_call(allocator_info,_From,State=#state{file=File}) ->
584
674
    SlAlloc=allocator_info(File),
585
 
    TW = truncated_warning(["=allocator"]),
 
675
    TW = truncated_warning([?allocator]),
586
676
    Reply = crashdump_viewer_html:allocator_info(SlAlloc,TW),
587
677
    {reply,Reply,State};
588
678
handle_call(hash_tables,_From,State=#state{file=File}) ->
589
679
    HashTables=hash_tables(File),
590
 
    TW = truncated_warning(["=hash_table","=index_table"]),
 
680
    TW = truncated_warning([?hash_table,?index_table]),
591
681
    Reply = crashdump_viewer_html:hash_tables(HashTables,TW),
592
682
    {reply,Reply,State};
593
683
handle_call(index_tables,_From,State=#state{file=File}) ->
594
684
    IndexTables=index_tables(File),
595
 
    TW = truncated_warning(["=hash_table","=index_table"]),
 
685
    TW = truncated_warning([?hash_table,?index_table]),
596
686
    Reply = crashdump_viewer_html:index_tables(IndexTables,TW),
597
687
    {reply,Reply,State}.
598
688
 
682
772
                    
683
773
 
684
774
%% Check if the dump was truncated with the same tag, but earlier id.
685
 
%% Eg if this is {"=proc","<0.30.0>"}, we should warn if the dump was
686
 
%% truncated in {"=proc","<0.29.0>"} or earlier
687
 
truncated_earlier({"=proc",Pid}) ->
 
775
%% Eg if this is {?proc,"<0.30.0>"}, we should warn if the dump was
 
776
%% truncated in {?proc,"<0.29.0>"} or earlier
 
777
truncated_earlier({?proc,Pid}) ->
688
778
    compare_pid(Pid,get(truncated_proc));
689
779
truncated_earlier(_Tag) ->
690
780
    false.
718
808
close(Fd) ->
719
809
    erase(chunk),
720
810
    file:close(Fd).
 
811
 
 
812
%% Set position relative to beginning of file
 
813
%% If position is within the already read Chunk, then adjust 'chunk'
 
814
%% and 'pos' in process dictionary. Else set position in file.
721
815
pos_bof(Fd,Pos) ->
 
816
    case get(pos) of
 
817
        undefined ->
 
818
            hard_pos_bof(Fd,Pos);
 
819
        OldPos when Pos>=OldPos ->
 
820
            case get(chunk) of
 
821
                undefined ->
 
822
                    hard_pos_bof(Fd,Pos);
 
823
                Chunk ->
 
824
                    ChunkSize = byte_size(Chunk),
 
825
                    ChunkEnd = OldPos+ChunkSize,
 
826
                    if Pos=<ChunkEnd ->
 
827
                            Diff = Pos-OldPos,
 
828
                            put(pos,Pos),
 
829
                            put(chunk,binary:part(Chunk,Diff,ChunkEnd-Pos));
 
830
                       true ->
 
831
                            hard_pos_bof(Fd,Pos)
 
832
                    end
 
833
            end;
 
834
        _ ->
 
835
            hard_pos_bof(Fd,Pos)
 
836
    end.
 
837
 
 
838
hard_pos_bof(Fd,Pos) ->
722
839
    reset_chunk(),
723
 
    file:position(Fd,{bof,Pos}). 
 
840
    file:position(Fd,{bof,Pos}).
 
841
 
724
842
 
725
843
get_chunk(Fd) ->
726
844
    case erase(chunk) of
979
1097
      [menu_item(0, {"./general_info","General information"},0),
980
1098
       menu_item(0, {"./processes","Processes"}, 0),
981
1099
       menu_item(0, {"./ports","Ports"}, 0),
982
 
       menu_item(0, {"./ets_tables","ETS tables"}, 0),
 
1100
       menu_item(2, "ETS tables", 0),
 
1101
       menu_item(0, {"./ets_tables","ETS tables"}, 1),
 
1102
       menu_item(0, {"./internal_ets_tables","Internal ETS tables"}, 1),
983
1103
       menu_item(0, {"./timers","Timers"}, 0),
984
1104
       menu_item(0, {"./fun_table","Fun table"}, 0),
985
1105
       menu_item(0, {"./atoms","Atoms"}, 0),
1066
1186
                {ok,<<$=:8,TagAndRest/binary>>} ->
1067
1187
                    {Tag,Id,Rest,N1} = tag(Fd,TagAndRest,1),
1068
1188
                    case Tag of
1069
 
                        "=erl_crash_dump" ->
1070
 
                            ets:delete_all_objects(cdv_dump_index_table),
1071
 
                            ets:insert(cdv_dump_index_table,{Tag,Id,N1+1}),
 
1189
                        ?erl_crash_dump ->
 
1190
                            reset_index_table(),
 
1191
                            insert_index(Tag,Id,N1+1),
1072
1192
                            put(last_tag,{Tag,""}),
1073
1193
                            Status = background_status(processing,File),
1074
1194
                            background_status(Status),
1107
1227
            background_done({R,undefined,undefined})
1108
1228
    end.
1109
1229
 
1110
 
indexify(Fd,<<"\n=",TagAndRest/binary>>,N) ->
1111
 
    {Tag,Id,Rest,N1} = tag(Fd,TagAndRest,N+2),
1112
 
    ets:insert(cdv_dump_index_table,{Tag,Id,N1+1}), % +1 to get past newline
1113
 
    put(last_tag,{Tag,Id}),
1114
 
    indexify(Fd,Rest,N1);
1115
 
indexify(Fd,<<>>,N) ->
1116
 
    case read(Fd) of
1117
 
        {ok,Chunk} when is_binary(Chunk) ->
1118
 
            indexify(Fd,Chunk,N);
1119
 
        eof ->
1120
 
            eof
1121
 
    end;
1122
 
indexify(Fd,<<$\n>>,N) ->
1123
 
    %% This clause is needed in case the chunk ends with a newline and
1124
 
    %% the next chunk starts with a tag (i.e. "\n=....")
1125
 
    case read(Fd) of
1126
 
        {ok,Chunk} when is_binary(Chunk) ->
1127
 
            indexify(Fd,<<$\n,Chunk/binary>>,N);
1128
 
        eof ->
1129
 
            eof
1130
 
    end;
1131
 
indexify(Fd,<<_Char:8,Rest/binary>>,N) ->
1132
 
    indexify(Fd,Rest,N+1).
 
1230
indexify(Fd,Bin,N) ->
 
1231
    case binary:match(Bin,<<"\n=">>) of
 
1232
        {Start,Len} ->
 
1233
            Pos = Start+Len,
 
1234
            <<_:Pos/binary,TagAndRest/binary>> = Bin,
 
1235
            {Tag,Id,Rest,N1} = tag(Fd,TagAndRest,N+Pos),
 
1236
            insert_index(Tag,Id,N1+1), % +1 to get past newline
 
1237
            put(last_tag,{Tag,Id}),
 
1238
            indexify(Fd,Rest,N1);
 
1239
        nomatch ->
 
1240
            case read(Fd) of
 
1241
                {ok,Chunk0} when is_binary(Chunk0) ->
 
1242
                    {Chunk,N1} =
 
1243
                        case binary:last(Bin) of
 
1244
                            $\n ->
 
1245
                                {<<$\n,Chunk0/binary>>,N+byte_size(Bin)-1};
 
1246
                            _ ->
 
1247
                                {Chunk0,N+byte_size(Bin)}
 
1248
                        end,
 
1249
                    indexify(Fd,Chunk,N1);
 
1250
                eof ->
 
1251
                    eof
 
1252
            end
 
1253
    end.
1133
1254
 
1134
1255
tag(Fd,Bin,N) ->
1135
1256
    tag(Fd,Bin,N,[],[],tag).
1136
1257
tag(_Fd,<<$\n:8,_/binary>>=Rest,N,Gat,Di,_Now) ->
1137
 
    {[$=|lists:reverse(Gat)],lists:reverse(Di),Rest,N};
 
1258
    {tag_to_atom(lists:reverse(Gat)),lists:reverse(Di),Rest,N};
1138
1259
tag(Fd,<<$\r:8,Rest/binary>>,N,Gat,Di,Now) ->
1139
1260
    tag(Fd,Rest,N+1,Gat,Di,Now);
1140
1261
tag(Fd,<<$::8,IdAndRest/binary>>,N,Gat,Di,tag) ->
1148
1269
        {ok,Chunk} when is_binary(Chunk) ->
1149
1270
            tag(Fd,Chunk,N,Gat,Di,Now);
1150
1271
        eof ->
1151
 
            {[$=|lists:reverse(Gat)],lists:reverse(Di),<<>>,N}
 
1272
            {tag_to_atom(lists:reverse(Gat)),lists:reverse(Di),<<>>,N}
1152
1273
    end.
1153
1274
 
1154
1275
check_if_truncated() ->
1155
1276
    case get(last_tag) of
1156
 
        {"=end",_} ->
 
1277
        {?ende,_} ->
1157
1278
            put(truncated,false),
1158
1279
            put(truncated_proc,false);
1159
1280
        TruncatedTag ->
1161
1282
            find_truncated_proc(TruncatedTag)
1162
1283
    end.
1163
1284
            
1164
 
find_truncated_proc({"=atom",_Id}) ->
 
1285
find_truncated_proc({?atoms,_Id}) ->
1165
1286
    put(truncated_proc,false);
1166
1287
find_truncated_proc({Tag,Pid}) ->
1167
1288
    case is_proc_tag(Tag) of
1168
1289
        true -> 
1169
1290
            put(truncated_proc,Pid);
1170
1291
        false -> 
1171
 
            %% This means that the dump is truncated between "=proc" and
1172
 
            %% "=proc_heap" => memory info is missing for all procs.
 
1292
            %% This means that the dump is truncated between ?proc and
 
1293
            %% ?proc_heap => memory info is missing for all procs.
1173
1294
            put(truncated_proc,"<0.0.0>")
1174
1295
    end.
1175
1296
 
1176
 
is_proc_tag(Tag)  when Tag=="=proc";
1177
 
                       Tag=="=proc_dictionary";
1178
 
                       Tag=="=proc_messages";
1179
 
                       Tag=="=proc_dictionary";
1180
 
                       Tag=="=debug_proc_dictionary";
1181
 
                       Tag=="=proc_stack";
1182
 
                       Tag=="=proc_heap" ->
 
1297
is_proc_tag(Tag)  when Tag==?proc;
 
1298
                       Tag==?proc_dictionary;
 
1299
                       Tag==?proc_messages;
 
1300
                       Tag==?proc_dictionary;
 
1301
                       Tag==?debug_proc_dictionary;
 
1302
                       Tag==?proc_stack;
 
1303
                       Tag==?proc_heap ->
1183
1304
    true;
1184
1305
is_proc_tag(_) ->
1185
1306
    false.
1186
1307
 
1187
 
related_tags("Atoms") ->
1188
 
    ["=atoms","=num_atoms"].
1189
 
 
1190
1308
%%% Inform the crashdump_viewer_server that a background job is completed.
1191
1309
background_done(Result) ->
1192
1310
    Dict = get(),
1198
1316
%%%-----------------------------------------------------------------
1199
1317
%%% Functions for reading information from the dump
1200
1318
general_info(File) ->
1201
 
    [{"=erl_crash_dump",_Id,Start}] = 
1202
 
        ets:lookup(cdv_dump_index_table,"=erl_crash_dump"),
 
1319
    [{_Id,Start}] = lookup_index(?erl_crash_dump),
1203
1320
    Fd = open(File),
1204
1321
    pos_bof(Fd,Start),
1205
1322
    Created = case get_rest_of_line(Fd) of
1207
1324
                  WholeLine -> WholeLine
1208
1325
              end,
1209
1326
 
1210
 
    GI0 = get_general_info(Fd,#general_info{created=Created,_=?space}),
 
1327
    GI0 = get_general_info(Fd,#general_info{created=Created}),
1211
1328
    GI = case GI0#general_info.num_atoms of
1212
1329
            ?space -> GI0#general_info{num_atoms=get_num_atoms(Fd)};
1213
1330
            _ -> GI0
1214
1331
        end,
1215
1332
 
1216
1333
    {MemTot,MemMax} = 
1217
 
        case ets:lookup(cdv_dump_index_table,"=memory") of
1218
 
            [{"=memory",_,MemStart}] ->
 
1334
        case lookup_index(?memory) of
 
1335
            [{_,MemStart}] ->
1219
1336
                pos_bof(Fd,MemStart),
1220
1337
                Memory = get_meminfo(Fd,[]),
1221
1338
                Tot = case lists:keysearch("total",1,Memory) of
1232
1349
        end,
1233
1350
 
1234
1351
    close(Fd),
1235
 
    {NumProcs,NumEts,NumFuns} = count(),
 
1352
    {NumProcs,NumEts,NumFuns,NumTimers} = count(),
1236
1353
    NodeName = 
1237
 
        case ets:lookup(cdv_dump_index_table,"=node") of
1238
 
            [{"=node",N,_Start}] ->
 
1354
        case lookup_index(?node) of
 
1355
            [{N,_Start}] ->
1239
1356
                N;
1240
1357
            [] ->
1241
 
                case ets:lookup(cdv_dump_index_table,"=no_distribution") of
 
1358
                case lookup_index(?no_distribution) of
1242
1359
                    [_] -> "nonode@nohost";
1243
1360
                    [] -> "unknown"
1244
1361
                end
1245
1362
        end,
1246
1363
 
1247
1364
    InstrInfo =
1248
 
        case ets:member(cdv_dump_index_table,"=old_instr_data") of
1249
 
            true ->
1250
 
                old_instr_data;
1251
 
            false ->
1252
 
                case ets:member(cdv_dump_index_table,"=instr_data") of
1253
 
                    true ->
1254
 
                        instr_data;
1255
 
                    false ->
1256
 
                        false
1257
 
                end
 
1365
        case lookup_index(?old_instr_data) of
 
1366
            [] ->
 
1367
                case lookup_index(?instr_data) of
 
1368
                    [] ->
 
1369
                        false;
 
1370
                    _ ->
 
1371
                        instr_data
 
1372
                end;
 
1373
            _ ->
 
1374
                old_instr_data
1258
1375
        end,
1259
1376
    GI#general_info{node_name=NodeName,
1260
1377
                    num_procs=integer_to_list(NumProcs),
1261
1378
                    num_ets=integer_to_list(NumEts),
 
1379
                    num_timers=integer_to_list(NumTimers),
1262
1380
                    num_fun=integer_to_list(NumFuns),
1263
1381
                    mem_tot=MemTot,
1264
1382
                    mem_max=MemMax,
1285
1403
    end.
1286
1404
 
1287
1405
get_num_atoms(Fd) ->
1288
 
    case ets:match(cdv_dump_index_table,{"=hash_table","atom_tab",'$1'}) of
1289
 
        [[Pos]] -> 
 
1406
    case lookup_index(?hash_table,"atom_tab") of
 
1407
        [{_,Pos}] -> 
1290
1408
            pos_bof(Fd,Pos),
1291
1409
            skip_rest_of_line(Fd), % size
1292
1410
            skip_rest_of_line(Fd), % used
1300
1418
            get_num_atoms2()
1301
1419
    end.
1302
1420
get_num_atoms2() ->
1303
 
    case ets:lookup(cdv_dump_index_table,"=num_atoms") of
 
1421
    case lookup_index(?num_atoms) of
1304
1422
        [] -> 
1305
1423
            ?space;
1306
 
        [{"=num_atoms",NA,_Pos}] -> 
 
1424
        [{NA,_Pos}] -> 
1307
1425
            %% If dump is translated this will exist
1308
1426
            case get(truncated) of
1309
1427
                true ->
1314
1432
    end.
1315
1433
 
1316
1434
count() ->
1317
 
    {ets:select_count(cdv_dump_index_table,count_ms("=proc")),
1318
 
     ets:select_count(cdv_dump_index_table,count_ms("=ets")),
1319
 
     ets:select_count(cdv_dump_index_table,count_ms("=fun"))}.
1320
 
 
1321
 
count_ms(Tag) ->
1322
 
    [{{Tag,'_','_'},[],[true]}].
1323
 
 
1324
 
 
1325
 
procs_summary(File) ->
1326
 
    AllProcs = ets:lookup(cdv_dump_index_table,"=proc"),
1327
 
    Fd = open(File),
1328
 
    R = lists:map(fun({"=proc",Pid,Start}) -> 
1329
 
                          pos_bof(Fd,Start),
1330
 
                          get_procinfo(Fd,fun main_procinfo/4,
1331
 
                                       ?initial_proc_record(Pid))
1332
 
                  end, 
1333
 
                  AllProcs),
1334
 
    close(Fd),
1335
 
    R.
1336
 
 
 
1435
    {count_index(?proc),count_index(?ets),count_index(?fu),count_index(?timer)}.
 
1436
 
 
1437
 
 
1438
%%-----------------------------------------------------------------
 
1439
%% Page with all processes
 
1440
%%
 
1441
%% If there are less than ?max_sort_process_num processes in the dump,
 
1442
%% we will store the list of processes in the server state in order to
 
1443
%% allow sorting according to the different columns of the
 
1444
%% table. Since ?max_sort_process_num=:=?items_chunk_size, there will
 
1445
%% never be more than one chunk in this case.
 
1446
%% 
 
1447
%% If there are more than ?max_sort_process_num processes in the dump,
 
1448
%% no sorting will be allowed, and the processes must be read (chunk
 
1449
%% by chunk) from the file each time the page is opened. This is to
 
1450
%% avoid really big data in the server state.
 
1451
procs_summary(SessionId,TW,_,State=#state{procs_summary=too_many}) ->
 
1452
    chunk_page(SessionId,State#state.file,TW,?proc,processes,
 
1453
               {no_sort,State#state.shared_heap},procs_summary_parsefun()),
 
1454
    State;
 
1455
procs_summary(SessionId,TW,SortOn,State) ->
 
1456
    ProcsSummary = 
 
1457
        case State#state.procs_summary of
 
1458
            undefined -> % first time - read from file
 
1459
                Fd = open(State#state.file),
 
1460
                {PS,_}=lookup_and_parse_index_chunk(first_chunk_pointer(?proc),
 
1461
                                                    Fd,procs_summary_parsefun()),
 
1462
                close(Fd),
 
1463
                PS;
 
1464
            PS ->
 
1465
                PS
 
1466
        end,
 
1467
    {SortedPS,NewSorted} = do_sort_procs(SortOn,ProcsSummary,State#state.sorted),
 
1468
    HtmlInfo = 
 
1469
        crashdump_viewer_html:chunk_page(processes,SessionId,TW,
 
1470
                                         {SortOn,State#state.shared_heap},
 
1471
                                         SortedPS),
 
1472
    crashdump_viewer_html:chunk(SessionId,done,HtmlInfo),
 
1473
    State#state{procs_summary=ProcsSummary,sorted=NewSorted}.
 
1474
 
 
1475
procs_summary_parsefun() ->
 
1476
    fun(Fd,Pid) -> 
 
1477
            get_procinfo(Fd,fun main_procinfo/4,#proc{pid=Pid}) 
 
1478
    end.
 
1479
 
 
1480
%%-----------------------------------------------------------------
 
1481
%% Page with one process
1337
1482
get_proc_details(File,Pid) ->
1338
 
    DumpVsn = ets:lookup_element(cdv_dump_index_table,"=erl_crash_dump",2),
1339
 
    case ets:match(cdv_dump_index_table,{"=proc",Pid,'$1'}) of
1340
 
        [[Start]] ->
 
1483
    [{DumpVsn,_}] = lookup_index(?erl_crash_dump),
 
1484
    case lookup_index(?proc,Pid) of
 
1485
        [{_,Start}] ->
1341
1486
            Fd = open(File),
1342
1487
            pos_bof(Fd,Start),
1343
1488
            Proc0 = 
1344
1489
                case DumpVsn of
1345
1490
                    "0.0" -> 
1346
1491
                        %% Old version (translated)
1347
 
                        ?initial_proc_record(Pid);
 
1492
                        #proc{pid=Pid};
1348
1493
                    _ ->
1349
 
                        (?initial_proc_record(Pid))#proc{
1350
 
                          stack_dump=if_exist("=proc_stack",Pid),
1351
 
                          msg_q=if_exist("=proc_messages",Pid),
1352
 
                          dict=if_exist("=proc_dictionary",Pid),
1353
 
                          debug_dict=if_exist("=debug_proc_dictionary",Pid)}
 
1494
                        #proc{pid=Pid,
 
1495
                              stack_dump=if_exist(?proc_stack,Pid),
 
1496
                              msg_q=if_exist(?proc_messages,Pid),
 
1497
                              dict=if_exist(?proc_dictionary,Pid),
 
1498
                              debug_dict=if_exist(?debug_proc_dictionary,Pid)}
1354
1499
                end,
1355
1500
            Proc = get_procinfo(Fd,fun all_procinfo/4,Proc0),
1356
1501
            close(Fd),
1368
1513
    end.
1369
1514
 
1370
1515
if_exist(Tag,Key) ->
1371
 
    case ets:select_count(cdv_dump_index_table,[{{Tag,Key,'_'},[],[true]}]) of
 
1516
    case count_index(Tag,Key) of
1372
1517
        0 -> 
1373
1518
            Tag1 = 
1374
1519
                case is_proc_tag(Tag) of
1375
 
                    true -> "=proc";
 
1520
                    true -> ?proc;
1376
1521
                    false -> Tag
1377
1522
                end,
1378
1523
            case truncated_here({Tag1,Key}) of
1523
1668
                N
1524
1669
        end,
1525
1670
    Ms = ets:fun2ms(
1526
 
           fun({Tag,Id,Start}) when Tag=:="=visible_node", Id=:=Channel -> 
 
1671
           fun({{Tag,Start},Ch}) when Tag=:=?visible_node, Ch=:=Channel -> 
1527
1672
                   {"Visible Node",Start};
1528
 
              ({Tag,Id,Start}) when Tag=:="=hidden_node", Id=:=Channel ->
 
1673
              ({{Tag,Start},Ch}) when Tag=:=?hidden_node, Ch=:=Channel ->
1529
1674
                   {"Hidden Node",Start};
1530
 
              ({Tag,Id,Start}) when Tag=:="=not_connected", Id=:=Channel -> 
 
1675
              ({{Tag,Start},Ch}) when Tag=:=?not_connected, Ch=:=Channel -> 
1531
1676
                   {"Not Connected Node",Start}
1532
1677
           end),
 
1678
    
1533
1679
    case ets:select(cdv_dump_index_table,Ms) of
1534
1680
        [] -> 
1535
1681
            not_found;
1540
1686
            {other_node,Type,NodeInfo}
1541
1687
    end.
1542
1688
 
 
1689
 
1543
1690
expand_memory(File,What,Pid,Binaries) ->
1544
1691
    Fd = open(File),
1545
1692
    put(fd,Fd),
1548
1695
        case What of
1549
1696
            "StackDump" -> read_stack_dump(Fd,Pid,Dict);
1550
1697
            "MsgQueue" -> read_messages(Fd,Pid,Dict);
1551
 
            "Dictionary" -> read_dictionary(Fd,"=proc_dictionary",Pid,Dict);
1552
 
            "DebugDictionary" -> read_dictionary(Fd,"=debug_proc_dictionary",Pid,Dict)
 
1698
            "Dictionary" -> read_dictionary(Fd,?proc_dictionary,Pid,Dict);
 
1699
            "DebugDictionary" -> read_dictionary(Fd,?debug_proc_dictionary,Pid,Dict)
1553
1700
        end,
1554
1701
    erase(fd),
1555
1702
    close(Fd),
1559
1706
%%% Read binaries.
1560
1707
%%%
1561
1708
read_binaries(Fd) ->
1562
 
    AllBinaries = ets:match(cdv_dump_index_table,{"=binary",'$1','$2'}),
 
1709
    AllBinaries = lookup_index(?binary),
1563
1710
    read_binaries(Fd,AllBinaries, gb_trees:empty()).
1564
1711
 
1565
 
read_binaries(Fd,[[Addr0,Pos]|Bins],Dict0) ->
 
1712
read_binaries(Fd,[{Addr0,Pos}|Bins],Dict0) ->
1566
1713
    pos_bof(Fd,Pos),
1567
1714
    {Addr,_} = get_hex(Addr0),
1568
1715
    Dict = 
1603
1750
%%%
1604
1751
 
1605
1752
read_stack_dump(Fd,Pid,Dict) ->
1606
 
    case ets:match(cdv_dump_index_table,{"=proc_stack",Pid,'$1'}) of
1607
 
        [[Start]] ->
 
1753
    case lookup_index(?proc_stack,Pid) of
 
1754
        [{_,Start}] ->
1608
1755
            pos_bof(Fd,Start),
1609
1756
            read_stack_dump1(Fd,Dict,[]);
1610
1757
        [] ->
1611
1758
            []
1612
1759
    end.
1613
1760
read_stack_dump1(Fd,Dict,Acc) ->
1614
 
    %% This function is never called if the dump is truncated in "=proc_heap:Pid"
 
1761
    %% This function is never called if the dump is truncated in {?proc_heap,Pid}
1615
1762
    case val(Fd) of
1616
1763
        "=" ++ _next_tag ->
1617
1764
            lists:reverse(Acc);
1631
1778
%%%
1632
1779
 
1633
1780
read_messages(Fd,Pid,Dict) ->
1634
 
    case ets:match(cdv_dump_index_table,{"=proc_messages",Pid,'$1'}) of
1635
 
        [[Start]] ->
 
1781
    case lookup_index(?proc_messages,Pid) of
 
1782
        [{_,Start}] ->
1636
1783
            pos_bof(Fd,Start),
1637
1784
            read_messages1(Fd,Dict,[]);
1638
1785
        [] ->
1639
1786
            []
1640
1787
    end.
1641
1788
read_messages1(Fd,Dict,Acc) ->
1642
 
    %% This function is never called if the dump is truncated in "=proc_heap:Pid"
 
1789
    %% This function is never called if the dump is truncated in {?proc_heap,Pid}
1643
1790
    case val(Fd) of
1644
1791
        "=" ++ _next_tag ->
1645
1792
            lists:reverse(Acc);
1659
1806
%%%
1660
1807
 
1661
1808
read_dictionary(Fd,Tag,Pid,Dict) ->
1662
 
    case ets:match(cdv_dump_index_table,{Tag,Pid,'$1'}) of
1663
 
        [[Start]] ->
 
1809
    case lookup_index(Tag,Pid) of
 
1810
        [{_,Start}] ->
1664
1811
            pos_bof(Fd,Start),
1665
1812
            read_dictionary1(Fd,Dict,[]);
1666
1813
        [] ->
1667
1814
            []
1668
1815
    end.
1669
1816
read_dictionary1(Fd,Dict,Acc) ->
1670
 
    %% This function is never called if the dump is truncated in "=proc_heap:Pid"
 
1817
    %% This function is never called if the dump is truncated in {?proc_heap,Pid}
1671
1818
    case val(Fd) of
1672
1819
        "=" ++ _next_tag ->
1673
1820
            lists:reverse(Acc);
1686
1833
%%%
1687
1834
 
1688
1835
read_heap(Fd,Pid,Dict0) ->
1689
 
    case ets:match(cdv_dump_index_table,{"=proc_heap",Pid,'$2'}) of
1690
 
        [[Pos]] ->
 
1836
    case lookup_index(?proc_heap,Pid) of
 
1837
        [{_,Pos}] ->
1691
1838
            pos_bof(Fd,Pos),
1692
1839
            read_heap(Dict0);
1693
1840
        [] ->
1695
1842
    end.
1696
1843
 
1697
1844
read_heap(Dict0) ->
1698
 
    %% This function is never called if the dump is truncated in "=proc_heap:Pid"
 
1845
    %% This function is never called if the dump is truncated in {?proc_heap,Pid}
1699
1846
    case get(fd) of
1700
1847
        end_of_heap ->
1701
1848
            Dict0;
1761
1908
        _ -> {Result,"name"}
1762
1909
    end.
1763
1910
    
1764
 
 
 
1911
%%-----------------------------------------------------------------
 
1912
%% Page with one port
1765
1913
get_port(File,Port) ->
1766
 
    case ets:match(cdv_dump_index_table,{"=port",Port,'$1'}) of
1767
 
        [[Start]] ->
 
1914
    case lookup_index(?port,Port) of
 
1915
        [{_,Start}] ->
1768
1916
            Fd = open(File),
1769
 
            R = get_portinfo(Fd,Port,Start),
 
1917
            pos_bof(Fd,Start),
 
1918
            R = get_portinfo(Fd,#port{id=Port}),
1770
1919
            close(Fd),
1771
1920
            {ok,R};
1772
1921
        [] ->
1781
1930
            end
1782
1931
    end.
1783
1932
 
1784
 
get_ports(File) ->
1785
 
    Ports = ets:lookup(cdv_dump_index_table,"=port"),
1786
 
    Fd = open(File),
1787
 
    R = lists:map(fun({"=port",Id,Start}) -> get_portinfo(Fd,Id,Start) end, 
1788
 
                  Ports),
1789
 
    close(Fd),
1790
 
    R.
1791
 
 
1792
 
 
1793
 
get_portinfo(Fd,Id,Start) ->
1794
 
    pos_bof(Fd,Start),
1795
 
    get_portinfo(Fd,#port{id=Id,_=?space}).
 
1933
%%-----------------------------------------------------------------
 
1934
%% Page with all ports
 
1935
get_ports(SessionId,File,TW) ->
 
1936
    ParseFun = fun(Fd,Id) -> get_portinfo(Fd,#port{id=Id}) end,
 
1937
    chunk_page(SessionId,File,TW,?port,ports,[],ParseFun).
1796
1938
 
1797
1939
get_portinfo(Fd,Port) ->
1798
1940
    case line_head(Fd) of
1802
1944
            get_portinfo(Fd,Port#port{connected=val(Fd)});
1803
1945
        "Links" ->
1804
1946
            get_portinfo(Fd,Port#port{links=val(Fd)});
 
1947
        "Registered as" ->
 
1948
            get_portinfo(Fd,Port#port{name=val(Fd)});
 
1949
        "Monitors" ->
 
1950
            get_portinfo(Fd,Port#port{monitors=val(Fd)});
1805
1951
        "Port controls linked-in driver" ->
1806
1952
            get_portinfo(Fd,Port#port{controls=["Linked in driver: " |
1807
1953
                                                val(Fd)]});
1820
1966
            Port
1821
1967
    end.
1822
1968
 
1823
 
get_ets_tables(File,Pid,WS) ->
1824
 
    EtsTables = ets:match_object(cdv_dump_index_table,{"=ets",Pid,'_'}),
1825
 
    Fd = open(File),
1826
 
    R = lists:map(fun({"=ets",P,Start}) -> 
1827
 
                          get_etsinfo(Fd,P,Start,WS) 
1828
 
                  end, 
1829
 
                  EtsTables),
1830
 
    close(Fd),
1831
 
    R.
1832
1969
 
1833
 
get_internal_ets_tables(File,WS) ->
1834
 
    InternalEts = ets:match_object(cdv_dump_index_table,
1835
 
                                   {"=internal_ets",'_','_'}),
1836
 
    Fd = open(File),
1837
 
    R = lists:map(fun({"=internal_ets",Descr,Start}) ->
1838
 
                          {Descr,get_etsinfo(Fd,undefined,Start,WS)}
1839
 
                  end,
1840
 
                  InternalEts),
1841
 
    close(Fd),
1842
 
    R.
1843
 
    
1844
 
get_etsinfo(Fd,Pid,Start,WS) ->
1845
 
    pos_bof(Fd,Start),
1846
 
    get_etsinfo(Fd,#ets_table{pid=Pid,type="hash",_=?space},WS).
 
1970
%%-----------------------------------------------------------------
 
1971
%% Page with external ets tables
 
1972
get_ets_tables(SessionId,File,Heading,TW,Pid,WS) ->
 
1973
    ParseFun = fun(Fd,Id) -> get_etsinfo(Fd,#ets_table{pid=Id},WS) end,
 
1974
    chunk_page(SessionId,File,TW,{?ets,Pid},ets_tables,Heading,ParseFun).
1847
1975
 
1848
1976
get_etsinfo(Fd,EtsTable,WS) ->
1849
1977
    case line_head(Fd) of
1875
2003
            EtsTable
1876
2004
    end.
1877
2005
 
1878
 
get_timers(File,Pid) ->
1879
 
    Timers = ets:match_object(cdv_dump_index_table,{"=timer",Pid,'$1'}),
 
2006
 
 
2007
%% Internal ets table page
 
2008
get_internal_ets_tables(File,WS) ->
 
2009
    InternalEts = lookup_index(?internal_ets),
1880
2010
    Fd = open(File),
1881
 
    R = lists:map(fun({"=timer",P,Start}) -> 
1882
 
                          get_timerinfo(Fd,P,Start) 
1883
 
                  end, 
1884
 
                  Timers),
 
2011
    R = lists:map(
 
2012
          fun({Descr,Start}) ->
 
2013
                  pos_bof(Fd,Start),
 
2014
                  {Descr,get_etsinfo(Fd,#ets_table{},WS)}
 
2015
          end,
 
2016
          InternalEts),
1885
2017
    close(Fd),
1886
2018
    R.
1887
2019
 
1888
 
get_timerinfo(Fd,Pid,Start) ->
1889
 
    pos_bof(Fd,Start),
1890
 
    get_timerinfo(Fd,#timer{pid=Pid,_=?space}).
 
2020
%%-----------------------------------------------------------------
 
2021
%% Page with list of all timers 
 
2022
get_timers(SessionId,File,Heading,TW,Pid) ->
 
2023
    ParseFun = fun(Fd,Id) -> get_timerinfo_1(Fd,#timer{pid=Id}) end,
 
2024
    chunk_page(SessionId,File,TW,{?timer,Pid},timers,Heading,ParseFun).
1891
2025
 
1892
 
get_timerinfo(Fd,Timer) ->
 
2026
get_timerinfo_1(Fd,Timer) ->
1893
2027
    case line_head(Fd) of
1894
2028
        "Message" ->
1895
 
            get_timerinfo(Fd,Timer#timer{msg=val(Fd)});
 
2029
            get_timerinfo_1(Fd,Timer#timer{msg=val(Fd)});
1896
2030
        "Time left" ->
1897
 
            get_timerinfo(Fd,Timer#timer{time=val(Fd)});
 
2031
            get_timerinfo_1(Fd,Timer#timer{time=val(Fd)});
1898
2032
        "=" ++ _next_tag ->
1899
2033
            Timer;
1900
2034
        Other ->
1902
2036
            Timer
1903
2037
    end.
1904
2038
 
 
2039
%%-----------------------------------------------------------------
 
2040
%% Page with information about the erlang distribution
1905
2041
nods(File) ->
1906
 
    case ets:lookup(cdv_dump_index_table,"=no_distribution") of
 
2042
    case lookup_index(?no_distribution) of
1907
2043
        [] ->
1908
 
            V = ets:lookup(cdv_dump_index_table,"=visible_node"),
1909
 
            H = ets:lookup(cdv_dump_index_table,"=hidden_node"),
1910
 
            N = ets:lookup(cdv_dump_index_table,"=not_connected"),
 
2044
            V = lookup_index(?visible_node),
 
2045
            H = lookup_index(?hidden_node),
 
2046
            N = lookup_index(?not_connected),
1911
2047
            Fd = open(File),
1912
2048
            Visible = lists:map(
1913
 
                        fun({"=visible_node",Channel,Start}) -> 
 
2049
                        fun({Channel,Start}) -> 
1914
2050
                                get_nodeinfo(Fd,Channel,Start)
1915
2051
                        end, 
1916
2052
                        V),
1917
2053
            Hidden = lists:map(
1918
 
                       fun({"=hidden_node",Channel,Start}) -> 
 
2054
                       fun({Channel,Start}) -> 
1919
2055
                               get_nodeinfo(Fd,Channel,Start)
1920
2056
                       end, 
1921
2057
                       H),
1922
2058
            NotConnected = lists:map(
1923
 
                             fun({"=not_connected",Channel,Start}) -> 
 
2059
                             fun({Channel,Start}) -> 
1924
2060
                                     get_nodeinfo(Fd,Channel,Start)
1925
2061
                             end, 
1926
2062
                             N),
1932
2068
 
1933
2069
get_nodeinfo(Fd,Channel,Start) ->
1934
2070
    pos_bof(Fd,Start),
1935
 
    get_nodeinfo(Fd,#nod{channel=Channel,_=?space}).
 
2071
    get_nodeinfo(Fd,#nod{channel=Channel}).
1936
2072
 
1937
2073
get_nodeinfo(Fd,Nod) ->
1938
2074
    case line_head(Fd) of
1963
2099
            Nod
1964
2100
    end.
1965
2101
 
1966
 
loaded_mods(File) ->
1967
 
    case ets:lookup(cdv_dump_index_table,"=loaded_modules") of
1968
 
        [{"=loaded_modules",_,StartTotal}] ->
1969
 
            Fd = open(File),
1970
 
            pos_bof(Fd,StartTotal),
1971
 
            {CC,OC} = get_loaded_mod_totals(Fd,{"unknown","unknown"}),
1972
 
            
1973
 
            Mods = ets:lookup(cdv_dump_index_table,"=mod"),
1974
 
            LM = lists:map(fun({"=mod",M,Start}) -> 
1975
 
                                   pos_bof(Fd,Start),
1976
 
                                   InitLM = #loaded_mod{mod=M,_=?space},
1977
 
                                   get_loaded_mod_info(Fd,InitLM,
1978
 
                                                       fun main_modinfo/3)
1979
 
                           end, 
1980
 
                           Mods),
1981
 
            close(Fd),
1982
 
            {CC,OC,LM};
1983
 
        [] ->
1984
 
            {"unknown","unknown",[]}
1985
 
    end.
 
2102
%%-----------------------------------------------------------------
 
2103
%% Page with details about one loaded modules
 
2104
get_loaded_mod_details(File,Mod) ->
 
2105
    [{_,Start}] = lookup_index(?mod,Mod),
 
2106
    Fd = open(File),
 
2107
    pos_bof(Fd,Start),
 
2108
    InitLM = #loaded_mod{mod=Mod,old_size="No old code exists"},
 
2109
    ModInfo = get_loaded_mod_info(Fd,InitLM,fun all_modinfo/3),
 
2110
    close(Fd),
 
2111
    ModInfo.
 
2112
 
 
2113
%%-----------------------------------------------------------------
 
2114
%% Page with list of all loaded modules
 
2115
loaded_mods(SessionId,File,TW) ->
 
2116
    ParseFun = 
 
2117
        fun(Fd,Id) -> 
 
2118
                get_loaded_mod_info(Fd,#loaded_mod{mod=Id},
 
2119
                                    fun main_modinfo/3) 
 
2120
        end,
 
2121
    {CC,OC} = 
 
2122
        case lookup_index(?loaded_modules) of
 
2123
            [{_,StartTotal}] ->
 
2124
                Fd = open(File),
 
2125
                pos_bof(Fd,StartTotal),
 
2126
                R = get_loaded_mod_totals(Fd,{"unknown","unknown"}),
 
2127
                close(Fd),
 
2128
                R;
 
2129
            [] ->
 
2130
                {"unknown","unknown"}
 
2131
    end,
 
2132
    chunk_page(SessionId,File,TW,?mod,loaded_mods,{CC,OC},ParseFun).
1986
2133
 
1987
2134
get_loaded_mod_totals(Fd,{CC,OC}) ->
1988
2135
    case line_head(Fd) of
1997
2144
            {CC,OC} % truncated file
1998
2145
    end.
1999
2146
 
2000
 
get_loaded_mod_details(File,Mod) ->
2001
 
    [[Start]] = ets:match(cdv_dump_index_table,{"=mod",Mod,'$1'}),
2002
 
    Fd = open(File),
2003
 
    pos_bof(Fd,Start),
2004
 
    InitLM = #loaded_mod{mod=Mod,old_size="No old code exists",
2005
 
                         _="No information available"},
2006
 
    ModInfo = get_loaded_mod_info(Fd,InitLM,fun all_modinfo/3),
2007
 
    close(Fd),
2008
 
    ModInfo.
2009
 
 
2010
2147
get_loaded_mod_info(Fd,LM,Fun) ->
2011
2148
    case line_head(Fd) of
2012
2149
        "Current size" ->
2073
2210
hex_to_dec(N) -> list_to_integer(N).
2074
2211
    
2075
2212
 
2076
 
 
2077
 
funs(File) ->
2078
 
    case ets:lookup(cdv_dump_index_table,"=fun") of
2079
 
        [] ->
2080
 
            [];
2081
 
        AllFuns ->
2082
 
            Fd = open(File),
2083
 
            R = lists:map(fun({"=fun",_,Start}) -> 
2084
 
                                  get_funinfo(Fd,Start) 
2085
 
                          end, 
2086
 
                          AllFuns),
2087
 
            close(Fd),
2088
 
            R
2089
 
    end.
2090
 
 
2091
 
get_funinfo(Fd,Start) ->
2092
 
    pos_bof(Fd,Start),
2093
 
    get_funinfo1(Fd,#fu{_=?space}).
2094
 
 
2095
 
get_funinfo1(Fd,Fu) ->
 
2213
%%-----------------------------------------------------------------
 
2214
%% Page with list of all funs
 
2215
funs(SessionId,File,TW) ->
 
2216
    ParseFun = fun(Fd,_Id) -> get_funinfo(Fd,#fu{}) end,
 
2217
    chunk_page(SessionId,File,TW,?fu,funs,[],ParseFun).
 
2218
 
 
2219
get_funinfo(Fd,Fu) ->
2096
2220
    case line_head(Fd) of
2097
2221
        "Module" ->
2098
 
            get_funinfo1(Fd,Fu#fu{module=val(Fd)});
 
2222
            get_funinfo(Fd,Fu#fu{module=val(Fd)});
2099
2223
        "Uniq" ->
2100
 
            get_funinfo1(Fd,Fu#fu{uniq=val(Fd)});
 
2224
            get_funinfo(Fd,Fu#fu{uniq=val(Fd)});
2101
2225
        "Index" ->
2102
 
            get_funinfo1(Fd,Fu#fu{index=val(Fd)});
 
2226
            get_funinfo(Fd,Fu#fu{index=val(Fd)});
2103
2227
        "Address" ->
2104
 
            get_funinfo1(Fd,Fu#fu{address=val(Fd)});
 
2228
            get_funinfo(Fd,Fu#fu{address=val(Fd)});
2105
2229
        "Native_address" ->
2106
 
            get_funinfo1(Fd,Fu#fu{native_address=val(Fd)});
 
2230
            get_funinfo(Fd,Fu#fu{native_address=val(Fd)});
2107
2231
        "Refc" ->
2108
 
            get_funinfo1(Fd,Fu#fu{refc=val(Fd)});
 
2232
            get_funinfo(Fd,Fu#fu{refc=val(Fd)});
2109
2233
        "=" ++ _next_tag ->
2110
2234
            Fu;
2111
2235
        Other ->
2113
2237
            Fu
2114
2238
    end.
2115
2239
 
2116
 
atoms(File) ->
2117
 
    case ets:lookup(cdv_dump_index_table,"=atoms") of
2118
 
        [{_atoms,_Id,Start}] ->
 
2240
%%-----------------------------------------------------------------
 
2241
%% Page with list of all atoms
 
2242
atoms(SessionId,File,TW,Num) ->
 
2243
    case lookup_index(?atoms) of
 
2244
        [{_Id,Start}] ->
2119
2245
            Fd = open(File),
2120
2246
            pos_bof(Fd,Start),
2121
 
            R = case get_n_lines_of_tag(Fd,100) of
2122
 
                    {all,N,Lines} ->
2123
 
                        {n_lines,1,N,"Atoms",Lines};
2124
 
                    {part,100,Lines} ->
2125
 
                        {n_lines,1,100,"Atoms",Lines,get(pos)};
2126
 
                    empty ->
2127
 
                        []
2128
 
                end,
2129
 
            close(Fd),
2130
 
            R;
 
2247
            case get_atoms(Fd,?items_chunk_size) of
 
2248
                {Atoms,Cont} ->
 
2249
                    crashdump_viewer_html:atoms(SessionId,TW,Num,Atoms),
 
2250
                    atoms_chunks(Fd,SessionId,Cont);
 
2251
                done ->
 
2252
                    crashdump_viewer_html:atoms(SessionId,TW,Num,done)
 
2253
            end;
2131
2254
        _ ->
2132
 
            []
2133
 
    end.
2134
 
 
 
2255
            crashdump_viewer_html:atoms(SessionId,TW,Num,done)
 
2256
    end.
 
2257
 
 
2258
get_atoms(Fd,Number) ->
 
2259
    case get_n_lines_of_tag(Fd,Number) of
 
2260
        {all,_,Lines} ->
 
2261
            close(Fd),
 
2262
            {Lines,done};
 
2263
        {part,_,Lines} ->
 
2264
            {Lines,Number};
 
2265
        empty ->
 
2266
            close(Fd),
 
2267
            done
 
2268
    end.
 
2269
 
 
2270
atoms_chunks(_Fd,SessionId,done) ->
 
2271
    crashdump_viewer_html:atoms_chunk(SessionId,done);
 
2272
atoms_chunks(Fd,SessionId,Number) ->
 
2273
    case get_atoms(Fd,Number) of
 
2274
        {Atoms,Cont} ->
 
2275
            crashdump_viewer_html:atoms_chunk(SessionId,Atoms),
 
2276
            atoms_chunks(Fd,SessionId,Cont);
 
2277
        done ->
 
2278
            atoms_chunks(Fd,SessionId,done)
 
2279
    end.
 
2280
 
 
2281
 
 
2282
%%-----------------------------------------------------------------
 
2283
%% Page with memory information
2135
2284
memory(File) ->
2136
 
    case ets:lookup(cdv_dump_index_table,"=memory") of
2137
 
        [{"=memory",_,Start}] ->
 
2285
    case lookup_index(?memory) of
 
2286
        [{_,Start}] ->
2138
2287
            Fd = open(File),
2139
2288
            pos_bof(Fd,Start),
2140
2289
            R = get_meminfo(Fd,[]),
2153
2302
        Key ->
2154
2303
            get_meminfo(Fd,[{Key,val(Fd)}|Acc])
2155
2304
    end.
2156
 
            
 
2305
 
 
2306
%%-----------------------------------------------------------------
 
2307
%% Page with information about allocated areas
2157
2308
allocated_areas(File) ->
2158
 
    case ets:lookup(cdv_dump_index_table,"=allocated_areas") of
2159
 
        [{"=allocated_areas",_,Start}] ->
 
2309
    case lookup_index(?allocated_areas) of
 
2310
        [{_,Start}] ->
2160
2311
            Fd = open(File),
2161
2312
            pos_bof(Fd,Start),
2162
2313
            R = get_allocareainfo(Fd,[]),
2183
2334
                end,
2184
2335
            get_allocareainfo(Fd,[AllocInfo|Acc])
2185
2336
    end.
2186
 
            
 
2337
 
 
2338
%%-----------------------------------------------------------------
 
2339
%% Page with information about allocators
2187
2340
allocator_info(File) ->
2188
 
    case ets:lookup(cdv_dump_index_table,"=allocator") of
 
2341
    case lookup_index(?allocator) of
2189
2342
        [] ->
2190
2343
            [];
2191
2344
        AllAllocators ->
2192
2345
            Fd = open(File),
2193
 
            R = lists:map(fun({"=allocator",Heading,Start}) -> 
 
2346
            R = lists:map(fun({Heading,Start}) ->
2194
2347
                                  {Heading,get_allocatorinfo(Fd,Start)} 
2195
2348
                          end, 
2196
2349
                          AllAllocators),
2220
2373
get_all_vals([Char|Rest],Acc) ->
2221
2374
    get_all_vals(Rest,[Char|Acc]).
2222
2375
 
2223
 
 
 
2376
%%-----------------------------------------------------------------
 
2377
%% Page with hash table information
2224
2378
hash_tables(File) ->
2225
 
    case ets:lookup(cdv_dump_index_table,"=hash_table") of
 
2379
    case lookup_index(?hash_table) of
2226
2380
        [] ->
2227
2381
            [];
2228
2382
        AllHashTables ->
2229
2383
            Fd = open(File),
2230
 
            R = lists:map(fun({"=hash_table",Name,Start}) -> 
 
2384
            R = lists:map(fun({Name,Start}) ->
2231
2385
                                  get_hashtableinfo(Fd,Name,Start) 
2232
2386
                          end, 
2233
2387
                          AllHashTables),
2237
2391
 
2238
2392
get_hashtableinfo(Fd,Name,Start) ->
2239
2393
    pos_bof(Fd,Start),
2240
 
    get_hashtableinfo1(Fd,#hash_table{name=Name,_=?space}).
 
2394
    get_hashtableinfo1(Fd,#hash_table{name=Name}).
2241
2395
 
2242
2396
get_hashtableinfo1(Fd,HashTable) ->
2243
2397
    case line_head(Fd) of
2256
2410
            HashTable
2257
2411
    end.
2258
2412
 
 
2413
%%-----------------------------------------------------------------
 
2414
%% Page with index table information
2259
2415
index_tables(File) ->
2260
 
    case ets:lookup(cdv_dump_index_table,"=index_table") of
 
2416
    case lookup_index(?index_table) of
2261
2417
        [] ->
2262
2418
            [];
2263
2419
        AllIndexTables ->
2264
2420
            Fd = open(File),
2265
 
            R = lists:map(fun({"=index_table",Name,Start}) -> 
 
2421
            R = lists:map(fun({Name,Start}) ->
2266
2422
                                  get_indextableinfo(Fd,Name,Start) 
2267
2423
                          end, 
2268
2424
                          AllIndexTables),
2272
2428
 
2273
2429
get_indextableinfo(Fd,Name,Start) ->
2274
2430
    pos_bof(Fd,Start),
2275
 
    get_indextableinfo1(Fd,#index_table{name=Name,_=?space}).
 
2431
    get_indextableinfo1(Fd,#index_table{name=Name}).
2276
2432
 
2277
2433
get_indextableinfo1(Fd,IndexTable) ->
2278
2434
    case line_head(Fd) of
2284
2440
            get_indextableinfo1(Fd,IndexTable#index_table{limit=val(Fd)});
2285
2441
        "rate" ->
2286
2442
            get_indextableinfo1(Fd,IndexTable#index_table{rate=val(Fd)});
 
2443
        "entries" ->
 
2444
            get_indextableinfo1(Fd,IndexTable#index_table{entries=val(Fd)});
2287
2445
        "=" ++ _next_tag ->
2288
2446
            IndexTable;
2289
2447
        Other ->
2295
2453
 
2296
2454
 
2297
2455
 
 
2456
%%-----------------------------------------------------------------
 
2457
%% Expand a set of data which was shown in a truncated form on
2298
2458
get_expanded(File,Pos,Size) ->
2299
2459
    Fd = open(File),
2300
2460
    R = case file:pread(Fd,Pos,Size) of
2307
2467
    R.
2308
2468
 
2309
2469
 
2310
 
get_next(File,Pos,N0,Start,What) ->
2311
 
    Fd = open(File),
2312
 
    pos_bof(Fd,Pos),
2313
 
    R = case get_n_lines_of_tag(Fd,N0) of
2314
 
            {all,N,Lines} ->
2315
 
                {n_lines,Start,N,What,Lines};
2316
 
            {part,N,Lines} ->
2317
 
                {n_lines,Start,N,What,Lines,get(pos)}
2318
 
        end,
2319
 
    close(Fd),
2320
 
    R.
2321
 
 
2322
 
 
2323
 
 
2324
2470
replace_all(From,To,[From|Rest],Acc) ->
2325
2471
    replace_all(From,To,Rest,[To|Acc]);
2326
2472
replace_all(From,To,[Char|Rest],Acc) ->
2567
2713
 
2568
2714
cdvbin(Sz,Pos) ->
2569
2715
    "#CDVBin<"++integer_to_list(Sz)++","++integer_to_list(Pos)++">".
 
2716
 
 
2717
 
 
2718
%%-----------------------------------------------------------------
 
2719
%% Functions for accessing the cdv_dump_index_table
 
2720
reset_index_table() ->
 
2721
    ets:delete_all_objects(cdv_dump_index_table).
 
2722
 
 
2723
insert_index(Tag,Id,Pos) ->
 
2724
    ets:insert(cdv_dump_index_table,{{Tag,Pos},Id}).
 
2725
 
 
2726
lookup_index(Tag) ->
 
2727
    lookup_index(Tag,'$2').
 
2728
lookup_index(Tag,Id) ->
 
2729
    ets:select(cdv_dump_index_table,[{{{Tag,'$1'},Id},[],[{{Id,'$1'}}]}]).
 
2730
 
 
2731
lookup_index_chunk({'#CDVFirstChunk',Tag,Id}) ->
 
2732
    ets:select(cdv_dump_index_table,
 
2733
               [{{{Tag,'$1'},Id},[],[{{Id,'$1'}}]}],
 
2734
               ?items_chunk_size);
 
2735
lookup_index_chunk(Cont) ->
 
2736
    ets:select(Cont).
 
2737
 
 
2738
%% Create a tag which can be used instead of an ets Continuation for
 
2739
%% the first call to lookup_index_chunk.
 
2740
first_chunk_pointer({Tag,Id}) ->
 
2741
    {'#CDVFirstChunk',Tag,Id};
 
2742
first_chunk_pointer(Tag) ->
 
2743
    first_chunk_pointer({Tag,'$2'}).
 
2744
 
 
2745
count_index(Tag) ->
 
2746
    ets:select_count(cdv_dump_index_table,[{{{Tag,'_'},'_'},[],[true]}]).
 
2747
count_index(Tag,Id) ->
 
2748
    ets:select_count(cdv_dump_index_table,[{{{Tag,'_'},Id},[],[true]}]).
 
2749
 
 
2750
 
 
2751
%%-----------------------------------------------------------------
 
2752
%% Convert tags read from crashdump to atoms used as first part of key
 
2753
%% in cdv_dump_index_table
 
2754
tag_to_atom("allocated_areas") -> ?allocated_areas;
 
2755
tag_to_atom("allocator") -> ?allocator;
 
2756
tag_to_atom("atoms") -> ?atoms;
 
2757
tag_to_atom("binary") -> ?binary;
 
2758
tag_to_atom("debug_proc_dictionary") -> ?debug_proc_dictionary;
 
2759
tag_to_atom("end") -> ?ende;
 
2760
tag_to_atom("erl_crash_dump") -> ?erl_crash_dump;
 
2761
tag_to_atom("ets") -> ?ets;
 
2762
tag_to_atom("fun") -> ?fu;
 
2763
tag_to_atom("hash_table") -> ?hash_table;
 
2764
tag_to_atom("hidden_node") -> ?hidden_node;
 
2765
tag_to_atom("index_table") -> ?index_table;
 
2766
tag_to_atom("instr_data") -> ?instr_data;
 
2767
tag_to_atom("internal_ets") -> ?internal_ets;
 
2768
tag_to_atom("loaded_modules") -> ?loaded_modules;
 
2769
tag_to_atom("memory") -> ?memory;
 
2770
tag_to_atom("mod") -> ?mod;
 
2771
tag_to_atom("no_distribution") -> ?no_distribution;
 
2772
tag_to_atom("node") -> ?node;
 
2773
tag_to_atom("not_connected") -> ?not_connected;
 
2774
tag_to_atom("num_atoms") -> ?num_atoms;
 
2775
tag_to_atom("old_instr_data") -> ?old_instr_data;
 
2776
tag_to_atom("port") -> ?port;
 
2777
tag_to_atom("proc") -> ?proc;
 
2778
tag_to_atom("proc_dictionary") -> ?proc_dictionary;
 
2779
tag_to_atom("proc_heap") -> ?proc_heap;
 
2780
tag_to_atom("proc_messages") -> ?proc_messages;
 
2781
tag_to_atom("proc_stack") -> ?proc_stack;
 
2782
tag_to_atom("timer") -> ?timer;
 
2783
tag_to_atom("visible_node") -> ?visible_node;
 
2784
tag_to_atom(UnknownTag) ->
 
2785
    io:format("WARNING: Found unexpected tag:~s~n",[UnknownTag]),
 
2786
    list_to_atom(UnknownTag).
 
2787
 
 
2788
%%%-----------------------------------------------------------------
 
2789
%%% Create a page by sending chunk by chunk to crashdump_viewer_html
 
2790
chunk_page(SessionId,File,TW,What,HtmlCB,HtmlExtra,ParseFun) ->
 
2791
    Fd = open(File),
 
2792
    case lookup_and_parse_index_chunk(first_chunk_pointer(What),Fd,ParseFun) of
 
2793
        done ->
 
2794
            crashdump_viewer_html:chunk_page(HtmlCB,SessionId,TW,HtmlExtra,done);
 
2795
        {Chunk,Cont} ->
 
2796
            HtmlInfo = crashdump_viewer_html:chunk_page(
 
2797
                             HtmlCB,
 
2798
                             SessionId,TW,HtmlExtra,Chunk),
 
2799
            chunk_page_1(Fd,HtmlInfo,SessionId,ParseFun,
 
2800
                         lookup_and_parse_index_chunk(Cont,Fd,ParseFun))
 
2801
    end.
 
2802
 
 
2803
chunk_page_1(_Fd,HtmlInfo,SessionId,_ParseFun,done) ->
 
2804
    crashdump_viewer_html:chunk(SessionId,done,HtmlInfo);
 
2805
chunk_page_1(Fd,HtmlInfo,SessionId,ParseFun,{Chunk,Cont}) ->
 
2806
    crashdump_viewer_html:chunk(SessionId,Chunk,HtmlInfo),
 
2807
    chunk_page_1(Fd,HtmlInfo,SessionId,ParseFun,
 
2808
                 lookup_and_parse_index_chunk(Cont,Fd,ParseFun)).
 
2809
 
 
2810
lookup_and_parse_index_chunk(Pointer,Fd,ParseFun) ->
 
2811
    case lookup_index_chunk(Pointer) of
 
2812
        '$end_of_table' ->
 
2813
            close(Fd),
 
2814
            done;
 
2815
        {Chunk,Cont} ->
 
2816
            R = lists:map(fun({Id,Start}) ->
 
2817
                                  pos_bof(Fd,Start),
 
2818
                                  ParseFun(Fd,Id)
 
2819
                          end,
 
2820
                          Chunk),
 
2821
            {R,Cont}
 
2822
    end.