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

« back to all changes in this revision

Viewing changes to lib/pman/src/pman_main.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:
83
83
    {Window, Grid,Frame, Visible}  =
84
84
        pman_win:pman_window(Grid_size, OSModuleExcluded, LINode),
85
85
 
 
86
    Noshell = case pman_shell:find_shell() of
 
87
                  noshell -> true;
 
88
                  _ -> false
 
89
              end,
86
90
 
87
91
    Pman_data = #gs_pman{win=Window, grid=Grid, frame=Frame,
88
92
                         size=Visible,
90
94
                         hide_modules=OSModuleExcluded,
91
95
                         focus= 1,
92
96
                         node= node(),
 
97
                         noshell = Noshell,
93
98
                         nodes= LINode},
94
99
 
95
100
    Pman_data2 = refresh(Pman_data),
131
136
            get_grid_size(LIProcess, Ack);
132
137
 
133
138
 
134
 
        Module ->
 
139
        _Module ->
135
140
            get_grid_size(LIProcess, Ack+1)
136
141
    end.
137
142
 
153
158
%% ---------------------------------------------------------------
154
159
 
155
160
update_nodes_menu(Pman_data) ->
156
 
    OSNodesNew = ordsets:list_to_set(get_nodes()),
157
 
    OSNodesOld = ordsets:list_to_set(Pman_data#gs_pman.nodes),
 
161
    OSNodesNew = ordsets:from_list(get_nodes()),
 
162
    OSNodesOld = ordsets:from_list(Pman_data#gs_pman.nodes),
158
163
 
159
164
    OSNodesAdd = ordsets:subtract(OSNodesNew,OSNodesOld),
160
165
    OSNodesDelete = ordsets:subtract(OSNodesOld,OSNodesNew),
180
185
%% Returnd: New position Int
181
186
%% ---------------------------------------------------------------
182
187
 
183
 
check_focus_choice(To,      0) -> 1;
 
188
check_focus_choice(_To,      0) -> 1;
184
189
check_focus_choice(0,    Size) -> Size; 
185
190
check_focus_choice(To,   Size) -> 
186
191
    case Size+1 of
201
206
get_pos([], _, _) -> 
202
207
    false;
203
208
 
204
 
get_pos([Element | Rest], Element, Count) ->
 
209
get_pos([Element | _Rest], Element, Count) ->
205
210
    Count;
206
211
 
207
212
get_pos([_ | Rest], Element, Count) ->
334
339
%% New processes however, will be covered by the filters.
335
340
%% 
336
341
 
337
 
execute_cmd('Show All',Pman_data,Data,Args) ->
 
342
execute_cmd('Show All',Pman_data,_Data,_Args) ->
338
343
 
339
344
    OSPidAll = pman_process:r_processes(Pman_data#gs_pman.node),
340
345
    
350
355
%% Open a list of not shown (hidden + new + system) processes (PIDS)
351
356
%% where the user can select which processes shall be shown.
352
357
%% 
353
 
execute_cmd('Show Selected',Pman_data,Data,Args) ->
 
358
execute_cmd('Show Selected',Pman_data,_Data,_Args) ->
354
359
 
355
360
    %% Open a dialog with a list of all PIDs that are not currently shown
356
361
    OSPidAll = pman_process:r_processes(Pman_data#gs_pman.node),
399
404
            %% Add the selected PIDs from the dialog to the list
400
405
            %% of explicitly shown PIDs
401
406
            OSPidShown = ordsets:union(Pman_data#gs_pman.show_pids,
402
 
                                       ordsets:list_to_set(List2)),
 
407
                                       ordsets:from_list(List2)),
403
408
            New_Pman_data = Pman_data#gs_pman{show_pids = OSPidShown},
404
409
            
405
410
            %% Refresh the list of PIDs
413
418
 
414
419
%% Start Help window
415
420
 
416
 
execute_cmd('Help',Pman_data,Data,Args)  ->
417
 
    HelpFile = filename:join(code:priv_dir(pman), "../doc/index.html"),
 
421
execute_cmd('Help',Pman_data,_Data,_Args)  ->
 
422
    HelpFile = filename:join([code:lib_dir(pman), "doc", "html", "index.html"]),
418
423
    tool_utils:open_help(gse:start([{kernel, true}]), HelpFile),
419
424
    Pman_data;
420
425
 
421
426
 
422
427
%% Trace the shell
423
428
 
424
 
execute_cmd('Trace Shell',Pman_data,Data,Args) ->
425
 
    Shell = pman_shell:find_shell(),
426
 
    pman_shell:start({{shell,Shell},self()},Pman_data#gs_pman.options),
427
 
    Pman_data;
428
 
 
 
429
execute_cmd('Trace Shell',Pman_data,_Data,_Args) ->
 
430
    case pman_shell:find_shell() of
 
431
        noshell ->
 
432
            Pman_data;
 
433
        Shell -> 
 
434
            pman_shell:start({{shell,Shell},self()},Pman_data#gs_pman.options),
 
435
            Pman_data#gs_pman{noshell = false}
 
436
    end;
429
437
 
430
438
 
431
439
%% Start Trace Window
432
440
 
433
 
execute_cmd('Trace Process',Pman_data,Data,Args) ->
 
441
execute_cmd('Trace Process',Pman_data,_Data,_Args) ->
434
442
    case get_pid_in_focus(Pman_data) of
435
443
        false      ->
436
444
            Pman_data;
442
450
 
443
451
%% Open trace windows for all pids linked to the pid in focus
444
452
 
445
 
execute_cmd('All Links',Pman_data,Data,Args) ->
 
453
execute_cmd('All Links',Pman_data,_Data,_Args) ->
446
454
    case get_pid_in_focus(Pman_data) of
447
455
        false      -> Pman_data;
448
456
        {true,{pidfunc,Pid,_}} ->
455
463
 
456
464
%%  Open trace window for a specific pid linked to the pid in focus
457
465
 
458
 
execute_cmd({'Links',LPid},Pman_data,Data,Args) ->
 
466
execute_cmd({'Links',LPid},Pman_data,_Data,_Args) ->
459
467
    case get_pid_in_focus(Pman_data) of
460
468
        false      -> Pman_data;
461
 
        {true,{pidfunc,Pid,_}} ->
 
469
        {true,{pidfunc,_Pid,_}} ->
462
470
            pman_shell:start(LPid, Pman_data#gs_pman.options),
463
471
            Pman_data
464
472
    end;
465
473
 
466
474
%% Kill the pid in focus
467
475
 
468
 
execute_cmd('Kill',Pman_data,Data,Args) ->
 
476
execute_cmd('Kill',Pman_data,_Data,_Args) ->
469
477
    case get_pid_in_focus(Pman_data) of
470
478
        false      -> 
471
479
            Pman_data;
476
484
 
477
485
%% Open window with module information
478
486
 
479
 
execute_cmd('Module',Pman_data,Data,Args) ->
 
487
execute_cmd('Module',Pman_data,_Data,_Args) ->
480
488
    case get_pid_in_focus(Pman_data) of
481
489
        false            -> Pman_data;          %0
482
490
        
491
499
%% Hide an explicitly selected process (PID).
492
500
%%
493
501
 
494
 
execute_cmd('Hide Selected Process', Pman_data, Data, Args) ->
 
502
execute_cmd('Hide Selected Process', Pman_data, _Data, _Args) ->
495
503
    case get_pid_in_focus(Pman_data) of
496
504
        %% No process selected
497
505
        false -> 
523
531
%% The selected modules are added to the list of hidden modules.
524
532
%%
525
533
 
526
 
execute_cmd('Hide Modules',Pman_data,Data,Args) ->
 
534
execute_cmd('Hide Modules',Pman_data,_Data,_Args) ->
527
535
 
528
536
    %% Get all loaded modules, and then strip unnecessary info
529
537
 
533
541
                element(1,T)
534
542
        end,
535
543
    OSModuleLoaded =
536
 
        ordsets:list_to_set(lists:map(MapFun, LITupleLoaded)),
 
544
        ordsets:from_list(lists:map(MapFun, LITupleLoaded)),
537
545
 
538
546
    %% Let the user select which of the loaded modules to exclude from the
539
547
    %% process overview
546
554
        {cancelled, _Reason} ->
547
555
            Pman_data;
548
556
        Selection ->
549
 
            OSDialogResult = ordsets:list_to_set(Selection),
 
557
            OSDialogResult = ordsets:from_list(Selection),
550
558
    
551
559
            OSModuleHidden = ordsets:union(OSDialogResult,
552
560
                                           Pman_data#gs_pman.hide_modules),
566
574
%% I.e. they will remain hidden, but will be shown if the filter is
567
575
%% switched off.
568
576
 
569
 
execute_cmd('Hide All',Pman_data,Data,Args) ->
 
577
execute_cmd('Hide All',Pman_data,_Data,_Args) ->
570
578
 
571
579
    OSPidAll = pman_process:r_processes(Pman_data#gs_pman.node),
572
580
 
593
601
%% Explicitly show a specific process (PID)
594
602
%%
595
603
 
596
 
execute_cmd('Show Selected Process', Pman_data, Data, Args) ->
 
604
execute_cmd('Show Selected Process', Pman_data, _Data, _Args) ->
597
605
    case get_pid_in_focus(Pman_data) of
598
606
 
599
607
        %% No process selected
615
623
%% Set default options for tracing
616
624
%%
617
625
 
618
 
execute_cmd('Default Options',Pman_data,Data,Args) ->
 
626
execute_cmd('Default Options',Pman_data,_Data,_Args) ->
619
627
    OldOptions = Pman_data#gs_pman.options,
620
628
    NewOptions = pman_options:dialog(Pman_data#gs_pman.win,
621
629
                                     "Default Trace Options",
622
630
                                     OldOptions),
623
631
    case NewOptions of
624
 
        {error, Reason} ->
 
632
        {error, _Reason} ->
625
633
            Pman_data;
626
634
        Options ->
627
635
            Pman_data#gs_pman{options=Options}
631
639
%% Save the set default options to the users pman-frofile file
632
640
%%
633
641
 
634
 
execute_cmd('Save Options', Pman_data,Data,Args)->
 
642
execute_cmd('Save Options', Pman_data,_Data,_Args)->
635
643
    %% Platform dependent code for determining where to store
636
644
    %% the user options
637
645
    FileName = pman_osdepend:options_file_name(),
644
652
    pman_osdepend:mkdir_for_file(FileName),
645
653
    
646
654
    case catch pman_options:save_to_file(Options,FileName) of
647
 
        {'EXIT', {file_problem, Reason}} ->
 
655
        {'EXIT', {file_problem, _Reason}} ->
648
656
            tool_utils:notify(Parent,"Could not save options.");
649
657
        true ->
650
658
            tool_utils:notify(Parent,"Options saved in\n" ++ FileName)
657
665
 
658
666
%% Exit the application
659
667
 
660
 
execute_cmd('Exit',Pman_data,Data,Args) ->
 
668
execute_cmd('Exit',Pman_data,_Data,_Args) ->
661
669
    gs:destroy(Pman_data#gs_pman.win),
662
670
    exit(topquit);
663
671
 
687
695
%% this must be "forwarded" to the geometry managing frame.
688
696
%% It is also forwarded to a "manual" geometry manager for the grid.
689
697
%% 
690
 
execute_cmd({configure,W,H,X,Y},Pman_data,Data,Args) ->
 
698
execute_cmd({configure,W,H,_X,_Y},Pman_data,_Data,_Args) ->
691
699
    
692
700
    gse:resize(Pman_data#gs_pman.frame, W, H-?MENU_HEIGHT),
693
701
 
711
719
%%
712
720
%% The checkbutton for hiding system processes has been selected.
713
721
 
714
 
execute_cmd('Hide System', Pman_data, Data, Args ) ->
 
722
execute_cmd('Hide System', Pman_data, _Data, Args ) ->
715
723
    [_Text, _Group, Bool|_Rest] = Args,
716
724
    New_Pman_data = Pman_data#gs_pman{hide_system=Bool},
717
725
    refresh(New_Pman_data);
723
731
%%
724
732
%% The checkbutton for hiding new processes has been selected.
725
733
 
726
 
execute_cmd('Auto Hide New', Pman_data, Data, Args ) ->
 
734
execute_cmd('Auto Hide New', Pman_data, _Data, Args ) ->
727
735
    [_Text, _Group, Bool|_Rest] = Args,
728
736
 
729
737
    Pman_data2 = Pman_data#gs_pman{hide_new=Bool},
736
744
 
737
745
 
738
746
 
739
 
execute_cmd(Cmd,Pman_data,Data,Args) -> Pman_data.
 
747
execute_cmd(_Cmd,Pman_data,_Data,_Args) -> Pman_data.
740
748
 
741
749
%% ---------------------------------------------------------------
742
750
%% Execute the Various command requests received Through events
744
752
%% ---------------------------------------------------------------
745
753
 
746
754
gs_cmd(Cmd,Pman_data) ->
747
 
    Window = Pman_data#gs_pman.win,
748
755
    case Cmd of
749
756
       
750
757
        %%Window manager commands
762
769
        %% Single click in the process list sets focus to the clicked process
763
770
        {gs,_Gl,click,{pidfunc,_,_},[_Col,Row|_T]} when integer(Row) ->
764
771
            focus(Row,Pman_data);
765
 
        {gs,_Gl,doubleclick,{pidfunc,P,M},[Col,Row| _]} when integer(Row) ->
 
772
        {gs,_Gl,doubleclick,{pidfunc,_P,_M},[_Col,Row| _]} when integer(Row) ->
766
773
            execute_cmd('Trace Process',Pman_data,[],[]);
767
774
      
768
775
        %%Menu Commands / Button presses
778
785
 
779
786
        {gs,_W,keypress,[],['Return',_,0,0]} ->
780
787
            execute_cmd('Trace',Pman_data,[],[]);
781
 
        {gs,_W,keypress,D,[Key,_,0,1]} ->
 
788
        {gs,_W,keypress,_D,[Key,_,0,1]} ->
782
789
            execute_cmd(key(Key),Pman_data,[],[]);
783
790
 
784
791
 
785
 
        Other ->
 
792
        _Other ->
786
793
 
787
794
            Pman_data
788
795
    end.
814
821
%%
815
822
 
816
823
disable_pid_actions() ->
817
 
    lists:foreach({gse, disable}, ?REQUIRES_FOCUS).
 
824
    lists:foreach(fun(X) -> gse:disable(X) end, ?REQUIRES_FOCUS).
818
825
 
819
826
 
820
827
enable_pid_actions()  ->
821
 
    lists:foreach({gse, enable}, ?REQUIRES_FOCUS).
822
 
 
823
 
 
824
 
 
825
 
 
 
828
    lists:foreach(fun(X) -> gse:enable(X) end, ?REQUIRES_FOCUS).
 
829
 
 
830
 
 
831
%% Check if node is running in noshell mode and if so disable the
 
832
%% 'Trace Shell' menu option.
 
833
 
 
834
trace_shell_possible(#gs_pman{noshell = true}) ->
 
835
    gse:disable('Trace Shell');
 
836
trace_shell_possible(_) ->
 
837
    ok.
826
838
 
827
839
%% ---------------------------------------------------------------
828
840
%% The main loop for the  pman window
876
888
            loop(update_nodes_menu(Pman_data2));
877
889
 
878
890
        %% Ignore EXIT signals from "inferior" processes. 
879
 
        {'EXIT', Pid, Reason} ->
 
891
        {'EXIT', _Pid, _Reason} ->
880
892
            loop(Pman_data);
881
893
        
882
894
 
964
976
    %% All processes are now displayed.
965
977
    %% Now set the focus appropriately.
966
978
 
967
 
    Pman_data4=set_focus(OSPidShow,Pman_data3),
968
 
 
969
 
 
970
 
 
 
979
    Pman_data4 = set_focus(OSPidShow,Pman_data3),
971
980
 
972
981
    focus(Pman_data4#gs_pman.focus, Pman_data3),
 
982
 
 
983
    trace_shell_possible(Pman_data4),
973
984
    
974
985
    case Size of
975
986
        1 -> ok;
1028
1039
                        [];
1029
1040
 
1030
1041
                    OSPidOld ->
1031
 
                        OSPidNew = ordsets:subtract(OSPidAll, OSPidOld)
 
1042
                        ordsets:subtract(OSPidAll, OSPidOld)
1032
1043
                end;
1033
1044
 
1034
1045
            false ->
1040
1051
        case Pman_data#gs_pman.hide_system of
1041
1052
            true ->
1042
1053
                OSPidSystem =
1043
 
                    lists:filter({pman_process, is_system_process},
 
1054
                    lists:filter(fun(P) -> pman_process:is_system_process(P) end,
1044
1055
                                 OSPidAll),
1045
1056
                ordsets:union(OSPidDontShow1, OSPidSystem);
1046
1057
            false ->
1101
1112
        'nonode@nohost' ->
1102
1113
            node();
1103
1114
 
1104
 
        Otherwise ->
 
1115
        _Otherwise ->
1105
1116
            % 1. Previous was this, but distributed.
1106
1117
            case This of
1107
1118
                'nonode@nohost' ->
1108
1119
                    node();
1109
1120
 
1110
1121
            % 2. Last was another node.
1111
 
                Remote ->
 
1122
                _Remote ->
1112
1123
                    LastName
1113
1124
            
1114
1125
            end