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

« back to all changes in this revision

Viewing changes to lib/megaco/examples/meas/megaco_codec_mstone_lib.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
 
%%<copyright>
2
 
%% <year>2006-2007</year>
3
 
%% <holder>Ericsson AB, All Rights Reserved</holder>
4
 
%%</copyright>
5
 
%%<legalnotice>
 
1
%%
 
2
%% %CopyrightBegin%
 
3
%% 
 
4
%% Copyright Ericsson AB 2006-2009. All Rights Reserved.
 
5
%% 
6
6
%% The contents of this file are subject to the Erlang Public License,
7
7
%% Version 1.1, (the "License"); you may not use this file except in
8
8
%% compliance with the License. You should have received a copy of the
9
9
%% Erlang Public License along with this software. If not, it can be
10
10
%% retrieved online at http://www.erlang.org/.
11
 
%%
 
11
%% 
12
12
%% Software distributed under the License is distributed on an "AS IS"
13
13
%% basis, WITHOUT WARRANTY OF ANY KIND, either express or implied. See
14
14
%% the License for the specific language governing rights and limitations
15
15
%% under the License.
 
16
%% 
 
17
%% %CopyrightEnd%
16
18
%%
17
 
%% The Initial Developer of the Original Code is Ericsson AB.
18
 
%%</legalnotice>
 
19
 
19
20
%%
20
21
%%----------------------------------------------------------------------
21
22
%% Purpose: Misc utility functions for the mstone modules
30
31
         expand_dirs/2,
31
32
         display_os_info/0, 
32
33
         display_system_info/0, 
 
34
         display_alloc_info/0, 
33
35
         display_app_info/0,
34
36
         detect_version/3]).
35
37
 
127
129
 
128
130
%%----------------------------------------------------------------------
129
131
%% 
 
132
%% D i s p l a y   A l l o c a t o r   I n f o 
 
133
%% 
 
134
%%----------------------------------------------------------------------
 
135
 
 
136
display_alloc_info() ->
 
137
    io:format("Allocator memory information:~n", []),
 
138
    AllocInfo = alloc_info(),
 
139
    display_alloc_info(AllocInfo).
 
140
 
 
141
display_alloc_info([]) ->
 
142
    ok;
 
143
display_alloc_info([{Alloc, Mem}|AllocInfo]) ->
 
144
    io:format("  ~15w: ~10w~n", [Alloc, Mem]),
 
145
    display_alloc_info(AllocInfo).
 
146
 
 
147
alloc_info() ->
 
148
    case erlang:system_info(allocator) of
 
149
        {_Allocator, _Version, Features, _Settings} ->
 
150
            alloc_info(Features);
 
151
        _ ->
 
152
            []
 
153
    end.
 
154
 
 
155
alloc_info(Allocators) ->
 
156
    Allocs = [temp_alloc, sl_alloc, std_alloc, ll_alloc, eheap_alloc,
 
157
              ets_alloc, binary_alloc, driver_alloc],
 
158
    alloc_info(Allocators, Allocs, []).
 
159
 
 
160
alloc_info([], _, Acc) ->
 
161
    lists:reverse(Acc);
 
162
alloc_info([Allocator | Allocators], Allocs, Acc) ->
 
163
    case lists:member(Allocator, Allocs) of
 
164
        true ->
 
165
            Instances0 = erlang:system_info({allocator, Allocator}),
 
166
            Instances =
 
167
                if
 
168
                    is_list(Instances0) ->
 
169
                        [Instance || Instance <- Instances0,
 
170
                                     element(1, Instance) =:= instance];
 
171
                    true ->
 
172
                        []
 
173
                end,
 
174
            AllocatorMem = alloc_mem_info(Instances),
 
175
            alloc_info(Allocators, Allocs, [{Allocator, AllocatorMem} | Acc]);
 
176
 
 
177
        false ->
 
178
            alloc_info(Allocators, Allocs, Acc)
 
179
    end.
 
180
 
 
181
 
 
182
alloc_mem_info(Instances) ->
 
183
    alloc_mem_info(Instances, []).
 
184
 
 
185
alloc_mem_info([], Acc) ->
 
186
    lists:sum([Mem || {instance, _, Mem} <- Acc]);
 
187
alloc_mem_info([{instance, N, Info}|Instances], Acc) ->
 
188
    InstanceMemInfo = alloc_instance_mem_info(Info),
 
189
    alloc_mem_info(Instances, [{instance, N, InstanceMemInfo} | Acc]).
 
190
 
 
191
alloc_instance_mem_info(InstanceInfo) ->
 
192
    MBCS = alloc_instance_mem_info(mbcs, InstanceInfo),
 
193
    SBCS = alloc_instance_mem_info(sbcs, InstanceInfo),
 
194
    MBCS + SBCS.
 
195
 
 
196
alloc_instance_mem_info(Key, InstanceInfo) ->
 
197
    case lists:keysearch(Key, 1, InstanceInfo) of
 
198
        {value, {Key, Info}} ->
 
199
            case lists:keysearch(blocks_size, 1, Info) of
 
