~rdoering/ubuntu/intrepid/erlang/fix-535090

« back to all changes in this revision

Viewing changes to lib/runtime_tools/src/inviso_autostart_server.erl

  • Committer: Bazaar Package Importer
  • Author(s): Soren Hansen
  • Date: 2007-05-01 16:57:10 UTC
  • mfrom: (1.1.9 upstream)
  • Revision ID: james.westby@ubuntu.com-20070501165710-2sapk0hp2gf3o0ip
Tags: 1:11.b.4-2ubuntu1
* Merge with Debian Unstable. Remaining changes:
  - Add -fno-stack-protector to fix broken crypto_drv.
* DebianMaintainerField update.

Show diffs side-by-side

added added

removed removed

Lines of Context:
20
20
-module(inviso_autostart_server).
21
21
-export([init/1]).
22
22
 
 
23
%% -----------------------------------------------------------------------------
 
24
%% Internal exports
 
25
%% -----------------------------------------------------------------------------
 
26
-export([cmd_file_interpreter_init/4]).
 
27
%% -----------------------------------------------------------------------------
 
28
 
 
29
 
23
30
%% This module provides a (well working) example of how to program an
24
31
%% autostart server responsible for initializing trace, setting patterns
25
32
%% and flags.
26
33
%%
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.
 
34
%% The general idea is that this code spawns interpreter processes in order to
 
35
%% execute commands concurrently. Each of the interpreter processes opens one or
 
36
%% several files (in sequence) containing erlang function calls which are evaluated
 
37
%% in the interpreter process context.
29
38
%% The argument provided to init shall be a list of options controlling
30
39
%% how to initialize tracing, which file(s) to open and variable bindings.
31
40
%%
32
 
%% This autostart_server understands standard inviso trace case files.
 
41
%% This autostart_server interpreters understands standard inviso trace case files.
 
42
%%
33
43
%% 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.
 
44
%% by the control component. It is therefore easy to translate inviso calls to
 
45
%% inviso_rt calls.
 
46
%%
 
47
%% This process may be killed by the inviso_rt process if stop_tracing is called.
 
48
%% The reason is that there is no time limit to the interpreter processes. Hence
 
49
%% they should be killed if tracing is not possible anylonger.
41
50
%% =============================================================================
42
51
 
43
52
 
52
61
%%     ServerParam={tracerdata,TracerData}|{cmdfiles,Files}|{bindings,Bindings}|
53
62
%%       {translations,Translations}|{debug,DbgLevel}
54
63
%%       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.
 
64
%%       Files=[FileNameSpecs,...] where each FileNameSpecs will be executed in
 
65
%%         a separate process. Making each FileNameSpec parallel.
 
66
%%         FileNameSpecs=[FileNameSpec,...]
 
67
%%           FileNameSpec=FileName | {FileName,Bindings}
57
68
%%       Bindings=[{Var,Value},...] variable environment understood by
58
69
%%         erl_eval:exprs/2.
59
70
%%       Translations=[Translation,...]
63
74
%%           ParamMF={M,F} | any()
64
75
%%           Translates Mod:Func/Arity to Mod2:Func2 with the arguments to
65
76
%%             Mod:Func translated using M:F/1. Note that ParamMF is not
66
 
%%             necessarily an MF. If no translation shall be done, ParamFun
 
77
%%             necessarily an MF. If no translation shall be done, ParamMF
67
78
%%             shall be anything else but an MF.
68
79
%%           Also note that Mod is optional in a Translation. That means that
69
80
%%           function calls without a module in the trace case file will
78
89
                            Bindings=get_initialbindings_opts(ArgsFromConfig),
79
90
                            Translations=get_translations_opts(ArgsFromConfig),
80
91
                            Dbg=get_dbg_opts(ArgsFromConfig),
81
 
                            interpret_cmd_files(CmdFiles,
82
 
                                                Bindings,
83
 
                                                Translations,
84
 
                                                Dbg);
 
92
                            Procs=start_cmd_file_interpreters(CmdFiles,
 
93
                                                              Bindings,
 
94
                                                              Translations,
 
95
                                                              Dbg),
 
96
                            loop(Procs,Dbg); % Wait for procs to be done.
