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

« back to all changes in this revision

Viewing changes to lib/runtime_tools/src/inviso_autostart.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:
 
1
%% ``The contents of this file are subject to the Erlang Public License,
 
2
%% Version 1.1, (the "License"); you may not use this file except in
 
3
%% compliance with the License. You should have received a copy of the
 
4
%% Erlang Public License along with this software. If not, it can be
 
5
%% retrieved via the world wide web at http://www.erlang.org/.
 
6
%% 
 
7
%% Software distributed under the License is distributed on an "AS IS"
 
8
%% basis, WITHOUT WARRANTY OF ANY KIND, either express or implied. See
 
9
%% the License for the specific language governing rights and limitations
 
10
%% under the License.
 
11
%% 
 
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
%%
 
18
%% Author: Lennart �hman, lennart.ohman@st.se
 
19
-module(inviso_autostart).
 
20
 
 
21
-export([autostart/1,which_config_file/0]).
 
22
 
 
23
%% This module implements the default autostart module for the inviso runtime
 
24
%% component.
 
25
%% It will:
 
26
%% (1) Open the autostart configuration file (either the default or the one
 
27
%%     pointed out by the runtime_tools application parameter inviso_autostart_config).
 
28
%% (2) Check that the incarnation counter has not reached 0. If so, we do not
 
29
%%     allow (yet) one autostart.
 
30
%% (3) Rewrite the configuration file if there was an incarnation counter.
 
31
%%     (With the counter decreased).
 
32
%% (4) Inspect the content of the configuration file and pass paramters in the
 
33
%%     return value (which is interpreted by the runtime component).
 
34
%%
 
35
%% CONTENT OF A CONFIGURATION FILE:
 
36
%% A plain text file containing erlang tuple terms, each ended with a period(.).
 
37
%% The following parameters are recognized:
 
38
%% {repeat,N} N=interger(),
 
39
%%   The number of remaining allowed autostart incarnations of inviso.
 
40
%% {options,Options} Options=list()
 
41
%%   The options which controls the runtime component, such as overload and
 
42
%%   dependency.
 
43
%% {mfa,{Mod,Func,Args}} Args=list()
 
44
%%   Controls how a spy process initiating tracing, patterns and flags shall
 
45
%%   be started.
 
46
%% {tag,Tag}
 
47
%%   The tag identifying the runtime component to control components.
 
48
%% =============================================================================
 
49
 
 
50
%% This function is run in the runtime component's context during autostart
 
51
%% to determine whether to continue and if, then how.
 
52
autostart(_AutoModArgs) ->
 
53
    ConfigFile=
 
54
        case application:get_env(inviso_autostart_conf) of
 
55
            {ok,FileName} when list(FileName) -> % Use this filename then.
 
56
                FileName;
 
57
            _ ->                            % Use a default name, in CWD!
 
58
                "inviso_autostart.config"
 
59
        end,
 
60
    case file:consult(ConfigFile) of
 
61
        {ok,Terms} ->                       % There is a configuration.
 
62
            case handle_repeat(ConfigFile,Terms) of
 
63
                ok ->                       % Handled or not, we shall continue.
 
64
                    {get_mfa(Terms),get_options(Terms),get_tag(Terms)};
 
65
                stop ->                     % We are out of allowed starts.
 
66
                    true                    % Then no autostart.
 
67
            end;
 
68
        {error,_} ->                        % There is no config file
 
69
            true                            % Then no autostart!
 
70
    end.
 
71
%% -----------------------------------------------------------------------------
 
72
 
 
73
%% Function returning the filename probably used as autostart config file.
 
74
%% Note that this function must be executed at the node in question.
 
75
which_config_file() ->
 
76
    case application:get_env(runtime_tools,inviso_autostart_conf) of
 
77
        {ok,FileName} when list(FileName) -> % Use this filename then.
 
78
            FileName;
 
79
        _ ->                                % Use a default name, in CWD!
 
80
            {ok,CWD}=file:get_cwd(),
 
81
            filename:join(CWD,"inviso_autostart.config")
 
82
    end.
 
83
%% -----------------------------------------------------------------------------
 
84
 
 
85
 
 
86
%% Help function which finds out if there is a limit on the number of times
 
87
%% we shall autostart. If there is a repeat parameter and it is greater than
 
88
%% zero, the file must be rewritten with the parameter decreased with one.
 
89
%% Returns 'ok' or 'stop'.
 
90
handle_repeat(FileName,Terms) ->
 
91
    case lists:keysearch(repeat,1,Terms) of
 
92
        {value,{_,N}} when N>0 ->           % Controlls how many time more.
 
93
            handle_repeat_rewritefile(FileName,Terms,N-1),
 
94
            ok;                             % Indicate that we shall continue.
 
95
        {value,_} ->                        % No we have reached the limit.
 
96
            stop;
 
97
        false ->                            % There is no repeat parameter.
 
98
            ok                              % No restrictions then!
 
99
    end.
 
100
 
 
101
%% Help function which writes the configuration file again, but with the
 
102
%% repeat parameter set to NewN.
 
103
%% Returns nothing significant.
 
104
handle_repeat_rewritefile(FileName,Term,NewN) ->
 
105
    case file:open(FileName,[write]) of
 
106
        {ok,FD} ->
 
107
            NewTerm=lists:keyreplace(repeat,1,Term,{repeat,NewN}),
 
108
            handle_repeat_rewritefile_2(FD,NewTerm),
 
109
            file:close(FD);
 
110
        {error,_Reason} ->                  % Not much we can do then?!
 
111
            error
 
112
    end.
 
113
 
 
114
handle_repeat_rewritefile_2(FD,[Tuple|Rest]) ->
 
115
    io:format(FD,"~w.~n",[Tuple]),
 
116
    handle_repeat_rewritefile_2(FD,Rest);
 
117
handle_repeat_rewritefile_2(_,[]) ->
 
118
    true.
 
119
%% -----------------------------------------------------------------------------
 
120
 
 
121
%% Three help functions finding the parameters possible to give to the runtime
 
122
%% component. Note that some of them have default values, should the parameter
 
123
%% not exist.
 
124
get_mfa(Terms) ->
 
125
    case lists:keysearch(mfa,1,Terms) of
 
126
        {value,{_,MFA}} ->
 
127
            MFA;
 
128
        false ->
 
129
            false
 
130
    end.
 
131
 
 
132
get_options(Terms) ->
 
133
    case lists:keysearch(options,1,Terms) of
 
134
        {value,{_,Options}} ->
 
135
            Options;
 
136
        false ->
 
137
            []
 
138
    end.
 
139
 
 
140
get_tag(Terms) ->
 
141
    case lists:keysearch(tag,1,Terms) of
 
142
        {value,{_,Tag}} ->
 
143
            Tag;
 
144
        false ->
 
145
            default_tag
 
146
    end.
 
147
%% -----------------------------------------------------------------------------
 
148
 
 
149
 
 
150
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%