~clint-fewbar/ubuntu/precise/erlang/merge-15b

« back to all changes in this revision

Viewing changes to lib/diameter/test/diameter_util.erl

  • Committer: Package Import Robot
  • Author(s): Sergei Golovan
  • Date: 2011-12-15 19:20:10 UTC
  • mfrom: (1.1.18) (3.5.15 sid)
  • mto: (3.5.16 sid)
  • mto: This revision was merged to the branch mainline in revision 33.
  • Revision ID: package-import@ubuntu.com-20111215192010-jnxcfe3tbrpp0big
Tags: 1:15.b-dfsg-1
* New upstream release.
* Upload to experimental because this release breaks external drivers
  API along with ABI, so several applications are to be fixed.
* Removed SSL patch because the old SSL implementation is removed from
  the upstream distribution.
* Removed never used patch which added native code to erlang beam files.
* Removed the erlang-docbuilder binary package because the docbuilder
  application was dropped by upstream.
* Documented dropping ${erlang-docbuilder:Depends} substvar in
  erlang-depends(1) manpage.
* Made erlang-base and erlang-base-hipe provide virtual package
  erlang-abi-15.b (the number means the first erlang version, which
  provides current ABI).

Show diffs side-by-side

added added

removed removed

Lines of Context:
 
1
%%
 
2
%% %CopyrightBegin%
 
3
%%
 
4
%% Copyright Ericsson AB 2010-2011. All Rights Reserved.
 
5
%%
 
6
%% The contents of this file are subject to the Erlang Public License,
 
7
%% Version 1.1, (the "License"); you may not use this file except in
 
8
%% compliance with the License. You should have received a copy of the
 
9
%% Erlang Public License along with this software. If not, it can be
 
10
%% retrieved online at http://www.erlang.org/.
 
11
%%
 
12
%% Software distributed under the License is distributed on an "AS IS"
 
13
%% basis, WITHOUT WARRANTY OF ANY KIND, either express or implied. See
 
14
%% the License for the specific language governing rights and limitations
 
15
%% under the License.
 
16
%%
 
17
%% %CopyrightEnd%
 
18
%%
 
19
 
 
20
-module(diameter_util).
 
21
 
 
22
%%
 
23
%% Utility functions.
 
24
%%
 
25
 
 
26
%% generic
 
27
-export([consult/2,
 
28
         run/1,
 
29
         fold/3,
 
30
         foldl/3,
 
31
         scramble/1]).
 
32
 
 
33
%% diameter-specific
 
34
-export([lport/2,
 
35
         lport/3,
 
36
         listen/2, listen/3,
 
37
         connect/3, connect/4,
 
38
         disconnect/4]).
 
39
 
 
40
%% common_test-specific
 
41
-export([write_priv/3,
 
42
         read_priv/2,
 
43
         map_priv/3]).
 
44
 
 
45
-define(L, atom_to_list).
 
46
 
 
47
%% ---------------------------------------------------------------------------
 
48
%% consult/2
 
49
%%
 
50
%% Extract info from the app/appup file (presumably) of the named
 
51
%% application.
 
52
 
 
53
consult(Name, Suf)
 
54
  when is_atom(Name), is_atom(Suf) ->
 
55
    case code:lib_dir(Name, ebin) of
 
56
        {error = E, Reason} ->
 
57
            {E, {Name, Reason}};
 
58
        Dir ->
 
59
            consult(filename:join([Dir, ?L(Name) ++ "." ++ ?L(Suf)]))
 
60
    end.
 
61
 
 
62
consult(Path) ->
 
63
    case file:consult(Path) of
 
64
        {ok, Terms} ->
 
65
            Terms;
 
66
        {error, Reason} ->
 
67
            {error, {Path, Reason}}
 
68
    end.
 
69
%% Name/Path in the return value distinguish the errors and allow for
 
70
%% a useful badmatch.
 
71
 
 
72
%% ---------------------------------------------------------------------------
 
73
%% run/1
 
74
%%
 
75
%% Evaluate functions in parallel and return a list of those that
 
76
%% failed to return. The fun takes a boolean (did the function return
 
77
%% or not), the function that was evaluated, the return value or exit
 
78
%% reason and the prevailing accumulator.
 
79
 
 
80
run(L) ->
 
81
    fold(fun cons/4, [], L).
 
82
 
 
83
cons(true, _, _, Acc) ->
 
84
    Acc;
 
85
cons(false, F, RC, Acc) ->
 
86
    [{F, RC} | Acc].
 
87
 
 
88
%% ---------------------------------------------------------------------------
 
89
%% fold/3
 
90
%%
 