85
97
                        false ->            % Then we can terminate normally.
86
98
                            true
87
99
                    end;
93
105
    end.
94
106
%% -----------------------------------------------------------------------------
95
107
 
96
 
interpret_cmd_files([FileName|Rest],Bindings,Translations,Dbg) ->
 
108
%% Help function which starts a process for each item found in the FileNames
 
109
%% list. The idea is that each item will be processed concurrently. The items
 
110
%% them selves may be a sequence of filenames.
 
111
%% Returns a list of spawned interpret processes.
 
112
start_cmd_file_interpreters([FileNames|Rest],Bindings,Translations,Dbg) ->
 
113
    P=spawn_link(?MODULE,cmd_file_interpreter_init,[FileNames,Bindings,Translations,Dbg]),
 
114
    MRef=erlang:monitor(process,P),         % Can't trap exits in this process.
 
115
    [{P,MRef}|start_cmd_file_interpreters(Rest,Bindings,Translations,Dbg)];
 
116
start_cmd_file_interpreters([],_,_,_) ->
 
117
    [].
 
118
%% -----------------------------------------------------------------------------
 
119
 
 
120
 
 
121
%% The loop where this process simply waits for all of the interpreters to be
 
122
%% done. Note that that may take som time. An interpreter may take as long time
 
123
%% necessary to do its task.
 
124
loop(Procs,Dbg) ->
 
125
    receive
 
126
        {'DOWN',MRef,process,Pid,_Reason} ->
 
127
            case lists:keysearch(MRef,1,Procs) of
 
128
                {value,{Pid,_}} ->          % It was an interpreter that terminated.
 
129
                    case lists:keydelete(MRef,1,Procs) of
 
130
                        [] ->               % No more interpreters.
 
131
                            true;           % Then terminate.
 
132
                        NewProcs ->
 
133
                            loop(NewProcs,Dbg)
 
134
                    end;
 
135
                false ->
 
136
                    loop(Procs,Dbg)
 
137
            end;
 
138
        _ ->
 
139
            loop(Procs,Dbg)
 
140
    end.
 
141
 
 
142
 
 
143
%% -----------------------------------------------------------------------------
 
144
%% The interpret process.
 
145
%%
 
146
%% An interpreter process executes trace case files. Several interpreter processes
 
147
%% may be running in parallel. It is not within the scoop of this implementation
 
148
%% of an autostart server to solve conflicts. (You may implement your own autostart
 
149
%% server!).
 
150
%% An interpret process may run for as long as necessary. Hence the function called
 
151
%% within the trace case file can contain wait functions, waiting for a certain
 
152
%% system state to occure before continuing.
 
153
%% Note that this process also mixes global and local bindings. GlobalBindings
 
154
%% is a binding() structure, where LocalBindings is a list of {Var,Value}.
 
155
%% Further it is possible to let FileName be a {inviso,Func,Args} tuple instead.
 
156
%% -----------------------------------------------------------------------------
 
157
 
 
158
%% Init function for an interpreter process instance.
 
159
cmd_file_interpreter_init(FileNames,GlobalBindings,Translations,Dbg) ->
 
160
    interpret_cmd_files(FileNames,GlobalBindings,Translations,Dbg).
 
161
 
 
162
interpret_cmd_files([{FileName,LocalBindings}|Rest],GlobalBindings,Translations,Dbg) ->
 
163
    Bindings=join_local_and_global_vars(LocalBindings,GlobalBindings),
 
164
    interpret_cmd_files_1(FileName,Bindings,Translations,Dbg),
 
165
    interpret_cmd_files(Rest,GlobalBindings,Translations,Dbg);
 
166
interpret_cmd_files([FileName|Rest],GlobalBindings,Translations,Dbg) ->
 
167
    interpret_cmd_files_1(FileName,GlobalBindings,Translations,Dbg),
 
168
    interpret_cmd_files(Rest,GlobalBindings,Translations,Dbg);
 
169
interpret_cmd_files([],_,_,_) ->            % Done, return nothing significant!
 
170
    true.
 
171
 
 
172
%% This is "inline" inviso calls.
 
173
interpret_cmd_files_1({inviso,F,Args},Bindings,Translations,Dbg) ->
 
