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

« back to all changes in this revision

Viewing changes to lib/megaco/examples/meas/megaco_codec_mstone2.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
%%----------------------------------------------------------------------
 
19
%% 
 
20
%% megaco_codec_mstone2:start().
 
21
%% 
 
22
%%----------------------------------------------------------------------
 
23
%% Purpose: mstone 2 measurement
 
24
%%          This module implement a simple performence measurment case.
 
25
%%          The architecture is as followes:
 
26
%%          - One loader process: 
 
27
%%            It keeps a list of all codec combinations, including
 
28
%%            all the messages (in a list) for each codec. 
 
29
%%            Initially it creates a timer (finished) (circa 10 minutes). 
 
30
%%            It spawns a worker process 
 
31
%%            for each codec config (it also creates a monitor to each
 
32
%%            process so it knows when they exit). When the result comes 
 
33
%%            in from a process (in the form of a DOWN message), spawns 
 
34
%%            a new worker process for this codec config and update's 
 
35
%%            the statistics.
 
36
%%            When the finished timer expires, it will stop respawing
 
37
%%            the worker processes, and instead just wait for them all
 
38
%%            to finish. 
 
39
%%            The test is finished by printing the statistics.
 
40
%%          - A worker process for each codec combination.
 
41
%%            This process is spawned by the loader process. It receives
 
42
%%            at start a list of messages. It shall decode and then 
 
43
%%            encode each message. When all messages has been processed
 
44
%%            it exits (normally).
 
45
%%----------------------------------------------------------------------
 
46
 
 
47
-module(megaco_codec_mstone2).
 
48
 
 
49
 
 
50
%% Exports
 
51
-export([start/0]).
 
52
 
 
53
 
 
54
%%%----------------------------------------------------------------------
 
55
%%% Macros
 
56
%%%----------------------------------------------------------------------
 
57
 
 
58
-define(LIB, megaco_codec_mstone_lib).
 
59
 
 
60
-ifndef(MSTONE_TIME).
 
61
-define(MSTONE_TIME, 10).
 
62
-endif.
 
63
-define(MSTONE_RUN_TIME, timer:minutes(?MSTONE_TIME)).
 
64
 
 
65
-ifndef(MSTONE_VERSION3).
 
66
-define(MSTONE_VERSION3, prev3c).
 
67
-endif.
 
68
-define(VERSION3, ?MSTONE_VERSION3).
 
69
 
 
70
-ifndef(MSTONE_CODECS).
 
71
-define(MSTONE_CODECS, [pretty, compact, per, ber, erlang]).
 
72
-endif.
 
73
 
 
74
-ifndef(MSTONE_RUNNER_MIN_HEAP_SZ).
 
