~ubuntu-branches/ubuntu/trusty/erlang/trusty

« back to all changes in this revision

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

  • Committer: Bazaar Package Importer
  • Author(s): Clint Byrum
  • Date: 2011-05-05 15:48:43 UTC
  • mfrom: (3.5.13 sid)
  • Revision ID: james.westby@ubuntu.com-20110505154843-0om6ekzg6m7ugj27
Tags: 1:14.b.2-dfsg-3ubuntu1
* Merge from debian unstable.  Remaining changes:
  - Drop libwxgtk2.8-dev build dependency. Wx isn't in main, and not
    supposed to.
  - Drop erlang-wx binary.
  - Drop erlang-wx dependency from -megaco, -common-test, and -reltool, they
    do not really need wx. Also drop it from -debugger; the GUI needs wx,
    but it apparently has CLI bits as well, and is also needed by -megaco,
    so let's keep the package for now.
  - debian/patches/series: Do what I meant, and enable build-options.patch
    instead.
* Additional changes:
  - Drop erlang-wx from -et
* Dropped Changes:
  - patches/pcre-crash.patch: CVE-2008-2371: outer level option with
    alternatives caused crash. (Applied Upstream)
  - fix for ssl certificate verification in newSSL: 
    ssl_cacertfile_fix.patch (Applied Upstream)
  - debian/patches/series: Enable native.patch again, to get stripped beam
    files and reduce the package size again. (build-options is what
    actually accomplished this)
  - Remove build-options.patch on advice from upstream and because it caused
    odd build failures.

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
32
32
         general_info/1,
33
33
         pretty_info_page/2,
34
34
         info_page/2,
35
 
         procs_summary/4,
36
35
         proc_details/4,
37
36
         expanded_memory/2,
38
37
         expanded_binary/1,
39
 
         next/2,
40
 
         ports/3,
41
 
         timers/3,
42
 
         ets_tables/4,
 
38
         port/3,
 
39
         internal_ets_tables/2,
43
40
         nods/2,
44
 
         loaded_mods/2,
45
41
         loaded_mod_details/2,
46
 
         funs/2,
47
 
         atoms/3,
 
42
         atoms/4,
 
43
         atoms_chunk/2,
48
44
         memory/2,
49
45
         allocated_areas/2,
50
46
         allocator_info/2,
51
47
         hash_tables/2,
52
48
         index_tables/2,
53
 
         error/2]).
 
49
         error/2,
 
50
         chunk_page/5,
 
51
         chunk/3]).
54
52
 
55
53
-include("crashdump_viewer.hrl").
56
54
 
79
77
 
80
78
 
81
79
read_file_frame_body() ->
82
 
    Entry =
83
 
        case webtool:is_localhost() of 
84
 
            true -> [input("TYPE=file NAME=browse SIZE=40"),
85
 
                     input("TYPE=hidden NAME=path")];
86
 
            false -> input("TYPE=text NAME=path SIZE=60")
87
 
        end,
 
80
    %% Using a plain text input field instead of a file input field
 
81
    %% (e.g. <INPUT TYPE=file NAME=pathj SIZE=40">) because most
 
82
    %% browsers can not forward the full path from this dialog even if
 
83
    %% the browser is running on localhost (Ref 'fakepath'-problem)
 
84
    Entry = input("TYPE=text NAME=path SIZE=60"),
88
85
    Form = 
89
86
        form(
90
 
          "NAME=read_file_form METHOD=post ACTION= \"./read_file\"",
 
87
          "NAME=read_file_form METHOD=post ACTION=\"./read_file\"",
91
88
          table(
92
89
            "BORDER=0",
93
90
            [tr(td("COLSPAN=2","Enter file to analyse")),
94
91
             tr(
95
92
               [td(Entry),
96
 
                td("ALIGN=center",
97
 
                   input("TYPE=submit onClick=\"path.value=browse.value;\""
98
 
                         "VALUE=Ok"))])])),
 
93
                td("ALIGN=center",input("TYPE=submit VALUE=Ok"))])])),