174
    {ok,Tokens1,_}=erl_scan:string("inviso:"++atom_to_list(F)++"("),
 
175
    Tokens2=tokenize_args(Args),
 
176
    {ok,Tokens3,_}=erl_scan:string(")."),
 
177
    case erl_parse:parse_exprs(Tokens1++Tokens2++Tokens3) of
 
178
        {ok,Exprs} ->
 
179
            interpret_cmd_files_3(Bindings,Exprs,Translations,Dbg);
 
180
        {error,_Reason} ->
 
181
            error
 
182
    end;
 
183
%% This is the case when it actually is a trace case file.
 
184
interpret_cmd_files_1(FileName,Bindings,Translations,Dbg) ->
97
185
    case file:open(FileName,[read]) of
98
186
        {ok,FD} ->
99
187
            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!
 
188
            file:close(FD);
102
189
        {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.
 
190
            inviso_rt_lib:debug(Dbg,interpret_cmd_files,[FileName,{error,Reason}])
 
191
    end.
108
192
 
109
193
%% Help function which handles Exprs returned from io:parse_erl_exprs and
110
194
%% tries to eval them. It is the side-effects we are interested in, like
114
198
%% corresponding runtime component calls.
115
199
%% Returns nothing significant.
116
200
interpret_cmd_files_2(FD,Bindings,{ok,Exprs,_},Translations,Dbg) ->
 
201
    {next,NewBindings}=interpret_cmd_files_3(Bindings,Exprs,Translations,Dbg),
 
202
    interpret_cmd_files_2(FD,NewBindings,io:parse_erl_exprs(FD,""),Translations,Dbg);
 
203
interpret_cmd_files_2(FD,Bindings,{error,ErrorInfo,Line},Translations,Dbg) ->
 
204
    inviso_rt_lib:debug(Dbg,parse_erl_exprs,[ErrorInfo,Line]),
 
205
    interpret_cmd_files_2(FD,Bindings,io:parse_erl_exprs(FD,""),Translations,Dbg);
 
206
interpret_cmd_files_2(_,_,{eof,_},_,_) ->    % End of file.
 
207
    true.
 
208
 
 
209
interpret_cmd_files_3(Bindings,Exprs,Translations,Dbg) ->
117
210
    case catch inviso_rt_lib:transform(Exprs,Translations) of
118
211
        NewExprs when list(NewExprs) ->     % We may have translated the API.
119
212
            case catch erl_eval:exprs(NewExprs,Bindings) of
120
213
                {'EXIT',Reason} ->
121
214
                    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);
 
215
                    {next,Bindings};
127
216
                {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)
 
217
                    {next,NewBindings}
133
218
            end;
134
219
        {'EXIT',Reason} ->
135
220
            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.
 
221
            {next,Bindings}
 
222
    end.
 
223
 
 
224
%% Help function adding variables to a bindings structure. If the variable already
 
225
%% is assigned in the structure, it will be overridden. Returns a new
 
226
%% bindings structure.
 
227
join_local_and_global_vars([{Var,Val}|Rest],Bindings) when atom(Var) ->
 
228
    join_local_and_global_vars(Rest,erl_eval:add_binding(Var,Val,Bindings));
 
229
join_local_and_global_vars([_|Rest],Bindings) ->
 
230
    join_local_and_global_vars(Rest,Bindings);
 
231
join_local_and_global_vars([],Bindings) ->
 
232
    Bindings.
 
233
 
 
234
%% Help function returning a string of tokens, including "," separation
 
235
%% between the arguments.
 
236
tokenize_args(Args=[Arg|Rest]) when length(Args)>1 ->
 
237
    AbsTerm=erl_parse:abstract(Arg),
 
238
    Tokens=erl_parse:tokens(AbsTerm),
 
239
    {ok,Token,_}=erl_scan:string(","),
 
240
    Tokens++Token++tokenize_args(Rest);
 
241
tokenize_args([Arg]) ->
 
242
    AbsTerm=erl_parse:abstract(Arg),
 
243
    erl_parse:tokens(AbsTerm);
 
244
tokenize_args([]) ->
 
245
    "".
143
246
%% -----------------------------------------------------------------------------
144
247
 
145
248