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

« back to all changes in this revision

Viewing changes to lib/runtime_tools/src/inviso_autostart_server.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
%%
 
20
-module(inviso_autostart_server).
 
21
-export([init/1]).
 
22
 
 
23
%% This module provides a (well working) example of how to program an
 
24
%% autostart server responsible for initializing trace, setting patterns
 
25
%% and flags.
 
26
%%
 
27
%% The general idea is that this code opens one or several files containing
 
28
%% erlang function calls which are evaluated in this process context.
 
29
%% The argument provided to init shall be a list of options controlling
 
30
%% how to initialize tracing, which file(s) to open and variable bindings.
 
31
%%
 
32
%% This autostart_server understands standard inviso trace case files.
 
33
%% The runtime component provides an API very similar to the API provided
 
34
%% by the control component. This program translates any control component
 
35
%% API calls (as could possibly be found in a trace case file) to corresponding
 
36
%% runtime component API calls.
 
37
%% It performs the trick by simply removing the parameters from the calls
 
38
%% before making the call, and of course changes the module name in the call.
 
39
%% This also means that variables concerning control components does not have
 
40
%% to be bound in this environment.
 
41
%% =============================================================================
 
42
 
 
43
 
 
44
%% -----------------------------------------------------------------------------
 
45
 
 
46
%% The independent autostart process spawned by the runtime component to carry
 
47
%% out initializations is spawened on this function (if using the example
 
48
%% autostart which comes with inviso).
 
49
%% ArgsFromConfig is as can be heard from the name comming from a paramater in
 
50
%% the autostart configuration file. Here it is supposed to be:
 
51
%%   ArgsFromConfig=[ServerParam,...]
 
52
%%     ServerParam={tracerdata,TracerData}|{cmdfiles,Files}|{bindings,Bindings}|
 
53
%%       {translations,Translations}|{debug,DbgLevel}
 
54
%%       TracerData=tracerdata given to inviso_rt:init_tracing/1 function.
 
55
%%       Files=[FileName,...] files with trace cases, which will be carried out
 
56
%%         in the order specified.
 
57
%%       Bindings=[{Var,Value},...] variable environment understood by
 
58
%%         erl_eval:exprs/2.
 
59
%%       Translations=[Translation,...]
 
60
%%       A translation file is a text-file with following tuples
 
61
%%         Translation={{Mod,Func,Arity,{Mod2,Func2,ParamMF}}}|
 
62
%%                     {{Func,Arity,{Mod2,Func2,ParamMF}}}
 
63
%%           ParamMF={M,F} | any()
 
64
%%           Translates Mod:Func/Arity to Mod2:Func2 with the arguments to
 
65
%%             Mod:Func translated using M:F/1. Note that ParamMF is not
 
66
%%             necessarily an MF. If no translation shall be done, ParamFun
 
67
%%             shall be anything else but an MF.
 
68
%%           Also note that Mod is optional in a Translation. That means that
 
69
%%           function calls without a module in the trace case file will
 
70
%%           be translated according to that translation.
 
71
init(ArgsFromConfig) ->
 
72
    case get_tracerdata_opts(ArgsFromConfig) of
 
73
        {ok,TracerData} ->                  % Otherwise we can not start a trace!
 
74
            case inviso_rt:init_tracing(TracerData) of
 
75
                {ok,_} ->                   % Ok, tracing has been initiated.
 
76
                    case get_cmdfiles_opts(ArgsFromConfig) of
 
77
                        {ok,CmdFiles} ->    % List of cmd-files.
 
78
                            Bindings=get_initialbindings_opts(ArgsFromConfig),
 
79
                            Translations=get_translations_opts(ArgsFromConfig),
 
80
                            Dbg=get_dbg_opts(ArgsFromConfig),
 
81
                            interpret_cmd_files(CmdFiles,
 
82
                                                Bindings,
 
83
                                                Translations,
 
84
                                                Dbg);
 
85
                        false ->            % Then we can terminate normally.
 
86
                            true
 
87
                    end;
 
88
                {error,Reason} ->           % This is fault, lets terminate abnormally.
 
89
                    exit({inviso,{error,Reason}})
 
90
            end;
 
91
        false ->                            % Then there is not much use then.
 
92
            true                            % Just terminate normally.
 
93
    end.
 
94
%% -----------------------------------------------------------------------------
 
95
 
 
96
interpret_cmd_files([FileName|Rest],Bindings,Translations,Dbg) ->
 
97
    case file:open(FileName,[read]) of
 
98
        {ok,FD} ->
 
99
            interpret_cmd_files_2(FD,Bindings,io:parse_erl_exprs(FD,""),Translations,Dbg),
 
100
            file:close(FD),
 
101
            interpret_cmd_files(Rest,Bindings,Translations,Dbg); % Yes, the original bindings!
 
102
        {error,Reason} ->                   % Something wrong with the file.
 