75
%% -define(MSTONE_RUNNER_MIN_HEAP_SZ,  16#7fff).
 
76
-define(MSTONE_RUNNER_MIN_HEAP_SZ,  16#ffff).
 
77
%% -define(MSTONE_RUNNER_MIN_HEAP_SZ, 16#17ffe).
 
78
%% -define(MSTONE_RUNNER_MIN_HEAP_SZ, 16#1ffff).
 
79
%% -define(MSTONE_RUNNER_OPTS, [link]).
 
80
-endif.
 
81
-define(MSTONE_RUNNER_OPTS, 
 
82
        [link, {min_heap_size, ?MSTONE_RUNNER_MIN_HEAP_SZ}]).
 
83
 
 
84
 
 
85
%%%----------------------------------------------------------------------
 
86
%%% Records
 
87
%%%----------------------------------------------------------------------
 
88
 
 
89
-record(codec_data, {ref, mod, config = [], msgs = []}).
 
90
 
 
91
-record(state, {timer, running = [], idle = [], flex_handler, flex_conf}).
 
92
 
 
93
 
 
94
%%%----------------------------------------------------------------------
 
95
%%% API
 
96
%%%----------------------------------------------------------------------
 
97
 
 
98
start() ->
 
99
    io:format("~n", []),
 
100
    ?LIB:display_os_info(),
 
101
    ?LIB:display_system_info(),
 
102
    ?LIB:display_app_info(),
 
103
    io:format("~n", []),
 
104
    Ref = erlang:monitor(process, spawn(fun() -> loader() end)),
 
105
    receive
 
106
        {'DOWN', Ref, process, _Pid, {done, Result}} ->
 
107
            display_result(Result);
 
108
        {'DOWN', Ref, process, _Pid, Result} ->
 
109
            io:format("Unexpected result:~n~p~n", [Result]),
 
110
            ok
 
111
    end.
 
112
 
 
113
 
 
114
%%%----------------------------------------------------------------------
 
115
%%% Internal functions
 
116
%%%----------------------------------------------------------------------
 
117
 
 
118
display_result(Result) ->
 
119
    {value, {worker_cnt, WC}} = lists:keysearch(worker_cnt, 1, Result),
 
120
    CodecStat = 
 
121
        [{Mod, Conf, Cnt} || {{codec_cnt, Mod, Conf}, Cnt} <- Result],
 
122
    MStone = lists:sum([Cnt || {_, _, Cnt} <- CodecStat]),
 
123
    io:format("Number of procs spawned: ~w~n"
 
124
              "MStone:                  ~w~n"
 
125
              "~n", [WC, MStone]),
 
126
    display_worker_result(lists:keysort(3, CodecStat)),
 
127
    ok.
 
128
    
 
129
display_worker_result([]) ->
 
130
    io:format("~n", []);
 
131
display_worker_result([{Mod, Conf, Cnt}|Res]) ->
 
132
    io:format("~s: ~w~n", [image_of(Mod, Conf), Cnt]),
 
133
    display_worker_result(Res).
 
134
 
 
135
image_of(megaco_per_bin_encoder, Conf) ->
 
136
    bin_image("per_bin", Conf);
 
137
image_of(megaco_ber_bin_encoder, Conf) ->
 
138
    bin_image("ber_bin", Conf);
 
139
image_of(megaco_pretty_text_encoder, Conf) ->
 
140
    text_image("pretty", Conf);
 
141
image_of(megaco_compact_text_encoder, Conf) ->
 
142
    text_image("compact", Conf);
 
143
image_of(megaco_erl_dist_encoder, Conf) ->
 
144
    erl_image("erl_dist", Conf).
 
145
 
 
146
bin_image(Bin, Conf) ->
 
147
    Drv = 
 
148
        case lists:member(driver, Conf) of
 
149
            true ->
 
150
                [driver];
 
151
            false ->
 
152
                []
 
153
        end,
 
154
    Nat = 
 
155
        case lists:member(native, Conf) of
 
156
            true ->
 
157
                [native];
 
158
            false ->
 
159
                []
 
160
        end,
 
161
    io_lib:format("~s ~w", [Bin, Drv ++ Nat]).
 
162
 
 
163
text_image(Txt, Conf) ->
 
164
    Flex = 
 
165
        case lists:keysearch(flex, 1, Conf) of
 
166
            false ->
 
167
                [];
 
168
            _ ->
 
169
                [flex]
 
170
        end,
 
171
    io_lib:format("~s ~w", [Txt, Flex]).
 
172
 
 
173
erl_image(Erl, Conf) ->
 
174
    MC = 
 
175
        case lists:member(megaco_compressed, Conf) of
 
176
            true ->
 
177
                [megaco_compressed];
 
178
            false ->
 
179
                []
 
180
        end,
 
181
    C = 
 
182
        case lists:member(compressed, Conf) of
 
183
            true ->
 
184
                [compressed];
 
185
            false ->
 
186
                []
 
187
        end,
 
188
    io_lib:format("~s ~w", [Erl, MC ++ C]).
 
189
    
 
190
 
 
191
%%%----------------------------------------------------------------------
 
192
 
 
193
loader() ->
 
194
    loader(?MSTONE_CODECS).
 
195
 
 
196
 
 
197
%% Dirs is a list of directories containing files,
 
198
%% each with a single megaco message. 
 
199
%%
 
200
%% Note that it is a requirement that each dir has
 
201
%% the name of the codec with which the messages has
 
202
%% been encoded: 
 
203
%%
 
204
%%    pretty | compact | ber | per | erlang
 
205
%%
 
206
 
 
207
loader(Dirs) ->
 
208
    process_flag(trap_exit, true),
 
209
    case (catch init(Dirs)) of
 
210
        {ok, State} ->
 
211
            loader_loop(running, State);
 
212
        Error ->
 
213
            exit(Error)
 
214
    end.
 
215
 
 
216
init(Dirs) ->
 
217
    ets:new(mstone, [set, private, named_table, {keypos, 1}]),
 
218
    ets:insert(mstone, {worker_cnt, 0}),
 
219
    {Pid, FlexConf} = ?LIB:start_flex_scanner(),
 
220
    io:format("read messages", []),
 
221
    CodecData = init_codec_data(?LIB:expand_dirs(Dirs), FlexConf),
 
222
    Timer = erlang:send_after(?MSTONE_RUN_TIME, self(), mstone_finished), 
 
223
    io:format("~n~n", []),
 
224
    {ok, #state{timer = Timer, 
 
225
                idle  = CodecData, 
 
226
                flex_handler = Pid, flex_conf = FlexConf}}.
 
227
 
 
228
init_codec_data(EDirs, FlexConf) ->
 
229
    [init_codec_data(MsgDir, Codec, Conf, FlexConf) || 
 
230
        {MsgDir, Codec, Conf} <- EDirs].
 
231
 
 
232
init_codec_data(MsgDir, Codec, Conf0, FlexConf) 
 
233
  when is_list(MsgDir) and is_atom(Codec) and is_list(Conf0) ->
 
234
    io:format(".", []),
 
235
    Conf = [{version3,?VERSION3}|init_codec_conf(FlexConf, Conf0)], 
 
236
    Msgs = [?LIB:detect_version(Codec, Conf, Bin) || 
 
237
               Bin <- ?LIB:read_messages(MsgDir)],
 
238
    ets:insert(mstone, {{codec_cnt, Codec, Conf}, 0}),
 
239
    #codec_data{mod = Codec, config = Conf, msgs = Msgs}.
 
240
 
 
241
init_codec_conf(FlexConf, [flex_scanner]) ->
 
242
    FlexConf;
 
243
init_codec_conf(_, Conf) ->
 
244
    Conf.
 
245
 
 
246
 
 
247
%% -- Main loop --
 
248
 
 
249
loader_loop(finishing, #state{flex_handler = Pid, running = []}) ->     
 
250
    %% we are done
 
251
    ?LIB:stop_flex_scanner(Pid),
 
252
    exit({done, lists:sort(ets:tab2list(mstone))});
 
253
 
 
254
loader_loop(finishing, State) ->
 
255
    receive
 
256
        {'DOWN', Ref, process, _Pid, {mstone_done, Codec, Conf, Cnt}} ->
 
257
            loader_loop(finishing, done_worker(Ref, Codec, Conf, Cnt, State))
 
258
    end;
 
259
 
 
260
loader_loop(running, #state{idle = []} = State) ->          
 
261
    receive
 
262
        mstone_finished ->
 
263
            loader_loop(finishing, State);
 
264
 
 
265
        {'DOWN', Ref, process, _Pid, {mstone_done, Codec, Conf, Cnt}} ->
 
266
            loader_loop(running, done_worker(Ref, Codec, Conf, Cnt, State))
 
267
    end;
 
268
 
 
269
loader_loop(running, State) ->  
 
270
    receive
 
271
        mstone_finished ->
 
272
            %% io:format("finishing~n", []),
 
273
            loader_loop(finishing, State);
 
274
 
 
275
        {'DOWN', Ref, process, _Pid, {mstone_done, Codec, Conf, Cnt}} ->
 
276
            State2 = done_worker(Ref, Codec, Conf, Cnt, State),
 
277
            loader_loop(running, State2)
 
278
 
 
279
    after 0 ->
 
280
            loader_loop(running, start_worker(State))
 
281
    end.
 
282
 
 
283
done_worker(Ref, Codec, Conf, Cnt,
 
284
            #state{running = Running, idle = Idle} = State) ->
 
285
    %% io:format("worker ~w ~w done~n", [Codec, Conf]),
 
286
    ets:update_counter(mstone, worker_cnt, 1),
 
287
    ets:update_counter(mstone, {codec_cnt, Codec, Conf}, Cnt),
 
288
    Running2 = lists:keydelete(Ref, #codec_data.ref, Running),
 
289
    CD = Running -- Running2,
 
290
    State#state{running = Running2, idle = lists:append(Idle, CD)}.
 
291
 
 
292
start_worker(#state{running = Running, idle = [H|T]} = State) ->
 
293
    #codec_data{mod = Codec, config = Conf, msgs = Msgs} = H,
 
294
    Worker = fun() -> worker(Codec, Conf, Msgs, 0) end, 
 
295
    Ref    = erlang:monitor(process, spawn(Worker)),
 
296
    CD = H#codec_data{ref = Ref},
 
297
    State#state{running = [CD | Running], idle = T}.
 
298
 
 
299
 
 
300
%%%----------------------------------------------------------------------
 
301
 
 
302
worker(Codec, Conf, [], Cnt) ->
 
303
    exit({mstone_done, Codec, Conf, Cnt});
 
304
worker(Codec, Conf, [{V, Msg}|Msgs], Cnt) ->
 
305
    work(Codec, Conf, V, Msg),
 
306
    worker(Codec, Conf, Msgs, Cnt + 1).
 
307
 
 
308
work(Codec, Conf, V, M) ->
 
309
    case (catch apply(Codec, decode_message, [Conf, V, M])) of
 
310
        {ok, Msg} ->
 
311
            case (catch apply(Codec, encode_message, [Conf, V, Msg])) of
 
312
                {ok, Bin} when is_binary(Bin) ->
 
313
                    ok;
 
314
                EncodeError ->
 
315
                    emsg("failed encoding message: ~n~p", [EncodeError]),
 
316
                    exit({mstone_worker_encode_failure, EncodeError})
 
317
            end;
 
318
        DecodeError ->
 
319
            emsg("failed decoding message: ~n~p", [DecodeError]),
 
320
            exit({mstone_worker_decode_failure, DecodeError})
 
321
    end.
 
322
    
 
323
 
 
324
 
 
325
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
326
 
 
327
emsg(F, A) ->
 
328
    error_logger:error_msg(F ++ "~n", A).
 
329
 
 
330