99
94
    table(
100
95
      "WIDTH=100% HEIGHT=60%",
101
96
      tr("VALIGN=middle",
215
210
            td(GenInfo#general_info.system_vsn)]),
216
211
        tr([th("ALIGN=left BGCOLOR=\"#8899AA\"","Compiled"),
217
212
            td(GenInfo#general_info.compile_time)]),
 
213
        tr([th("ALIGN=left BGCOLOR=\"#8899AA\"","Taints"),
 
214
            td(GenInfo#general_info.taints)]),
218
215
        case GenInfo#general_info.mem_tot of
219
216
            "" -> "";
220
217
            MemTot ->
233
230
            td(GenInfo#general_info.num_procs)]),
234
231
        tr([th("ALIGN=left BGCOLOR=\"#8899AA\"","ETS tables"),
235
232
            td(GenInfo#general_info.num_ets)]),
 
233
        tr([th("ALIGN=left BGCOLOR=\"#8899AA\"","Timers"),
 
234
            td(GenInfo#general_info.num_timers)]),
236
235
        tr([th("ALIGN=left BGCOLOR=\"#8899AA\"","Funs"),
237
236
            td(GenInfo#general_info.num_fun)])]),
238
237
     case GenInfo#general_info.instr_info of
293
292
     pre(pretty_format(Info))].
294
293
    
295
294
%%%-----------------------------------------------------------------
296
 
%%% Make table with summary of process information
297
 
procs_summary(Sorted,ProcsSummary,TW,SharedHeap) ->
298
 
    Heading = "Process Information",
299
 
    header(Heading,
300
 
           body(
301
 
             procs_summary_body(Heading,ProcsSummary,TW,Sorted,SharedHeap))).
302
 
    
303
 
procs_summary_body(Heading,[],TW,_Sorted,_SharedHeap) ->
304
 
    [h1(Heading),
305
 
     warn(TW),
306
 
     "No processes were found\n"];
307
 
procs_summary_body(Heading,ProcsSummary,TW,Sorted,SharedHeap) ->
308
 
    MemHeading = 
309
 
        if SharedHeap -> 
310
 
                "Stack";
311
 
           true ->
312
 
                "Stack+heap"
313
 
        end,
314
 
 
315
 
    [heading(Heading,"processes"),
316
 
     warn(TW),
317
 
     table(
318
 
       "BORDER=4 CELLPADDING=4",
319
 
       [tr(
320
 
          [summary_table_head("pid","Pid",Sorted),
321
 
           summary_table_head("name_func","Name/Spawned as",Sorted),
322
 
           summary_table_head("state","State",Sorted), 
323
 
           summary_table_head("reds","Reductions",Sorted), 
324
 
           summary_table_head("mem",MemHeading,Sorted),
325
 
           summary_table_head("msg_q_len","MsgQ Length",Sorted)]) |
326
 
        lists:map(fun(Proc) -> procs_summary_table(Proc) end,ProcsSummary)])].
327
 
 
328
 
summary_table_head(Sorted,Text,Sorted) ->
329
 
    %% Mark the sorted column (bigger and italic)
330
 
    th(font("SIZE=\"+1\"",em(href("./sort_procs?sort="++Sorted,Text))));
331
 
summary_table_head(SortOn,Text,_Sorted) ->
332
 
    th(href("./sort_procs?sort="++SortOn,Text)).
333
 
 
334
 
procs_summary_table(Proc) ->
335
 
    #proc{pid=Pid,name=Name,state=State,
336
 
          reds=Reds,stack_heap=Mem0,msg_q_len=MsgQLen}=Proc,
337
 
    Mem = case Mem0 of
338
 
              -1 -> "unknown";
339
 
              _ -> integer_to_list(Mem0)
340
 
          end,
341
 
    tr(
342
 
      [td(href(["./proc_details?pid=",Pid],Pid)),
343
 
       td(Name),
344
 
       td(State),
345
 
       td("ALIGN=right",integer_to_list(Reds)),
346
 
       td("ALIGN=right",Mem),
347
 
       td("ALIGN=right",integer_to_list(MsgQLen))]).
348
 
 
349
 
%%%-----------------------------------------------------------------
350
295
%%% Print details for one process
351
296
proc_details(Pid,Proc,TW,SharedHeap) ->
352
297
    Script = 
592
537
     href("javascript:history.go(-1)","BACK")].
593
538
    
594
539
%%%-----------------------------------------------------------------
595
 
%%% Print table of ports
596
 
ports(Heading,Ports,TW) ->
597
 
    header(Heading,body(ports_body(Heading,Ports,TW))).
 
540
%%% Print info for one port
 
541
port(Heading,Port,TW) ->
 
542
    header(Heading,body(port_body(Heading,Port,TW))).
598
543
    
599
 
ports_body(Heading,[],TW) ->
600
 
    [h1(Heading),
601
 
     warn(TW),
602
 
     "No ports were found\n"];
603
 
ports_body(Heading,Ports,TW) ->
 
544
port_body(Heading,Port,TW) ->
604
545
    [heading(Heading,"ports"),
605
546
     warn(TW),
606
547
     table(
607
548
       "BORDER=4 CELLPADDING=4",
608
 
       [tr(
609
 
          [th("Id"),
610
 
           th("Slot"),
611
 
           th("Connected"),
612
 
           th("Links"),
613
 
           th("Controls")]) |
614
 
        lists:map(fun(Port) -> ports_table(Port) end, Ports)])].
 
549
       [tr([th(Head) || Head <- port_table_head()]), ports_table(Port)])].
615
550
 
616
 
ports_table(Port) ->
617
 
    #port{id=Id,slot=Slot,connected=Connected,links=Links,
618
 
          controls=Controls}=Port,
619
 
    tr(
620
 
      [td(Id),
621
 
       td("ALIGHT=right",Slot),
622
 
       td(href_proc_port(Connected)),
623
 
       td(href_proc_port(Links)),
624
 
       td(Controls)]).
625
 
    
626
551
%%%-----------------------------------------------------------------
627
 
%%% Print table of ETS tables
628
 
ets_tables(Heading,EtsTables,InternalEts,TW) ->
629
 
    header(Heading,body(ets_tables_body(Heading,EtsTables,InternalEts,TW))).
 
552
%%% Print table of internal ETS tables
 
553
internal_ets_tables(InternalEts,TW) ->
 
554
    Heading = "Internal ETS tables",
 
555
    header(Heading,body(internal_ets_tables_body(Heading,InternalEts,TW))).
630
556
    
631
 
ets_tables_body(Heading,[],InternalEts,TW) ->
 
557
internal_ets_tables_body(Heading,[],TW) ->
632
558
    [h1(Heading),
633
559
     warn(TW),
634
 
     "No ETS tables were found\n" |
635
 
     internal_ets_tables_table(InternalEts)];
636
 
ets_tables_body(Heading,EtsTables,InternalEts,TW) ->
637
 
    [heading(Heading,"ets_tables"),
 
560
     "No internal ETS tables were found\n"];
 
561
internal_ets_tables_body(Heading,InternalEts,TW) ->
 
562
    [heading(Heading,"internal_ets_tables"),
638
563
     warn(TW),
639
564
     table(
640
565
       "BORDER=4 CELLPADDING=4",
641
566
       [tr(
642
 
          [th("Owner"),
643
 
           th("Slot"),
644
 
           th("Id"),
645
 
           th("Name"),
646
 
           th("Type"),
647
 
           th("Buckets"),
648
 
           th("Objects"),
649
 
           th("Memory (bytes)")]) |
650
 
        lists:map(fun(EtsTable) -> ets_tables_table(EtsTable) end,
651
 
                  EtsTables)]) |
652
 
    internal_ets_tables_table(InternalEts)].
653
 
 
654
 
ets_tables_table(EtsTable) ->
655
 
    #ets_table{pid=Pid,slot=Slot,id=Id,name=Name,type=Type,
656
 
               buckets=Buckets,size=Size,memory=Memory} = EtsTable,
657
 
    tr(
658
 
      [td(href_proc_port(Pid)),
659
 
       td(Slot),
660
 
       td(Id),
661
 
       td(Name),
662
 
       td(Type),
663
 
       td("ALIGN=right",Buckets),
664
 
       td("ALIGN=right",Size),
665
 
       td("ALIGN=right",Memory)]).
666
 
 
667
 
internal_ets_tables_table(InternalEtsTables) ->
668
 
    [h2("Internal ETS tables"),
669
 
     table(
670
 
       "BORDER=4 CELLPADDING=4",
671
 
       [tr(
672
567
          [th("Description"),
673
568
           th("Id"),
674
569
           th("Name"),
679
574
        lists:map(fun(InternalEtsTable) -> 
680
575
                          internal_ets_tables_table1(InternalEtsTable)
681
576
                  end,
682
 
                  InternalEtsTables)])].
 
577
                  InternalEts)])].
683
578
 
684
579
internal_ets_tables_table1({Descr,InternalEtsTable}) ->
685
580
    #ets_table{id=Id,name=Name,type=Type,buckets=Buckets,
694
589
       td("ALIGN=right",Memory)]).
695
590
 
696
591
%%%-----------------------------------------------------------------
697
 
%%% Print table of timers
698
 
timers(Heading,Timers,TW) ->
699
 
    header(Heading,body(timers_body(Heading,Timers,TW))).
700
 
    
701
 
timers_body(Heading,[],TW) ->
702
 
    [h1(Heading),
703
 
     warn(TW),
704
 
     "No timers were found\n"];
705
 
timers_body(Heading,Timers,TW) ->
706
 
    [heading(Heading,"timers"),
707
 
     warn(TW),
708
 
     table(
709
 
       "BORDER=4 CELLPADDING=4",
710
 
       [tr(
711
 
          [th("Owner"),
712
 
           th("Message"),
713
 
           th("Time left")]) |
714
 
        lists:map(fun(Timer) -> timers_table(Timer) end, Timers)])].
715
 
 
716
 
timers_table(Timer) ->
717
 
    #timer{pid=Pid,msg=Msg,time=Time}=Timer,
718
 
    tr(
719
 
      [td(href_proc_port(Pid)),
720
 
       td(Msg),
721
 
       td("ALIGN=right",Time)]).
722
 
 
723
 
%%%-----------------------------------------------------------------
724
592
%%% Print table of nodes in distribution
725
593
nods(Nods,TW) ->
726
594
    header("Distribution Information",body(nodes_body(Nods,TW))).
824
692
         ?space -> "";
825
693
         _ -> font("COLOR=\"#FF0000\"",["ERROR: ",Error,"\n"])
826
694
     end.
827
 
%%%-----------------------------------------------------------------
828
 
%%% Print loaded modules information
829
 
loaded_mods({CC,OC,LM},TW) ->
830
 
    Heading = "Loaded Modules Information",
831
 
    header(Heading,body(loaded_mods_body(Heading,CC,OC,LM,TW))).
832
 
    
833
 
loaded_mods_body(Heading,"unknown","unknown",[],TW) ->
834
 
    [h1(Heading),
835
 
     warn(TW),
836
 
     "No loaded modules information was found\n"];
837
 
loaded_mods_body(Heading,CC,OC,LM,TW) ->
838
 
    [heading(Heading,"loaded_modules"),
839
 
     warn(TW),
840
 
     p([b("Current code: "),CC," bytes",br(),
841
 
        b("Old code: "),OC," bytes"]),
842
 
     table(
843
 
       "BORDER=4 CELLPADDING=4",
844
 
       [tr([th("Module"),
845
 
            th("Current size (bytes)"),
846
 
            th("Old size (bytes)")]) |
847
 
        lists:map(fun(Mod) -> loaded_mods_table(Mod) end,LM)])].
848
 
 
849
 
loaded_mods_table(#loaded_mod{mod=Mod,current_size=CS,old_size=OS}) ->
850
 
    tr([td(href(["loaded_mod_details?mod=",Mod],Mod)),
851
 
        td("ALIGN=right",CS),
852
 
        td("ALIGN=right",OS)]).
853
 
    
854
695
 
855
696
%%%-----------------------------------------------------------------
856
697
%%% Print detailed information about one module
880
721
    
881
722
 
882
723
%%%-----------------------------------------------------------------
883
 
%%% Print table of funs
884
 
funs(Funs,TW) ->
885
 
    Heading = "Fun Information",
886
 
    header(Heading,body(funs_body(Heading,Funs,TW))).
887
 
    
888
 
funs_body(Heading,[],TW) ->
889
 
    [h1(Heading),
890
 
     warn(TW),
891
 
     "No Fun information was found\n"];
892
 
funs_body(Heading,Funs,TW) ->
893
 
    [heading(Heading,"funs"),
894
 
     warn(TW),
895
 
     table(
896
 
       "BORDER=4 CELLPADDING=4",
897
 
       [tr(
898
 
          [th("Module"),
899
 
           th("Uniq"),
900
 
           th("Index"),
901
 
           th("Address"),
902
 
           th("Native_address"),
903
 
           th("Refc")]) |
904
 
        lists:map(fun(Fun) -> funs_table(Fun) end, Funs)])].
905
 
 
906
 
funs_table(Fu) ->
907
 
    #fu{module=Module,uniq=Uniq,index=Index,address=Address,
908
 
        native_address=NativeAddress,refc=Refc}=Fu,
909
 
    tr(
910
 
      [td(Module),
911
 
       td("ALIGN=right",Uniq),
912
 
       td("ALIGN=right",Index),
913
 
       td(Address),
914
 
       td(NativeAddress),
915
 
       td("ALIGN=right",Refc)]).
916
 
    
917
 
%%%-----------------------------------------------------------------
918
724
%%% Print atoms
919
 
atoms(Atoms,Num,TW) ->
 
725
atoms(SessionId,TW,Num,FirstChunk) ->
920
726
    Heading = "Atoms",
921
 
    header(Heading,body(atoms_body(Heading,Atoms,Num,TW))).
922
 
 
923
 
atoms_body(Heading,[],Num,TW) ->
924
 
    [h1(Heading),
925
 
     warn(TW),
926
 
     "No atoms were found in log",br(),
927
 
     "Total number of atoms in node was ", Num, br()];    
928
 
atoms_body(Heading,Atoms,Num,TW) ->
929
 
    [heading(Heading,"atoms"),
930
 
     warn(TW),
931
 
     "Total number of atoms in node was ", Num, 
932
 
     br(),
933
 
     "The last created atom is shown first",
934
 
     br(),br() |
935
 
     n_first(Atoms)].
936
 
 
937
 
n_first({n_lines,Start,N,What,Lines,Pos}) ->
938
 
    NextHref = next_href(N,What,Pos,Start),
939
 
    [What," number ",integer_to_list(Start),"-",integer_to_list(Start+N-1),
940
 
     br(),
941
 
     NextHref, 
942
 
     pre(Lines),
943
 
     NextHref];
944
 
n_first({n_lines,_Start,_N,_What,Lines}) ->
945
 
    [pre(Lines)].
946
 
 
947
 
%%%-----------------------------------------------------------------
948
 
%%% Print next N lines of "something"
949
 
next(NLines,TW) ->
950
 
    header(element(4,NLines),body(next_body(NLines,TW))).
951
 
 
952
 
next_body({n_lines,Start,N,What,Lines,Pos},TW) ->
953
 
    PrefHref = prev_href(),
954
 
    NextHref = next_href(N,What,Pos,Start),
955
 
    [warn(TW),
956
 
     What," number ",integer_to_list(Start),"-",integer_to_list(Start+N-1),
957
 
     br(),
958
 
     PrefHref,
959
 
     ?space,
960
 
     NextHref, 
961
 
     pre(Lines),
962
 
     PrefHref,
963
 
     ?space,
964
 
     NextHref];
965
 
next_body({n_lines,Start,N,What,Lines},TW) ->
966
 
    PrefHref = prev_href(),
967
 
    [warn(TW),
968
 
     What," number ",integer_to_list(Start),"-",integer_to_list(Start+N-1),
969
 
     br(),
970
 
     PrefHref,
971
 
     pre(Lines),
972
 
     PrefHref].
973
 
    
974
 
 
975
 
prev_href() ->
976
 
    href("javascript:history.back()",["Previous"]).
977
 
 
978
 
next_href(N,What,Pos,Start) ->
979
 
    href(["./next?pos=",integer_to_list(Pos),
980
 
          "&num=",integer_to_list(N),
981
 
          "&start=",integer_to_list(Start+N),
982
 
          "&what=",What],
983
 
         "Next").
 
727
    case FirstChunk of
 
728
        done ->
 
729
            deliver_first(SessionId,[start_html_page(Heading),
 
730
                                     h1(Heading),
 
731
                                     warn(TW),
 
732
                                     "No atoms were found in log",br(),
 
733
                                     "Total number of atoms in node was ", Num, 
 
734
                                     br()]);
 
735
        _ ->
 
736
            deliver_first(SessionId,[start_html_page(Heading),
 
737
                                     heading(Heading,"atoms"),
 
738
                                     warn(TW),
 
739
                                     "Total number of atoms in node was ", Num, 
 
740
                                     br(),
 
741
                                     "The last created atom is shown first",
 
742
                                     br(),
 
743
                                     start_pre()]),
 
744
            atoms_chunk(SessionId,FirstChunk)
 
745
    end.
 
746
            
 
747
atoms_chunk(SessionId,done) ->
 
748
    deliver(SessionId,[stop_pre(),stop_html_page()]);
 
749
atoms_chunk(SessionId,Atoms) ->
 
750
    deliver(SessionId,Atoms).
984
751
 
985
752
%%%-----------------------------------------------------------------
986
753
%%% Print memory information
1118
885
           th("Size"),
1119
886
           th("Limit"),
1120
887
           th("Used"),
1121
 
           th("Rate")]) |
 
888
           th("Rate"),
 
889
           th("Entries")]) |
1122
890
        lists:map(fun(IndexTable) -> index_tables_table(IndexTable) end,
1123
891
                  IndexTables)])].
1124
892
 
1125
893
index_tables_table(IndexTable) ->
1126
 
    #index_table{name=Name,size=Size,limit=Limit,used=Used,rate=Rate} = 
1127
 
        IndexTable,
 
894
    #index_table{name=Name,size=Size,limit=Limit,used=Used,
 
895
                 rate=Rate,entries=Entries} = IndexTable,