103
            inviso_rt_lib:debug(Dbg,interpret_cmd_files,[FileName,{error,Reason}]),
 
104
            interpret_cmd_files(Rest,Bindings,Translations,Dbg) % Yes, the original bindings!
 
105
    end;
 
106
interpret_cmd_files([],_,_,_) ->            % Done, return nothing significant!
 
107
    true.
 
108
 
 
109
%% Help function which handles Exprs returned from io:parse_erl_exprs and
 
110
%% tries to eval them. It is the side-effects we are interested in, like
 
111
%% setting flags and patterns. Note that we will get a failure should there
 
112
%% be a variable conflict.
 
113
%% Also note that there is logic to translate control component API calls to
 
114
%% corresponding runtime component calls.
 
115
%% Returns nothing significant.
 
116
interpret_cmd_files_2(FD,Bindings,{ok,Exprs,_},Translations,Dbg) ->
 
117
    case catch inviso_rt_lib:transform(Exprs,Translations) of
 
118
        NewExprs when list(NewExprs) ->     % We may have translated the API.
 
119
            case catch erl_eval:exprs(NewExprs,Bindings) of
 
120
                {'EXIT',Reason} ->
 
121
                    inviso_rt_lib:debug(Dbg,exprs,[Exprs,Bindings,{'EXIT',Reason}]),
 
122
                    interpret_cmd_files_2(FD,
 
123
                                          Bindings,
 
124
                                          io:parse_erl_exprs(FD,""),
 
125
                                          Translations,
 
126
                                          Dbg);
 
127
                {value,_Val,NewBindings} -> % Only interested in the side effects!
 
128
                    interpret_cmd_files_2(FD,
 
129
                                          NewBindings,
 
130
                                          io:parse_erl_exprs(FD,""),
 
131
                                          Translations,
 
132
                                          Dbg)
 
133
            end;
 
134
        {'EXIT',Reason} ->
 
135
            inviso_rt_lib:debug(Dbg,translate2runtime_funcs,[Exprs,Reason]),
 
136
            interpret_cmd_files_2(FD,Bindings,io:parse_erl_exprs(FD,""),Translations,Dbg)
 
137
    end;
 
138
interpret_cmd_files_2(FD,Bindings,{error,ErrorInfo,Line},Translations,Dbg) ->
 
139
    inviso_rt_lib:debug(Dbg,parse_erl_exprs,[ErrorInfo,Line]),
 
140
    interpret_cmd_files_2(FD,Bindings,io:parse_erl_exprs(FD,""),Translations,Dbg);
 
141
interpret_cmd_files_2(_,_,{eof,_},_,_) ->    % End of file.
 
142
    true.
 
143
%% -----------------------------------------------------------------------------
 
144
 
 
145
 
 
146
%% -----------------------------------------------------------------------------
 
147
%% Help functions working on the options given as argument to init during spawn.
 
148
%% -----------------------------------------------------------------------------
 
149
 
 
150
get_tracerdata_opts(ArgsFromConfig) ->
 
151
    case lists:keysearch(tracerdata,1,ArgsFromConfig) of
 
152
        {value,{_,TracerData}} ->
 
153
            {ok,TracerData};
 
154
        false ->
 
155
            false
 
156
    end.
 
157
%% -----------------------------------------------------------------------------
 
158
 
 
159
get_cmdfiles_opts(ArgsFromConfig) ->
 
160
    case lists:keysearch(cmdfiles,1,ArgsFromConfig) of
 
161
        {value,{_,CmdFiles}} ->
 
162
            {ok,CmdFiles};
 
163
        false ->
 
164
            false
 
165
    end.
 
166
%% -----------------------------------------------------------------------------
 
167
 
 
168
get_initialbindings_opts(ArgsFromConfig) ->
 
169
    case lists:keysearch(bindings,1,ArgsFromConfig) of
 
170
        {value,{_,Bindings}} ->
 
171
            Bindings;
 
172
        false ->                            % Then we use empty bindings.
 
173
            erl_eval:new_bindings()
 
174
    end.
 
175
%% -----------------------------------------------------------------------------
 
176
 
 
177
get_translations_opts(ArgsFromConfig) ->
 
178
    case lists:keysearch(translations,1,ArgsFromConfig) of
 
179
        {value,{_,Translations}} ->
 
180
            Translations;
 
181
        false ->                            % This becomes nearly point less.
 
182
            []
 
183
    end.
 
184
%% -----------------------------------------------------------------------------
 
185
 
 
186
get_dbg_opts(ArgsFromConfig) ->
 
187
    case lists:keysearch(debug,1,ArgsFromConfig) of
 
188
        {value,{_,DbgLevel}} ->
 
189
            DbgLevel;
 
190
        false ->
 
191
            off
 
192
    end.
 
193
%% -----------------------------------------------------------------------------
 
194
 
 
195
%% EOF
 
196
 
 
197
 
 
198