91
%% Parallel fold. Results are folded in the order received.
 
92
 
 
93
fold(Fun, Acc0, L)
 
94
  when is_function(Fun, 4) ->
 
95
    Ref = make_ref(),
 
96
    %% Spawn a middleman to collect down messages from processes
 
97
    %% spawned for each function so as not to assume that all DOWN
 
98
    %% messages are ours.
 
99
    MRef = run1([fun fold/4, Ref, Fun, Acc0, L], Ref),
 
100
    {Ref, RC} = down(MRef),
 
101
    RC.
 
102
 
 
103
fold(Ref, Fun, Acc0, L) ->
 
104
    recv(run(Ref, L), Ref, Fun, Acc0).
 
105
 
 
106
run(Ref, L) ->
 
107
    [{run1(F, Ref), F} || F <- L].
 
108
 
 
109
run1(F, Ref) ->
 
110
    {_, MRef} = spawn_monitor(fun() -> exit({Ref, eval(F)}) end),
 
111
    MRef.
 
112
 
 
113
recv([], _, _, Acc) ->
 
114
    Acc;
 
115
recv(L, Ref, Fun, Acc) ->
 
116
    {MRef, R} = down(),
 
117
    {MRef, F} = lists:keyfind(MRef, 1, L),
 
118
    recv(lists:keydelete(MRef, 1, L),
 
119
         Ref,
 
120
         Fun,
 
121
         acc(R, Ref, F, Fun, Acc)).
 
122
 
 
123
acc({Ref, RC}, Ref, F, Fun, Acc) ->
 
124
    Fun(true, F, RC, Acc);
 
125
acc(Reason, _, F, Fun, Acc) ->
 
126
    Fun(false, F, Reason, Acc).
 
127
 
 
128
down(MRef) ->
 
129
    receive {'DOWN', MRef, process, _, Reason} -> Reason end.
 
130
 
 
131
down() ->
 
132
    receive {'DOWN', MRef, process, _, Reason} -> {MRef, Reason} end.
 
133
 
 
134
%% ---------------------------------------------------------------------------
 
135
%% foldl/3
 
136
%%
 
137
%% Parallel fold. Results are folded in order of the function list.
 
138
 
 
139
foldl(Fun, Acc0, L)
 
140
  when is_function(Fun, 4) ->
 
141
    Ref = make_ref(),
 
142
    recvl(run(Ref, L), Ref, Fun, Acc0).
 
143
 
 
144
recvl([], _, _, Acc) ->
 
145
    Acc;
 
146
recvl([{MRef, F} | L], Ref, Fun, Acc) ->
 
147
    R = down(MRef),
 
148
    recvl(L, Ref, Fun, acc(R, Ref, F, Fun, Acc)).
 
149
 
 
150
%% ---------------------------------------------------------------------------
 
151
%% scramble/1
 
152
%%
 
153
%% Sort a list into random order.
 
154
 
 
155
scramble(L) ->
 
156
    foldl(fun(true, _, S, false) -> S end,
 
157
          false,
 
158
          [[fun s/1, L]]).
 
159
 
 
160
s(L) ->
 
161
    random:seed(now()),
 
162
    s([], L).
 
163
 
 
164
s(Acc, []) ->
 
165
    Acc;
 
166
s(Acc, L) ->
 
167
    {H, [T|Rest]} = lists:split(random:uniform(length(L)) - 1, L),
 
168
    s([T|Acc], H ++ Rest).
 
169
 
 
170
%% ---------------------------------------------------------------------------
 
171
%% eval/1
 
172
%%
 
173
%% Evaluate a function in one of a number of forms.
 
174
 
 
175
eval({M,[F|A]})
 
176
  when is_atom(F) ->
 
177
    apply(M,F,A);
 
178
 
 
179
eval({M,F,A}) ->
 
180
    apply(M,F,A);
 
181
 
 
182
eval([F|A])
 
183
  when is_function(F) ->
 
184
    apply(F,A);
 
185
 
 
186
eval(L)
 
187
  when is_list(L) ->
 
188
    run(L);
 
189
 
 
190
eval(F)
 
191
  when is_function(F,0) ->
 
192
    F().
 
193
 
 
194
%% ---------------------------------------------------------------------------
 
195
%% write_priv/3
 
196
%%
 
197
%% Write an arbitrary term to a named file.
 
198
 
 
199
write_priv(Config, Name, Term) ->
 
200
    write(path(Config, Name), Term).
 
201
 
 
202
write(Path, Term) ->
 
203
    ok = file:write_file(Path, term_to_binary(Term)).
 
204
 
 
205
%% read_priv/2
 
206
%%
 
207
%% Read a term from a file.
 