200
                {value, {blocks_size, Mem, _, _}} ->
 
201
                    Mem;
 
202
                _ ->
 
203
                    0
 
204
            end;
 
205
        _ ->
 
206
            0
 
207
    end.
 
208
 
 
209
 
 
210
%%----------------------------------------------------------------------
 
211
%% 
130
212
%% D i s p l a y   A p p   I n f o 
131
213
%% 
132
214
%%----------------------------------------------------------------------
145
227
    AI = megaco_ber_bin_drv_media_gateway_control_v1:info(),
146
228
    Vsn = 
147
229
        case lists:keysearch(vsn, 1, AI) of
148
 
            {value, {vsn, V}} when atom(V) ->
 
230
            {value, {vsn, V}} when is_atom(V) ->
149
231
                atom_to_list(V);
150
 
            {value, {vsn, V}} when list(V) ->
 
232
            {value, {vsn, V}} when is_list(V) ->
151
233
                V;
152
234
            _ ->
153
235
                "unknown"
166
248
 
167
249
expand_dirs([], _, EDirs) ->
168
250
    lists:reverse(lists:flatten(EDirs));
169
 
expand_dirs([Dir|Dirs], DrvInclude, EDirs) when atom(Dir) ->
 
251
expand_dirs([Dir|Dirs], DrvInclude, EDirs) when is_atom(Dir) ->
170
252
    EDir = expand_dir(atom_to_list(Dir), DrvInclude),
171
253
    expand_dirs(Dirs, DrvInclude, [EDir|EDirs]);
172
 
expand_dirs([Dir|Dirs], DrvInclude, EDirs) when list(Dir) ->
 
254
expand_dirs([Dir|Dirs], DrvInclude, EDirs) when is_list(Dir) ->
173
255
    EDir = expand_dir(Dir, DrvInclude),
174
256
    expand_dirs(Dirs, DrvInclude, [EDir|EDirs]).
175
257
 
 
258
expand_dir(Dir, flex) ->
 
259
    case Dir of
 
260
        "pretty" ->
 
261
            [{Dir, megaco_pretty_text_encoder, [flex_scanner]},
 
262
             {Dir, megaco_pretty_text_encoder, [flex_scanner]},
 
263
             {Dir, megaco_pretty_text_encoder, [flex_scanner]},
 
264
             {Dir, megaco_pretty_text_encoder, [flex_scanner]},
 
265
             {Dir, megaco_pretty_text_encoder, [flex_scanner]},
 
266
             {Dir, megaco_pretty_text_encoder, [flex_scanner]},
 
267
             {Dir, megaco_pretty_text_encoder, [flex_scanner]},
 
268
             {Dir, megaco_pretty_text_encoder, [flex_scanner]}];
 
269
        "compact" ->
 
270
            [{Dir, megaco_compact_text_encoder, [flex_scanner]},
 
271
             {Dir, megaco_compact_text_encoder, [flex_scanner]},
 
272
             {Dir, megaco_compact_text_encoder, [flex_scanner]},
 
273
             {Dir, megaco_compact_text_encoder, [flex_scanner]},
 
274
             {Dir, megaco_compact_text_encoder, [flex_scanner]},
 
275
             {Dir, megaco_compact_text_encoder, [flex_scanner]},
 
276
             {Dir, megaco_compact_text_encoder, [flex_scanner]},
 
277
             {Dir, megaco_compact_text_encoder, [flex_scanner]}];
 
278
        "ber" ->
 
279
            [];
 
280
        "per" ->
 
281
            [];
 
282
        "erlang" ->
 
283
            [];
 
284
        Else ->
 
285
            error({invalid_codec, Else})
 
286
    end;
176
287
expand_dir(Dir, only_drv) ->
177
288
    case Dir of
178
289
        "pretty" ->
286
397
            error({file_empty, FileName});
287
398
 
288
399
        {ok, #file_info{type = Type}} ->
289
 
            error({invalid_type, Type, FileName});
 
400
            error({invalid_type, FileName, Type});
290
401
 
291
402
        {ok, Info} ->
292
 
            error({unexpected_file_info, Info, FileName});
 
403
            error({unexpected_file_info, FileName, Info});
293
404
 
294
405
        Error ->
295
 
            error({failed_reading_file_info, Error})
 
406
            error({failed_reading_file_info, File, Error})
296
407
 
297
408
    end.
298
409
 
302
413
        {ok, Files} ->
303
414
            lists:sort(Files);
304
415
        Error ->
305
 
            error({failed_listing_dir, Error})
 
416
            error({failed_listing_dir, Dir, Error})
306
417
    end.
307
418
 
308
419
 
340
451
 
341
452
flex_scanner_handler(Pid) ->
342
453
    case (catch megaco_flex_scanner:start()) of
343
 
        {ok, Port} when port(Port) ->
 
454
        {ok, Port} when is_port(Port) ->
344
455
            Pid ! {flex_scanner_started, self(), {flex, Port}},
345
456
            flex_scanner_handler(Pid, Port);
346
457
        {error, {load_driver, {open_error, Reason}}} ->