~ubuntu-branches/debian/squeeze/erlang/squeeze

« back to all changes in this revision

Viewing changes to lib/appmon/src/appmon.erl

  • Committer: Bazaar Package Importer
  • Author(s): Erlang Packagers, Sergei Golovan
  • Date: 2006-12-03 17:07:44 UTC
  • mfrom: (2.1.11 feisty)
  • Revision ID: james.westby@ubuntu.com-20061203170744-rghjwupacqlzs6kv
Tags: 1:11.b.2-4
[ Sergei Golovan ]
Fixed erlang-base and erlang-base-hipe prerm scripts.

Show diffs side-by-side

added added

removed removed

Lines of Context:
18
18
-module(appmon).
19
19
-behaviour(gen_server).
20
20
 
21
 
%%%----------------------------------------------------------------------
 
21
%%%---------------------------------------------------------------------
22
22
%%% Appmon main module.
23
23
%%% Creates the main window and receives load and application
24
24
%%% information from all connected nodes.
25
 
%%%----------------------------------------------------------------------
 
25
%%%---------------------------------------------------------------------
26
26
 
27
27
%% External exports
28
28
-export([start/0, stop/0]).
38
38
-record(options, {single, many, time, queue, prog, linear}).
39
39
 
40
40
%% Main window data
41
 