208
 
 
209
read_priv(Config, Name) ->
 
210
    read(path(Config, Name)).
 
211
 
 
212
read(Path) ->
 
213
    {ok, Bin} = file:read_file(Path),
 
214
    binary_to_term(Bin).
 
215
    
 
216
%% map_priv/3
 
217
%%
 
218
%% Modify a term in a file and return both old and new values.
 
219
 
 
220
map_priv(Config, Name, Fun1) ->
 
221
    map(path(Config, Name), Fun1).
 
222
 
 
223
map(Path, Fun1) ->
 
224
    T0 = read(Path),
 
225
    T1 = Fun1(T0),
 
226
    write(Path, T1),
 
227
    {T0, T1}.
 
228
 
 
229
path(Config, Name)
 
230
  when is_atom(Name) ->
 
231
    path(Config, ?L(Name));
 
232
path(Config, Name) ->
 
233
    Dir = proplists:get_value(priv_dir, Config),
 
234
    filename:join([Dir, Name]).
 
235
 
 
236
%% ---------------------------------------------------------------------------
 
237
%% lport/2-3
 
238
%%
 
239
%% Lookup the port number of a tcp/sctp listening transport.
 
240
 
 
241
lport(M, Ref) ->
 
242
    lport(M, Ref, 1).
 
243
 
 
244
lport(M, Ref, Tries) ->
 
245
    lp(tmod(M), Ref, Tries).
 
246
 
 
247
lp(M, Ref, T) ->
 
248
    L = [N || {listen, N, _} <- M:ports(Ref)],
 
249
    if [] /= L orelse T =< 1 ->
 
250
            L;
 
251
       true ->
 
252
            receive after 50 -> ok end,
 
253
            lp(M, Ref, T-1)
 
254
    end.
 
255
 
 
256
%% ---------------------------------------------------------------------------
 
257
%% listen/2-3
 
258
%%
 
259
%% Add a listening transport on the loopback address and a free port.
 
260
 
 
261
listen(SvcName, Prot) ->
 
262
    listen(SvcName, Prot, []).
 
263
 
 
264
listen(SvcName, Prot, Opts) ->
 
265
    add_transport(SvcName, {listen, opts(Prot, listen) ++ Opts}).
 
266
 
 
267
%% ---------------------------------------------------------------------------
 
268
%% connect/2-3
 
269
%%
 
270
%% Add a connecting transport on and connect to a listening transport
 
271
%% with the specified reference.
 
272
 
 
273
connect(Client, Prot, LRef) ->
 
274
    connect(Client, Prot, LRef, []).
 
275
 
 
276
connect(Client, Prot, LRef, Opts) ->
 
277
    [PortNr] = lport(Prot, LRef, 20),
 
278
    Ref = add_transport(Client, {connect, opts(Prot, PortNr) ++ Opts}),
 
279
    true = diameter:subscribe(Client),
 
280
    ok = receive
 
281
             {diameter_event, Client, {up, Ref, _, _, _}} -> ok
 
282
         after 2000 ->
 
283
                 {Client, Prot, PortNr, process_info(self(), messages)}
 
284
         end,
 
285
    Ref.
 
286
 
 
287
%% ---------------------------------------------------------------------------
 
288
%% disconnect/4
 
289
%%
 
290
%% Remove the client transport and expect the server transport to go
 
291
%% down.
 
292
 
 
293
disconnect(Client, Ref, Server, LRef) ->
 
294
    true = diameter:subscribe(Server),
 
295
    ok = diameter:remove_transport(Client, Ref),
 
296
    ok = receive
 
297
             {diameter_event, Server, {down, LRef, _, _}} -> ok
 
298
         after 2000 ->
 
299
                 {Client, Ref, Server, LRef, process_info(self(), messages)}
 
300
         end.
 
301
 
 
302
%% ---------------------------------------------------------------------------
 
303
 
 
304
-define(ADDR, {127,0,0,1}).
 
305
 
 
306
add_transport(SvcName, T) ->
 
307
    {ok, Ref} = diameter:add_transport(SvcName, T),
 
308
    Ref.
 
309
 
 
310
tmod(tcp) ->
 
311
    diameter_tcp;
 
312
tmod(sctp) ->
 
313
    diameter_sctp.
 
314
 
 
315
opts(Prot, T) ->
 
316
    [{transport_module, tmod(Prot)},
 
317
     {transport_config, [{ip, ?ADDR}, {port, 0} | opts(T)]}].
 
318
 
 
319
opts(listen) ->
 
320
    [];
 
321
opts(PortNr) ->
 
322
    [{raddr, ?ADDR}, {rport, PortNr}].