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

« back to all changes in this revision

Viewing changes to lib/os_mon/src/cpu_sup.erl

  • Committer: Bazaar Package Importer
  • Author(s): Sergei Golovan
  • Date: 2009-05-07 15:07:37 UTC
  • mfrom: (1.2.1 upstream) (5.1.2 sid)
  • Revision ID: james.westby@ubuntu.com-20090507150737-i4yb5elwinm7r0hc
Tags: 1:13.b-dfsg1-1
* Removed another bunch of non-free RFCs from original tarball
  (closes: #527053).
* Fixed build-dependencies list by adding missing comma. This requires
  libsctp-dev again. Also, added libsctp1 dependency to erlang-base and
  erlang-base-hipe packages because the shared library is loaded via
  dlopen now and cannot be added using dh_slibdeps (closes: #526682).
* Weakened dependency of erlang-webtool on erlang-observer to recommends
  to avoid circular dependencies (closes: #526627).
* Added solaris-i386 to HiPE enabled architectures.
* Made script sources in /usr/lib/erlang/erts-*/bin directory executable,
  which is more convenient if a user wants to create a target Erlang system.
* Shortened extended description line for erlang-dev package to make it
  fit 80x25 terminals.

Show diffs side-by-side

added added

removed removed

Lines of Context:
1
 
%% ``The contents of this file are subject to the Erlang Public License,
 
1
%%
 
2
%% %CopyrightBegin%
 
3
%% 
 
4
%% Copyright Ericsson AB 1997-2009. All Rights Reserved.
 
5
%% 
 
6
%% The contents of this file are subject to the Erlang Public License,
2
7
%% Version 1.1, (the "License"); you may not use this file except in
3
8
%% compliance with the License. You should have received a copy of the
4
9
%% Erlang Public License along with this software. If not, it can be
5
 
%% retrieved via the world wide web at http://www.erlang.org/.
 
10
%% retrieved online at http://www.erlang.org/.
6
11
%% 
7
12
%% Software distributed under the License is distributed on an "AS IS"
8
13
%% basis, WITHOUT WARRANTY OF ANY KIND, either express or implied. See
9
14
%% the License for the specific language governing rights and limitations
10
15
%% under the License.
11
16
%% 
12
 
%% The Initial Developer of the Original Code is Ericsson Utvecklings AB.
13
 
%% Portions created by Ericsson are Copyright 1999, Ericsson Utvecklings
14
 
%% AB. All Rights Reserved.''
15
 
%% 
16
 
%%     $Id$
 
17
%% %CopyrightEnd%
17
18
%%
18
19
-module(cpu_sup).
19
20
 
249
250
            {ok, [N], _} = io_lib:fread("~d", Ps),
250
251
            N-1
251
252
    end;
 
253
get_uint32_measurement(Request, #internal{os_type = {unix, dragonfly}}) ->
 
254
    D = os:cmd("/sbin/sysctl -n vm.loadavg") -- "\n",
 
255
    {ok,[Load1,Load5,Load15],_} = io_lib:fread("{ ~f ~f ~f }", D),
 
256
    %% We could count the lines from the ps command as well
 
257
    case Request of
 
258
        ?avg1  -> sunify(Load1);
 
259
        ?avg5  -> sunify(Load5);
 
260
        ?avg15 -> sunify(Load15);
 
261
        ?ping -> 4711;
 
262
        ?nprocs ->
 
263
            Ps = os:cmd("/bin/ps -ax | /usr/bin/wc -l"),
 
264
            {ok, [N], _} = io_lib:fread("~d", Ps),
 
265
            N-1
 
266
    end;
252
267
get_uint32_measurement(Request, #internal{os_type = {unix, openbsd}}) ->
253
268
    D = os:cmd("/sbin/sysctl -n vm.loadavg") -- "\n",
254
269
    {ok, [L1, L5, L15], _} = io_lib:fread("~f ~f ~f", D),
536
551
            port_server_start();
537
552
        {unix, Flavor} when Flavor==darwin;
538
553
                            Flavor==freebsd;
 
554
                            Flavor==dragonfly;
539
555
                            Flavor==openbsd;
540
556
                            Flavor==irix64;
541
557
                            Flavor==irix ->
620
636
        {Pid, ?nprocs} ->
621
637
            port_command(Port, ?nprocs),
622
638
            Result = port_receive_uint32(Port, Timeout),
623
 
            port_server_handle_reply(Port, Pid, Result, Timeout);
 
639
            Pid ! {self(), {data, Result}},
 
640
            port_server_loop(Port, Timeout);
624
641
 
625
642
        % Average load for the past minute
626
643
        {Pid, ?avg1} ->
627
644
            port_command(Port, ?avg1),
628
645
            Result = port_receive_uint32(Port, Timeout),
629
 
            port_server_handle_reply(Port, Pid, Result, Timeout);
 
646
            Pid ! {self(), {data, Result}},
 
647
            port_server_loop(Port, Timeout);
630
648
 
631
649
        % Average load for the past five minutes
632
650
        {Pid, ?avg5} ->
633
651
            port_command(Port, ?avg5),
634
652
            Result = port_receive_uint32(Port, Timeout),
635
 
            port_server_handle_reply(Port, Pid, Result, Timeout);
 
653
            Pid ! {self(), {data, Result}},
 
654
            port_server_loop(Port, Timeout);
636
655
        
637
656
        % Average load for the past 15 minutes
638
657
        {Pid, ?avg15} ->
639
658
            port_command(Port, ?avg15),
640
659
            Result = port_receive_uint32(Port, Timeout),
641
 
            port_server_handle_reply(Port, Pid, Result, Timeout);
 
660
            Pid ! {self(), {data, Result}},
 
661
            port_server_loop(Port, Timeout);
642
662
 
643
663
        {Pid, ?util} ->
644
664
            port_command(Port, ?util),
645
665
            Result = port_receive_util(Port, Timeout),
646
 
            port_server_handle_reply(Port, Pid, Result, Timeout);
 
666
            Pid ! {self(), {data, Result}},
 
667
            port_server_loop(Port, Timeout);
647
668
 
648
669
        % Port ping
649
670
        {Pid, ?ping} ->
650
671
            port_command(Port, ?ping),
651
672
            Result = port_receive_uint32(Port, Timeout),
652
 
            port_server_handle_reply(Port, Pid, Result, Timeout);
 
673
            Pid ! {self(), {data, Result}},
 
674
            port_server_loop(Port, Timeout);
653
675
 
654
676
        % Close port and this server
655
677
        {Pid, ?quit} ->
659
681
            ok;
660
682
 
661
683
        % Ignore other commands
662
 
        _Other -> port_server_loop(Port, Timeout)
 
684
        _ -> port_server_loop(Port, Timeout)
663
685
    end.        
664
686
 
665
 
port_server_handle_reply(Port, Pid, Reply, Timeout) ->
666
 
    case Reply of
667
 
        {error, Reason} ->
668
 
            %%% FIXME: Could this happen?
669
 
 
670
 
            % Explain error for the client
671
 
            Pid ! {self(), {error, Reason}},
672
 
            % Kill and clean the port and its messages
673
 
            port_command(Port, ?quit),
674
 
            port_close(Port),
675
 
            port_server_flush_messages(Port),
676
 
            % Reboot port
677
 
            exit(timeout); 
678
 
        Result -> 
679
 
           % All is fine, send result to client
680
 
           Pid ! {self(), {data, Result}},
681
 
           port_server_loop(Port, Timeout)
682
 
    end.
683
 
   
684
 
%% Necessary?
685
 
port_server_flush_messages(Port) ->
686
 
    receive {'EXIT', Port, _} -> ok after 0 -> ok end,
687
 
    receive {Port, {data, _}} -> ok after 0 -> ok end.
688
 
 
689
687
port_receive_uint32( Port,  Timeout) -> port_receive_uint32(Port, Timeout, []).
690
688
port_receive_uint32(_Port, _Timeout, [D3,D2,D1,D0]) -> ?INT32(D3,D2,D1,D0);
691
689
port_receive_uint32(_Port, _Timeout, [_,_,_,_ | G]) -> exit({port_garbage, G});