-record(win, {name,                             % atom() Monitored node name
 
41
-record(win, {name,                             % atom() Monitored node
42
42
              window,                           % gsobj()
43
43
              wwindow,                          % int() Window width
44
44
              hwindow,                          % int() Window height
46
46
              canvas,                           % gsobj()
47
47
              wcanvas,                          % int() Canvas width
48
48
              hcanvas,                          % int() Canvas height
49
 
              l1, l2,                           % gsobj() Lines on canvas
 
49
              l1, l2,                           % gsobj() Canvas lines
50
50
              leds,                             % [gsobj()] Load meter
51
51
              nodelabel,                        % {gsobj(),gsobj()}
52
 
              appobjs=[],                       % [gsobj()] App. buttons etc.
 
52
              appobjs=[],                       % [gsobj()] Buttons etc.
53
53
              nodemenu}).                       % gsobj() Node menu
54
54
 
55
55
%% Node data
56
 
-record(mnode, {name,                           % atom() Monitored node name
 
56
-record(mnode, {name,                           % atom() Node name
57
57
                status,                         % alive | dead
58
58
                pid,                            % pid()
59
59
                apps,                           % [{Pid,App,Descr}]
68
68
                lbpid,                          % pid()
69
69
                mnodes=[]}).                    % [#mnode{}] 
70
70
 
71
 
%%%----------------------------------------------------------------------
 
71
%%%---------------------------------------------------------------------
72
72
%%% External exports
73
 
%%%----------------------------------------------------------------------
 
73
%%%---------------------------------------------------------------------
74
74
 
75
75
start() ->
76
76
     gen_server:start({local, appmon}, ?MODULE, [], []).
79
79
    gen_server:cast(appmon, stop).
80
80
 
81
81
 
82
 
%%%----------------------------------------------------------------------
 
82
%%%---------------------------------------------------------------------
83
83
%%% gen_server callbacks
84
 
%%%----------------------------------------------------------------------
 
84
%%%---------------------------------------------------------------------
85
85
 
86
86
%%----------------------------------------------------------------------
87
87
%% Func: init/1
98
98
    
99
99
    LbPid = appmon_lb:start(self ()),
100
100
 
 
101
    %% Check which remote nodes have appmon code available (OTP-4887)
 
102
    NodesOk = lists:filter(fun(Node) -> check_node(Node) end, nodes()),
 
103
    Nodes = [node()|NodesOk],
 
104
 
101
105
    %% Start monitoring the existing nodes
102
 
    MNodes = mk_mnodes([node()|nodes()], LbPid),
 
106
    MNodes = mk_mnodes(Nodes, LbPid),
103
107
 
104
108
    %% Draw the main window
105
109
    GS = gs:start([{kernel,true}]),
109
113
    lists:foreach(fun(Node) ->
110
114
                          display_addnode(GUI, Node)
111
115
                  end,
112
 
                  [node()|nodes()]),
 
116
                  Nodes),
113
117
 
114
118
    %% Mark the default options as selected in the Options menu
115
119
    display_setopt(GUI, single),
120
124
                window_mode=single, load_mode1=time, load_mode2=prog,
121
125
                lbpid=LbPid, mnodes=MNodes}}.
122
126
 
 
127
check_node(Node) ->
 
128
    case rpc:call(Node, code, which, [appmon]) of
 
129
        File when is_list(File) ->
 
130
            true;
 
131
        _ -> % non_existing (| cover_compiled)
 
132
            false
 
133
    end.
 
134
 
123
135
%%----------------------------------------------------------------------
124
136
%% Func: handle_call/3
125
137
%% Returns: {reply, Reply, State}          |
129
141
%%          {stop, Reason, Reply, State}   | (terminate/2 is called)
130
142
%%          {stop, Reason, State}            (terminate/2 is called)
131
143
%%----------------------------------------------------------------------
132
 
handle_call(norequest, From, State) ->
 
144
handle_call(norequest, _From, State) ->
133
145
    {reply, null, State}.
134
146
 
135
147
%%----------------------------------------------------------------------
148
160
%%          {stop, Reason, State}            (terminate/2 is called)
149
161
%%----------------------------------------------------------------------
150
162
%% Load information from a node
151
 
handle_info({delivery, Serv, load, Node, Load}, State) ->
 
163
handle_info({delivery, _Serv, load, Node, Load}, State) ->
152
164
    
153
165
    %% Update node information
154
166
    MNode = get_mnode(Node, State#state.mnodes),
166
178
    {noreply, State#state{mnodes=MNodes}};
167
179
 
168
180
%% Application information from a node
169
 
handle_info({delivery, Serv, app_ctrl, Node, Apps}, State) ->
 
181
handle_info({delivery, _Serv, app_ctrl, Node, Apps}, State) ->
170
182
    
171
183
    %% Update node information
172
184
    MNode = get_mnode(Node, State#state.mnodes),
190
202
 
191
203
    %% First, make sure appmon code is available at remode node,
192
204
    %% or the node should be ignored (OTP-3591)
193
 
    case rpc:call(Node, code, which, [appmon]) of
194
 
        File when is_list(File) ->
 
205
    case check_node(Node) of
 
206
        true ->
195
207
 
196
208
            %% If this is a previously unknown node, update window's
197
209
            %% 'Nodes' menu
218
230
            appmon_lb:update_status(State#state.lbpid, Node, alive),
219
231
            {noreply, State#state{mnodes=MNodes}};
220
232
 
221
 
        _Other -> % non_existing (| cover_compiled)
 
233
        false ->
222
234
            {noreply, State}
223
235
    end;
224
236
 
305
317
                        ping ->
306
318
                            %% Ignore - makes no sense to ping yourself
307
319
                            ignore;
308
 
                        Other -> % reboot | restart | stop
 
320
                        _ -> % reboot | restart | stop
309
321
                            apply(init, Action, [])
310
322
                    end;
311
323
 
313
325
                    case Action of
314
326
                        ping ->
315
327
                            net_adm:ping(Node);
316
 
                        Other -> % reboot | restart | stop
 
328
                        _ -> % reboot | restart | stop
317
329
                            rpc:cast(Node, init, Action, [])
318
330
                    end
319
331
            end,
374
386
                    case State#state.window_mode of
375
387
 
376
388
                        single ->
377
 
                            {ok, GUI} = get_win2(WinObj, State#state.wins),
 
389
                            {ok, GUI} =
 
390
                                get_win2(WinObj, State#state.wins),
378
391
                                    
379
 
                            %% Clear the window and correct the node name
 
392
                            %% Clear window and correct the node name
380
393
                            draw_clear(GUI),
381
394
                            GUI1 = draw_nodename(GUI, Node),
382
395
 
383
 
                            %% Update the window with the correct node name
 
396
                            %% Update window with the correct node name
384
397
                            %% and the applications running at the node
385
398
                            MNode = get_mnode(Node, State#state.mnodes),
386
399
                            GUI2 = case MNode#mnode.status of
389
402
                                           GUI1;
390
403
                                       alive ->
391
404
                                           display_nodeup(GUI1, Node),
392
 
                                           draw_apps(GUI1, MNode#mnode.apps)
 
405
                                           draw_apps(GUI1,
 
406
                                                     MNode#mnode.apps)
393
407
                                   end,
394
408
                            Wins = replace_win(GUI#win.name, GUI2,
395
409
                                               State#state.wins),
399
413
                        many ->
400
414
                            GUI = draw_win(State#state.gs, Node),
401
415
 
402
 
                            %% Update the Nodes menu with all known nodes -
403
 
                            %% use the MNodes to get them in the right order
 
416
                            %% Update Nodes menu with all known nodes -
 
417
                            %% use MNodes to get them in the right order
404
418
                            lists:foreach(fun(MNode) ->
405
 
                                                  Name = MNode#mnode.name,
406
 
                                                  display_addnode(GUI, Name)
 
419
                                                  Name =
 
420
                                                      MNode#mnode.name,
 
421
                                                  display_addnode(GUI,
 
422
                                                                  Name)
407
423
                                          end,
408
424
                                          State#state.mnodes),
409
425
 
410
 
                            %% Mark the selected options in the Options menu
 
426
                            %% Mark selected options in the Options menu
411
427
                            display_setopt(GUI, many),
412
428
                            display_setopt(GUI, State#state.load_mode1),
413
429
                            display_setopt(GUI, State#state.load_mode2),
421
437
                                           GUI;
422
438
                                       alive ->
423
439
                                           display_nodeup(GUI, Node),
424
 
                                           draw_apps(GUI, MNode#mnode.apps)
 
440
                                           draw_apps(GUI,
 
441
                                                     MNode#mnode.apps)
425
442
                                   end,
426
443
                            Wins = [GUI1|State#state.wins],
427
444
                            
431
448
 
432
449
        %% Help menu = Help button
433
450
        help ->
434
 
            HelpFile = filename:join(code:priv_dir(appmon),
435
 
                                     "../doc/index.html"),
436
 
            tool_utils:open_help(State#state.gs, HelpFile),
 
451
            HelpFile = filename:join([code:lib_dir(appmon),
 
452
                                     "doc", "html", "part_frame.html"]),
 
453
            case State#state.wins of
 
454
                [Win] ->
 
455
                    tool_utils:open_help(Win#win.window, HelpFile);
 
456
                _ ->
 
457
                    tool_utils:open_help(State#state.gs, HelpFile)
 
458
            end,
437
459
            {noreply, State};
438
460
                
439
 
        Other ->
 
461
        _Other ->
440
462
            {noreply, State}
441
463
    end;
442
 
handle_info({gs, WinObj, configure, _Data, [WWindow, HWindow|_]}, State) ->
 
464
handle_info({gs, WinObj, configure, _, [WWindow, HWindow|_]}, State) ->
443
465
    {ok, GUI} = get_win2(WinObj, State#state.wins),
444
466
    GUI1 = draw_resize(GUI, WWindow, HWindow),
445
467
    display_scrollbar(GUI1),
474
496
                    {noreply, State}
475
497
            end
476
498
    end;
477
 
handle_info(Info, State) ->
 
499
handle_info(_Info, State) ->
478
500
    {noreply, State}.
479
501
        
480
502
%%----------------------------------------------------------------------
482
504
%% Purpose: Shutdown the server
483
505
%% Returns: any (ignored by gen_server)
484
506
%%----------------------------------------------------------------------
485
 
terminate(A1, State) ->
 
507
terminate(_Reason, State) ->
486
508
    bcast(State#state.mnodes, {kill}),
487
509
    appmon_lb:stop(State#state.lbpid),
488
510
    ok.
492
514
%% Purpose: Convert process state when code is changed
493
515
%% Returns: {ok, NewState}
494
516
%%----------------------------------------------------------------------
495
 
code_change(OldVsn, State, Extra) ->
 
517
code_change(_OldVsn, State, _Extra) ->
496
518
    {ok, State}.
497
519
    
498
520
 
499
 
%%%----------------------------------------------------------------------
 
521
%%%---------------------------------------------------------------------
500
522
%%% Internal functions
501
 
%%%----------------------------------------------------------------------
 
523
%%%---------------------------------------------------------------------
502
524
 
503
525
%%----------------------------------------------------------------------
504
526
%% MNode manipulating functions
540
562
%%   Node -> atom()
541
563
%%   MNode -> #mnode{}
542
564
%%   MNodes1 -> MNodes2 -> [#mnode{}]
543
 
%% Replaces, or adds if previously not included, the mnode with name Node
544
 
%% in MNodes1 with MNode.
 
565
%% Replaces, or adds if previously not included, the mnode with name
 
566
%% Node in MNodes1 with MNode.
545
567
replace_mnode(Node, MNode, [#mnode{name=Node} | MNodes]) ->
546
568
    [MNode | MNodes];
547
569
replace_mnode(Node, MNode, [MNode2 | MNodes]) ->
548
570
    [MNode2 | replace_mnode(Node, MNode, MNodes)];
549
 
replace_mnode(Node, MNode, []) ->
 
571
replace_mnode(_Node, MNode, []) ->
550
572
    [MNode].
551
573
        
552
574
 
597
619
%%----------------------------------------------------------------------
598
620
%% GUI manipulating functions
599
621
%%----------------------------------------------------------------------
600
 
-define(PAD, 10).                               % Pad between objects
601
 
-define(PAD2, 4*?PAD).                          % Pad betw. node lbl and app
602
 
 
603
 
-define(hMENUBAR, 25).                          % Note: Hardwired in Tcl/Tk
604
 
 
605
 
-define(xNODELBL, 60).                          % Node label
 
622
-define(PAD, 10).                         % Pad between objects
 
623
-define(PAD2, 4*?PAD).                    % Pad betw. node lbl and app
 
624
 
 
625
-define(hMENUBAR, 25).                    % Note: Hardwired in Tcl/Tk
 
626
 
 
627
-define(xNODELBL, 60).                    % Node label
606
628
-define(yNODELBL, 35).
607
629
-define(hNODELBL, 20).
608
630
 
609
 
-define(xMETER, 5).                             % Meter
 
631
-define(xMETER, 5).                       % Meter
610
632
-define(yMETER, ?yNODELBL).
611
633
-define(wMETER, 20).
612
634
-define(hMETER, ?hNODELBL + ?PAD + ?PAD2 + ?hBTN).
613
635
-define(LEDCOUNT, 16).
614
636
 
615
 
-define(xBTN, ?xNODELBL).                       % Application buttons
 
637
-define(xBTN, ?xNODELBL).                 % Application buttons
616
638
-define(yBTN, ?yNODELBL + ?hNODELBL + ?PAD + ?PAD2).
617
 
-define(wBTN, 70). % min width
 
639
-define(wBTN, 70).                        % min width
618
640
-define(hBTN, 20).
619
641
 
620
 
-define(wCANVAS, 470 + ?wMETER + 3*?PAD).       % Canvas
 
642
-define(wCANVAS, 470 + ?wMETER + 3*?PAD). % Canvas
621
643
-define(hCANVAS, ?yNODELBL + ?hNODELBL + ?PAD + ?PAD2 + ?hBTN + 2*?PAD).
622
644
 
623
 
-define(wWIN, ?wCANVAS).                        % Window
 
645
-define(wWIN, ?wCANVAS).                  % Window
624
646
-define(hWIN, ?hMENUBAR + ?hCANVAS).
625
647
 
626
648
%%--Main window---------------------------------------------------------
629
651
 
630
652
    %% Main window
631
653
    NodeStr = atom_to_list(Node),
632
 
    Win = gs:create(window, GS, [{title, "APPMON: Overview on " ++ NodeStr},
 
654
    Win = gs:create(window, GS, [{title,
 
655
                                  "APPMON: Overview on " ++ NodeStr},
633
656
                                 {width, ?wWIN}, {height, ?hWIN},
634
657
                                 {configure, true}]),
635
658
    Canvas = gs:create(canvas, Win, [{x, 0}, {y, ?hMENUBAR},
636
 
                                     {width, ?wCANVAS}, {height, ?hCANVAS}]),
637
 
    L1 = gs:create(line, Canvas, [{coords, [{0,?yNODELBL-?PAD},
638
 
                                            {?wCANVAS,?yNODELBL-?PAD}]}]),
639
 
    L2 = gs:create(line, Canvas, [{coords, [{0,?hCANVAS-?PAD},
640
 
                                            {?wCANVAS,?hCANVAS-?PAD}]}]),
 
659
                                     {width, ?wCANVAS},
 
660
                                     {height, ?hCANVAS}]),
 
661
    L1 = gs:create(line, Canvas, [{coords,
 
662
                                   [{0,?yNODELBL-?PAD},
 
663
                                    {?wCANVAS,?yNODELBL-?PAD}]}]),
 
664
    L2 = gs:create(line, Canvas, [{coords,
 
665
                                   [{0,?hCANVAS-?PAD},
 
666
                                    {?wCANVAS,?hCANVAS-?PAD}]}]),
641
667
    
642
668
    %% Standard buttons
643
669
    MenuBar = gs:create(menubar, Win, [{height, ?hMENUBAR}]),
644
670
 
645
 
    FileMenuBtn = gs:create(menubutton, MenuBar, [{label, {text,"File"}}]),
 
671
    FileMenuBtn = gs:create(menubutton, MenuBar,
 
672
                            [{label, {text,"File"}}]),
646
673
    FileMenu = gs:create(menu, FileMenuBtn, []),
647
674
    gs:create(menuitem, FileMenu, [{label, {text,"Show List Box..."}},
648
675
                                   {data, listbox}]),
652
679
    gs:create(menuitem, FileMenu, [{label, {text, "Exit"}},
653
680
                                   {data, exit}]),
654
681
 
655
 
    ActionMenuBtn = gs:create(menubutton,MenuBar,[{label,{text,"Actions"}}]),
 
682
    ActionMenuBtn = gs:create(menubutton, MenuBar,
 
683
                              [{label,{text,"Actions"}}]),
656
684
    ActionMenu = gs:create(menu, ActionMenuBtn, []),
657
685
    gs:create(menuitem, ActionMenu, [{label, {text,"Reboot"}},
658
686
                                     {data, {action, reboot, Win}}]),
663
691
    gs:create(menuitem, ActionMenu, [{label, {text,"Ping"}},
664
692
                                     {data, {action, ping, Win}}]),
665
693
 
666
 
    OptMenuBtn = gs:create(menubutton, MenuBar, [{label, {text,"Options"}}]),
 
694
    OptMenuBtn = gs:create(menubutton, MenuBar,
 
695
                           [{label, {text,"Options"}}]),
667
696
    OptMenu = gs:create(menu, OptMenuBtn, []),
668
697
    G0 = now(), % Group identity unique per window!
669
698
    SMI = gs:create(menuitem, OptMenu, [{label, {text,"One window"}},
676
705
    G1 = now(),
677
706
    TMI = gs:create(menuitem, OptMenu, [{label, {text,"Load: time"}},
678
707
                                        {itemtype, radio}, {group, G1},
679
 
                                        {data, {option, time,
680
 
                                                [{load_method,time}]}}]),
 
708
                                        {data,
 
709
                                         {option, time,
 
710
                                          [{load_method,time}]}}]),
681
711
    QMI = gs:create(menuitem, OptMenu, [{label, {text,"Load: queue"}},
682
712
                                        {itemtype, radio}, {group, G1},
683
 
                                        {data, {option, queue,
684
 
                                                [{load_method,queue}]}}]),
 
713
                                        {data,
 
714
                                         {option, queue,
 
715
                                          [{load_method,queue}]}}]),
685
716
    G2 = now(),
686
 
    PMI = gs:create(menuitem, OptMenu, [{label, {text,"Load: progressive"}},
687
 
                                        {itemtype, radio}, {group, G2},
688
 
                                        {data, {option, prog,
689
 
                                                [{load_scale,prog}]}}]),
 
717
    PMI = gs:create(menuitem, OptMenu,
 
718
                    [{label, {text,"Load: progressive"}},
 
719
                     {itemtype, radio}, {group, G2},
 
720
                     {data, {option, prog, [{load_scale,prog}]}}]),
690
721
    LMI = gs:create(menuitem, OptMenu, [{label, {text,"Load: linear"}},
691
722
                                        {itemtype, radio}, {group, G2},
692
 
                                        {data, {option, linear,
693
 
                                                [{load_scale,linear}]}}]),
 
723
                                        {data,
 
724
                                         {option, linear,
 
725
                                          [{load_scale,linear}]}}]),
694
726
 
695
 
    NodeMenuBtn = gs:create(menubutton, MenuBar, [{label, {text,"Nodes"}}]),
 
727
    NodeMenuBtn = gs:create(menubutton, MenuBar,
 
728
                            [{label, {text,"Nodes"}}]),
696
729
    NodeMenu = gs:create(menu, NodeMenuBtn, []),
697
730
 
698
 
    HelpMenuBtn = gs:create(menubutton, MenuBar, [{label, {text,"Help"}},
699
 
                                                  {side, right}]),
 
731
    HelpMenuBtn = gs:create(menubutton, MenuBar,
 
732
                            [{label, {text,"Help"}}, {side, right}]),
700
733
    HelpMenu = gs:create(menu, HelpMenuBtn, []),
701
 
    gs:create(menuitem, HelpMenu, [{label, {text,"Help"}}, {data, help}]),
 
734
    gs:create(menuitem, HelpMenu, [{label, {text,"Help"}},
 
735
                                   {data, help}]),
702
736
 
703
737
    %% Meter
704
738
    HLed = trunc((?hMETER)/(?LEDCOUNT)),
705
739
    Leds = draw_leds(?LEDCOUNT, Canvas, ?yMETER, HLed, []),
706
740
    leds_down(Leds, ?LEDCOUNT, 0),
707
 
    gs:create(text, Canvas, [{coords, [{?xMETER, ?yMETER+HLed*?LEDCOUNT}]},
 
741
    gs:create(text, Canvas, [{coords,
 
742
                              [{?xMETER, ?yMETER+HLed*?LEDCOUNT}]},
708
743
                             {anchor, nw},
709
744
                             {font, {screen,8}},
710
745
                             {text, "Load"}]),
720
755
 
721
756
    %% Node label
722
757
    WNodeLbl = 8*length(NodeStr)+10,
723
 
    NLRect = gs:create(rectangle, Canvas, [{coords, [{?xNODELBL,?yNODELBL},
724
 
                                                     {?xNODELBL+WNodeLbl,
725
 
                                                      ?yNODELBL+?hNODELBL}]},
726
 
                                           {fill, black}]),
 
758
    NLRect = gs:create(rectangle, Canvas,
 
759
                       [{coords, [{?xNODELBL,?yNODELBL},
 
760
                                  {?xNODELBL+WNodeLbl,
 
761
                                   ?yNODELBL+?hNODELBL}]},
 
762
                        {fill, black}]),
727
763
    Xc = ?xNODELBL + round(WNodeLbl/2),
728
764
    Yc = ?yNODELBL + round(?hNODELBL/2),
729
 
    NLText = gs:create(text, Canvas, [{text, NodeStr}, {fg, {250,235,215}},
730
 
                                      {coords, [{Xc,Yc}]}, {anchor, c}]),
 
765
    NLText = gs:create(text, Canvas, [{text, NodeStr},
 
766
                                      {fg, {250,235,215}},
 
767
                                      {coords, [{Xc,Yc}]},
 
768
                                      {anchor, c}]),
731
769
    NodeLbl = {NLRect, NLText},
732
770
    
733
771
    gs:config(Win, {map, true}),
739
777
         l1=L1, l2=L2, leds=Leds, nodelabel=NodeLbl, nodemenu=NodeMenu}.
740
778
 
741
779
draw_leds(N, Canvas, Y, HLed, Leds) when N>0 ->
742
 
    Top = ?yNODELBL + (?LEDCOUNT-N)*HLed,
743
780
    Led = gs:create(rectangle, Canvas,
744
 
                    [{coords, [{?xMETER,Y}, {?xMETER+?wMETER,Y+HLed}]}]),
 
781
                    [{coords,
 
782
                      [{?xMETER,Y}, {?xMETER+?wMETER,Y+HLed}]}]),
745
783
    draw_leds(N-1, Canvas, Y+HLed, HLed, [Led | Leds]);
746
784
draw_leds(0, _Canvas, _Y, _HLed, Leds) ->
747
785
    Leds.
754
792
%% Used when a changing the node to display
755
793
draw_nodename(GUI, Node) ->
756
794
    NodeStr = atom_to_list(Node),
757
 
    gs:config(GUI#win.window, {title, "APPMON: Overview on " ++ NodeStr}),
 
795
    gs:config(GUI#win.window,
 
796
              {title, "APPMON: Overview on " ++ NodeStr}),
758
797
    GUI#win{name=Node}.
759
798
 
760
799
%% Resize the canvas (when the window has been resized)
797
836
draw_apps(GUI, [App | Apps], X, Lx0, N, GSObjs) ->
798
837
 
799
838
    %% Some necessary data
800
 
    {Pid, AppName, _Descr} = App,
 
839
    {_Pid, AppName, _Descr} = App,
801
840
    Text = atom_to_list(AppName),
802
841
    Width = max(8*length(Text)+10, ?wBTN),
803
842
 
811
850
               0 ->
812
851
                   Ly1 = ?yNODELBL + ?hNODELBL +?PAD,
813
852
                   Ly2 = Ly1 + ?PAD2,
814
 
                   gs:create(line, GUI#win.canvas, [{coords, [{Lx, Ly1},
815
 
                                                              {Lx, Ly2}]}]);
 
853
                   gs:create(line, GUI#win.canvas,
 
854
                             [{coords, [{Lx, Ly1}, {Lx, Ly2}]}]);
816
855
               %% Nth application, N>1 - draw a horizontal line from
817
856
               %% line connecting to the previous application button,
818
857
               %% to above this application button, then vertically down
820
859
               _ ->
821
860
                   Ly1 = ?yNODELBL + ?hNODELBL + ?PAD + ?PAD2/2,
822
861
                   Ly2 = Ly1 + ?PAD2/2,
823
 
                   gs:create(line, GUI#win.canvas, [{coords, [{Lx0, Ly1},
824
 
                                                              {Lx, Ly1},
825
 
                                                              {Lx, Ly2}]}])
 
862
                   gs:create(line, GUI#win.canvas,
 
863
                             [{coords, [{Lx0, Ly1}, {Lx, Ly1},
 
864
                                        {Lx, Ly2}]}])
826
865
           end,
827
866
    
828
867
    %% The application is represented using a 'canvasbutton'
830
869
    AppBtn = canvasbutton(GUI#win.canvas, Text, X, ?yBTN, Width, ?hBTN,
831
870
                          Data),
832
871
 
833
 
    draw_apps(GUI, Apps, X+Width+?PAD, Lx, N+1, [AppBtn, Line | GSObjs]);
 
872
    draw_apps(GUI, Apps, X+Width+?PAD, Lx, N+1, [AppBtn, Line|GSObjs]);
834
873
draw_apps(_GUI, [], X, _N, _Lx0, GSObjs) ->
835
874
    {GSObjs, X}.
836
875
 
842
881
display_addnode([GUI|GUIs], Node) ->
843
882
    display_addnode(GUI, Node),
844
883
    display_addnode(GUIs, Node);
845
 
display_addnode([], Node) ->
 
884
display_addnode([], _Node) ->
846
885
    ignore;
847
886
display_addnode(GUI, Node) ->
848
887
    Txt = "Show " ++ atom_to_list(Node),
849
888
    gs:create(menuitem, GUI#win.nodemenu,
850
 
              [{label, {text,Txt}}, {data, {node, Node, GUI#win.window}}]).
 
889
              [{label, {text,Txt}},
 
890
               {data, {node, Node, GUI#win.window}}]).
851
891
 
852
892
%% Show that a node has come back up
853
893
display_nodeup(GUI, Node) ->
854
894
    {Rect, Text} = GUI#win.nodelabel,
855
895
 
856
896
    %% Check coordinates for the rectangle and compute the new width
857
 
    [{L, T}, {R, B}] = gs:read(Rect, coords),
 
897
    [{L, T}, {_R, B}] = gs:read(Rect, coords),
858
898
    NodeStr = atom_to_list(Node),
859
899
    W = 8*length(NodeStr)+10,
860
900
    
861
901
    gs:config(Rect, [{coords, [{L, T}, {L+W, B}]}, {fill, black}]),
862
902
    gs:config(Text, [{text, NodeStr}, {fg, {250,235,215}},
863
 
                     {coords, [{L+round(W/2), T+round((?hNODELBL)/2)}]}]).
 
903
                     {coords,
 
904
                      [{L+round(W/2), T+round((?hNODELBL)/2)}]}]).
864
905
 
865
906
%% Show that a node has gone down
866
907
display_nodedown(GUI) ->
867
908
    {Rect, Text} = GUI#win.nodelabel,
868
909
    
869
 
    [{L, T}, {R, B}] = gs:read(Rect, coords),
 
910
    [{L, T}, {_R, B}] = gs:read(Rect, coords),
870
911
    gs:config(Rect, [{coords, [{L, T}, {L+114, B}]}, {fill, gray}]),
871
912
    gs:config(Text, [{text, "No connection"}, {fg, black},
872
913
                     {coords, [{L+57, T+round((?hNODELBL)/2)}]}]).
880
921
    HCanvas = GUI#win.hcanvas,
881
922
    if
882
923
        WCanvas>WWindow ->
883
 
            gs:config(GUI#win.canvas,[{hscroll, bottom},
884
 
                                      {scrollregion,{0,0,WCanvas,HCanvas}}]);
 
924
            gs:config(GUI#win.canvas,
 
925
                      [{hscroll, bottom},
 
926
                       {scrollregion,{0,0,WCanvas,HCanvas}}]);
885
927
        true ->
886
928
            gs:config(GUI#win.canvas, [{hscroll, false}])
887
929
    end,
888
930
    if
889
931
        HCanvas>HWindow ->
890
 
            gs:config(GUI#win.canvas,[{vscroll, left},
891
 
                                      {scrollregion,{0,0,WCanvas,HCanvas}}]);
 
932
            gs:config(GUI#win.canvas,
 
933
                      [{vscroll, left},
 
934
                       {scrollregion,{0,0,WCanvas,HCanvas}}]);
892
935
                                        
893
936
        true ->
894
937
            gs:config(GUI#win.canvas, [{vscroll, false}])
924
967
            leds_up(GUI#win.leds, Old, New)
925
968
    end.
926
969
 
927
 
leds_down(Leds, Old, New) when Old == New -> 
 
970
leds_down(_Leds, Old, New) when Old == New -> 
928
971
    done;
929
972
leds_down(Leds, Old, New) when Old > New -> 
930
973
    reset_led(Leds, Old),
931
974
    leds_down(Leds, Old-1, New).
932
 
leds_up(Leds, Old, New) when Old == New -> 
 
975
leds_up(_Leds, Old, New) when Old == New -> 
933
976
    done;
934
977
leds_up(Leds, Old, New) when Old < New -> 
935
978
    set_led(Leds, Old),
937
980
 
938
981
led_on_col(N) when N > 13 -> ?highloadfg;
939
982
led_on_col(N) when N > 9 -> ?midloadfg;
940
 
led_on_col(N) -> ?lowloadfg.
 
983
led_on_col(_) -> ?lowloadfg.
941
984
 
942
985
led_off_col(N) when N > 13 -> ?highloadbg;
943
986
led_off_col(N) when N > 9 -> ?midloadbg;
944
 
led_off_col(N) -> ?lowloadbg.
 
987
led_off_col(_) -> ?lowloadbg.
945
988
 
946
 
reset_led(Leds, 0) -> ok;
 
989
reset_led(_Leds, 0) -> ok;
947
990
reset_led(Leds, N) ->
948
991
    gs:config(lists:nth(N, Leds), [{fill, led_off_col(N)}]).
949
992
 
950
 
set_led(Leds, 0) -> ok;
 
993
set_led(_Leds, 0) -> ok;
951
994
set_led(Leds, N) ->
952
995
    gs:config(lists:nth(N, Leds), [{fill, led_on_col(N)}]).
953
996
 
967
1010
                  MNodes).
968
1011
 
969
1012
max(X, Y) when X>Y -> X;
970
 
max(X, Y) -> Y.
 
1013
max(_, Y) -> Y.
971
1014
 
972
1015
%% parse_nodes(MNodes) -> NodeApps
973
1016
%%   MNodes -> [#mnode{}]
982
1025
parse_nodes([MNode|MNodes], NodeApps) ->
983
1026
    Apps = parse_apps(MNode#mnode.apps, []),
984
1027
    parse_nodes(MNodes,
985
 
                [{MNode#mnode.name, MNode#mnode.status, Apps}|NodeApps]);
 
1028
                [{MNode#mnode.name,MNode#mnode.status,Apps}|NodeApps]);
986
1029
parse_nodes([], NodeApps) ->
987
1030
    NodeApps.
988
1031