1128
896
    tr(
1129
897
      [td(Name),
1130
898
       td("ALIGN=right",Size),
1131
899
       td("ALIGN=right",Limit),
1132
900
       td("ALIGN=right",Used),
1133
 
       td("ALIGN=right",Rate)]).
 
901
       td("ALIGN=right",Rate),
 
902
       td("ALIGN=right",Entries)]).
1134
903
 
1135
904
%%%-----------------------------------------------------------------
1136
905
%%% Internal library
 
906
start_html_page(Title) ->
 
907
    [only_http_header(),
 
908
     start_html(),
 
909
     only_html_header(Title),
 
910
     start_html_body()].
 
911
 
 
912
stop_html_page() ->
 
913
    [stop_html_body(),
 
914
     stop_html()].
 
915
 
 
916
only_http_header() ->
 
917
    ["Pragma:no-cache\r\n",
 
918
     "Content-type: text/html\r\n\r\n"].
 
919
 
 
920
only_html_header(Title) -> 
 
921
    only_html_header(Title,"").
 
922
only_html_header(Title,JavaScript) ->    
 
923
    ["<HEAD>\n",
 
924
     "<TITLE>", Title,  "</TITLE>\n",
 
925
     JavaScript,
 
926
     "</HEAD>\n"].
 
927
 
 
928
start_html() ->
 
929
    "<HTML>\n".
 
930
stop_html() ->
 
931
    "</HTML>".
 
932
start_html_body() ->
 
933
    "<BODY BGCOLOR=\"#FFFFFF\">\n".
 
934
stop_html_body() ->
 
935
    "</BODY>\n".
 
936
 
1137
937
header(Body) ->
1138
938
    header("","",Body).
1139
939
header(Title,Body) ->
1140
940
    header(Title,"",Body).
1141
941
header(Title,JavaScript,Body) ->
1142
 
    ["Pragma:no-cache\r\n",
1143
 
     "Content-type: text/html\r\n\r\n",
 
942
    [only_http_header(),
1144
943
     html_header(Title,JavaScript,Body)].
1145
944
 
1146
945
html_header(Title,JavaScript,Body) ->    
1147
 
    ["<HTML>\n",
1148
 
     "<HEAD>\n",
1149
 
     "<TITLE>", Title,  "</TITLE>\n",
1150
 
     JavaScript,
1151
 
     "</HEAD>\n",
 
946
    [start_html(),
 
947
     only_html_header(Title,JavaScript),
1152
948
     Body,
1153
 
     "</HTML>"].
 
949
     stop_html()].
1154
950
 
1155
951
body(Text) ->
1156
 
    ["<BODY BGCOLOR=\"#FFFFFF\">\n",
 
952
    [start_html_body(),
1157
953
     Text,
1158
 
     "<\BODY>\n"].
 
954
     stop_html_body()].
1159
955
 
1160
956
frameset(Args,Frames) ->
1161
957
    ["<FRAMESET ",Args,">\n", Frames, "\n</FRAMESET>\n"].
1162
958
frame(Args) ->
1163
959
    ["<FRAME ",Args, ">\n"].
1164
960
 
 
961
start_visible_table() ->
 
962
    start_table("BORDER=\"4\" CELLPADDING=\"4\"").
 
963
start_visible_table(ColTitles) ->
 
964
    [start_visible_table(),
 
965
     tr([th(ColTitle) || ColTitle <- ColTitles])].
 
966
 
 
967
start_table(Args) ->
 
968
    ["<TABLE ", Args, ">\n"].
 
969
stop_table() ->
 
970
    "</TABLE>\n".
 
971
 
1165
972
table(Args,Text) ->
1166
 
    ["<TABLE ", Args, ">\n", Text, "\n</TABLE>\n"].
 
973
    [start_table(Args), Text, stop_table()].
1167
974
tr(Text) ->
1168
975
    ["<TR>\n", Text, "\n</TR>\n"].
1169
976
tr(Args,Text) ->
1181
988
    ["<B>",Text,"</B>"].
1182
989
em(Text) ->    
1183
990
    ["<EM>",Text,"</EM>\n"].
 
991
start_pre() ->
 
992
    "<PRE>".
 
993
stop_pre() ->
 
994
    "</PRE>".
1184
995
pre(Text) ->
1185
 
    ["<PRE>",Text,"</PRE>"].
 
996
    [start_pre(),Text,stop_pre()].
1186
997
href(Link,Text) ->
1187
998
    ["<A HREF=\"",Link,"\">",Text,"</A>"].
1188
999
href(Args,Link,Text) ->
1197
1008
    ["<INPUT ", Args, ">\n"].
1198
1009
h1(Text) ->
1199
1010
    ["<H1>",Text,"</H1>\n"].
1200
 
h2(Text) ->
1201
 
    ["<H2>",Text,"</H2>\n"].
1202
1011
font(Args,Text) ->
1203
1012
    ["<FONT ",Args,">\n",Text,"\n</FONT>\n"].
1204
1013
p(Text) ->    
1221
1030
href_proc_port([$#,$P,$o,$r,$t,$<|T],Acc) ->
1222
1031
    {[$#|Port]=HashPort,Rest} = to_gt(T,[$;,$t,$l,$&,$t,$r,$o,$P,$#]),
1223
1032
    href_proc_port(Rest,[href("TARGET=\"main\"",
1224
 
                              ["./ports?port=",Port],HashPort)|Acc]);
 
1033
                              ["./port?port=",Port],HashPort)|Acc]);
1225
1034
href_proc_port([$<,$<|T],Acc) ->
1226
1035
    %% No links to binaries
1227
1036
    href_proc_port(T,[$;,$t,$l,$&,$;,$t,$l,$&|Acc]);
1241
1050
    %% Port written by crashdump_viewer:parse_term(...)
1242
1051
    {[$#|Port]=HashPort,[$"|Rest]} = to_gt(T,[$;,$t,$l,$&,$t,$r,$o,$P,$#]),
1243
1052
    href_proc_port(Rest,[href("TARGET=\"main\"",
1244
 
                              ["./ports?port=",Port],HashPort)|Acc]);
 
1053
                              ["./port?port=",Port],HashPort)|Acc]);
1245
1054
href_proc_port([$",$#,$C,$D,$V,$P,$i,$d,$<|T],Acc) ->
1246
1055
    %% Pid written by crashdump_viewer:parse_term(...)
1247
1056
    {Pid,[$"|Rest]} = to_gt(T,[$;,$t,$l,$&]),
1420
1229
            "&lt;" ++ _Pid -> 
1421
1230
                href("TARGET=\"main\"",["./proc_details?pid=",H],H);
1422
1231
            "#Port&lt;" ++ Port -> 
1423
 
                href("TARGET=\"main\"",["./ports?port=","Port&lt;"++Port],H);
 
1232
                href("TARGET=\"main\"",["./port?port=","Port&lt;"++Port],H);
1424
1233
            "#" ++ _other -> 
1425
1234
                H
1426
1235
        end,
1429
1238
    replace_insrt(T,Insrt,[H|Acc]);
1430
1239
replace_insrt([],[],Acc) ->
1431
1240
    Acc.
 
1241
 
 
1242
%%%-----------------------------------------------------------------
 
1243
%%% Create a page with one table by delivering chunk by chunk to
 
1244
%%% inets. crashdump_viewer first calls chunk_page/5 once, then
 
1245
%%% chunk/3 multiple times until all data is delivered.
 
1246
chunk_page(processes,SessionId,TW,{Sorted,SharedHeap},FirstChunk) ->
 
1247
    Columns = procs_summary_table_head(Sorted,SharedHeap),
 
1248
    chunk_page(SessionId, "Process Information", TW, FirstChunk,
 
1249
               "processes", Columns, fun procs_summary_table/1);
 
1250
chunk_page(ports,SessionId,TW,_,FirstChunk) ->
 
1251
    chunk_page(SessionId, "Port Information", TW, FirstChunk,
 
1252
               "ports", port_table_head(), fun ports_table/1);
 
1253
chunk_page(ets_tables,SessionId,TW,Heading,FirstChunk) ->
 
1254
    Columns = ["Owner",
 
1255
               "Slot",
 
1256
               "Id",
 
1257
               "Name",
 
1258
               "Type",
 
1259
               "Buckets",
 
1260
               "Objects",
 
1261
               "Memory (bytes)"],
 
1262
    chunk_page(SessionId, Heading, TW, FirstChunk,
 
1263
               "ets_tables", Columns, fun ets_tables_table/1);
 
1264
chunk_page(timers,SessionId,TW,Heading,FirstChunk) ->
 
1265
    chunk_page(SessionId, Heading, TW, FirstChunk, "timers",
 
1266
               ["Owner","Message","Time left"], fun timers_table/1);
 
1267
chunk_page(loaded_mods,SessionId,TW,{CC,OC},FirstChunk) ->
 
1268
    TotalsInfo = p([b("Current code: "),CC," bytes",br(),
 
1269
                    b("Old code: "),OC," bytes"]),
 
1270
    Columns = ["Module","Current size (bytes)","Old size (bytes)"],
 
1271
    chunk_page(SessionId, "Loaded Modules Information", TW, FirstChunk,
 
1272
               "loaded_modules", TotalsInfo,Columns, fun loaded_mods_table/1);
 
1273
chunk_page(funs,SessionId, TW, _, FirstChunk) ->
 
1274
    Columns = ["Module",
 
1275
               "Uniq",
 
1276
               "Index",
 
1277
               "Address",
 
1278
               "Native_address",
 
1279
               "Refc"],
 
1280
    chunk_page(SessionId, "Fun Information", TW, FirstChunk,
 
1281
               "funs", Columns, fun funs_table/1).
 
1282
 
 
1283
chunk_page(SessionId,Heading,TW,FirstChunk,Type,TableColumns,TableFun) ->
 
1284
    chunk_page(SessionId,Heading,TW,FirstChunk,Type,[],TableColumns,TableFun).
 
1285
chunk_page(SessionId,Heading,TW,done,Type,_TotalsInfo,_TableColumns,_TableFun) ->
 
1286
    no_info_found(SessionId,Heading,TW,Type);
 
1287
chunk_page(SessionId,Heading,TW,FirstChunk,Type,TotalsInfo,TableColumns,TableFun) ->
 
1288
    deliver_first(SessionId,[start_html_page(Heading),
 
1289
                             heading(Heading,Type),
 
1290
                             warn(TW),
 
1291
                             TotalsInfo,
 
1292
                             start_visible_table(TableColumns)]),
 
1293
    chunk(SessionId,FirstChunk,TableFun),
 
1294
    TableFun.
 
1295
 
 
1296
no_info_found(SessionId, Heading, TW, Type) ->
 
1297
    Info = ["No ", Type, " were found\n"],
 
1298
    deliver_first(SessionId,[start_html_page(Heading),
 
1299
                             h1(Heading),
 
1300
                             warn(TW),
 
1301
                             Info,
 
1302
                             stop_html_page()]).
 
1303
 
 
1304
chunk(SessionId, done, _TableFun) ->
 
1305
    deliver(SessionId,[stop_table(),stop_html_page()]);
 
1306
chunk(SessionId, Items, TableFun) ->
 
1307
    deliver(SessionId, [lists:map(TableFun, Items),
 
1308
                        stop_table(), %! Will produce an empty table at the end
 
1309
                        start_visible_table()]). % of the page :(
 
1310
 
 
1311
%%%-----------------------------------------------------------------
 
1312
%%% Deliver part of a page to inets
 
1313
%%% The first part, which includes the HTTP header, must always be
 
1314
%%% delivered as a string (i.e. no binaries). The rest of the page is
 
1315
%%% better delivered as binaries in order to avoid data copying.
 
1316
deliver_first(SessionId,String) ->
 
1317
    mod_esi:deliver(SessionId,String).
 
1318
deliver(SessionId,IoList) ->
 
1319
    mod_esi:deliver(SessionId,[list_to_binary(IoList)]).
 
1320
 
 
1321
 
 
1322
%%%-----------------------------------------------------------------
 
1323
%%% Page specific stuff for chunk pages
 
1324
procs_summary_table_head(Sorted,SharedHeap) ->
 
1325
    MemHeading =
 
1326
        if SharedHeap ->
 
1327
                "Stack";
 
1328
           true ->
 
1329
                "Stack+heap"
 
1330
        end,
 
1331
    [procs_summary_table_head("pid","Pid",Sorted),
 
1332
     procs_summary_table_head("name_func","Name/Spawned as",Sorted),
 
1333
     procs_summary_table_head("state","State",Sorted),
 
1334
     procs_summary_table_head("reds","Reductions",Sorted),
 
1335
     procs_summary_table_head("mem",MemHeading,Sorted),
 
1336
     procs_summary_table_head("msg_q_len","MsgQ Length",Sorted)].
 
1337
 
 
1338
procs_summary_table_head(_,Text,no_sort) ->
 
1339
    Text;
 
1340
procs_summary_table_head(Sorted,Text,Sorted) ->
 
1341
    %% Mark the sorted column (bigger and italic)
 
1342
    font("SIZE=\"+1\"",em(href("./sort_procs?sort="++Sorted,Text)));
 
1343
procs_summary_table_head(SortOn,Text,_Sorted) ->
 
1344
    href("./sort_procs?sort="++SortOn,Text).
 
1345
 
 
1346
procs_summary_table(Proc) ->
 
1347
    #proc{pid=Pid,name=Name,state=State,
 
1348
          reds=Reds,stack_heap=Mem0,msg_q_len=MsgQLen}=Proc,
 
1349
    Mem = case Mem0 of
 
1350
              -1 -> "unknown";
 
1351
              _ -> integer_to_list(Mem0)
 
1352
          end,
 
1353
    tr(
 
1354
      [td(href(["./proc_details?pid=",Pid],Pid)),
 
1355
       td(Name),
 
1356
       td(State),
 
1357
       td("ALIGN=right",integer_to_list(Reds)),
 
1358
       td("ALIGN=right",Mem),
 
1359
       td("ALIGN=right",integer_to_list(MsgQLen))]).
 
1360
 
 
1361
port_table_head() ->
 
1362
    ["Id","Slot","Connected","Links","Name","Monitors","Controls"].
 
1363
 
 
1364
ports_table(Port) ->
 
1365
    #port{id=Id,slot=Slot,connected=Connected,links=Links,name=Name,
 
1366
          monitors=Monitors,controls=Controls}=Port,
 
1367
    tr(
 
1368
      [td(Id),
 
1369
       td("ALIGN=right",Slot),
 
1370
       td(href_proc_port(Connected)),
 
1371
       td(href_proc_port(Links)),
 
1372
       td(Name),
 
1373
       td(href_proc_port(Monitors)),
 
1374
       td(Controls)]).
 
1375
 
 
1376
ets_tables_table(EtsTable) ->
 
1377
    #ets_table{pid=Pid,slot=Slot,id=Id,name=Name,type=Type,
 
1378
               buckets=Buckets,size=Size,memory=Memory} = EtsTable,
 
1379
    tr(
 
1380
      [td(href_proc_port(Pid)),
 
1381
       td(Slot),
 
1382
       td(Id),
 
1383
       td(Name),
 
1384
       td(Type),
 
1385
       td("ALIGN=right",Buckets),
 
1386
       td("ALIGN=right",Size),
 
1387
       td("ALIGN=right",Memory)]).
 
1388
 
 
1389
timers_table(Timer) ->
 
1390
    #timer{pid=Pid,msg=Msg,time=Time}=Timer,
 
1391
    tr(
 
1392
      [td(href_proc_port(Pid)),
 
1393
       td(Msg),
 
1394
       td("ALIGN=right",Time)]).
 
1395
 
 
1396
loaded_mods_table(#loaded_mod{mod=Mod,current_size=CS,old_size=OS}) ->
 
1397
    tr([td(href(["loaded_mod_details?mod=",Mod],Mod)),
 
1398
        td("ALIGN=right",CS),
 
1399
        td("ALIGN=right",OS)]).
 
1400
 
 
1401
funs_table(Fu) ->
 
1402
    #fu{module=Module,uniq=Uniq,index=Index,address=Address,
 
1403
        native_address=NativeAddress,refc=Refc}=Fu,
 
1404
    tr(
 
1405
      [td(Module),
 
1406
       td("ALIGN=right",Uniq),
 
1407
       td("ALIGN=right",Index),
 
1408
       td(Address),
 
1409
       td(NativeAddress),
 
1410
       td("ALIGN=right",Refc)]).