~ubuntu-branches/ubuntu/trusty/erlang/trusty

« back to all changes in this revision

Viewing changes to lib/inets/test/inets_test_lib.erl

  • Committer: Bazaar Package Importer
  • Author(s): Clint Byrum
  • Date: 2011-05-05 15:48:43 UTC
  • mfrom: (3.5.13 sid)
  • Revision ID: james.westby@ubuntu.com-20110505154843-0om6ekzg6m7ugj27
Tags: 1:14.b.2-dfsg-3ubuntu1
* Merge from debian unstable.  Remaining changes:
  - Drop libwxgtk2.8-dev build dependency. Wx isn't in main, and not
    supposed to.
  - Drop erlang-wx binary.
  - Drop erlang-wx dependency from -megaco, -common-test, and -reltool, they
    do not really need wx. Also drop it from -debugger; the GUI needs wx,
    but it apparently has CLI bits as well, and is also needed by -megaco,
    so let's keep the package for now.
  - debian/patches/series: Do what I meant, and enable build-options.patch
    instead.
* Additional changes:
  - Drop erlang-wx from -et
* Dropped Changes:
  - patches/pcre-crash.patch: CVE-2008-2371: outer level option with
    alternatives caused crash. (Applied Upstream)
  - fix for ssl certificate verification in newSSL: 
    ssl_cacertfile_fix.patch (Applied Upstream)
  - debian/patches/series: Enable native.patch again, to get stripped beam
    files and reduce the package size again. (build-options is what
    actually accomplished this)
  - Remove build-options.patch on advice from upstream and because it caused
    odd build failures.

Show diffs side-by-side

added added

removed removed

Lines of Context:
 
1
%%
 
2
%% %CopyrightBegin%
 
3
%%
 
4
%% Copyright Ericsson AB 2001-2010. 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(inets_test_lib).
 
21
 
 
22
-include("inets_test_lib.hrl").
 
23
-include_lib("inets/src/http_lib/http_internal.hrl").
 
24
 
 
25
%% Various small utility functions
 
26
-export([start_http_server/1, start_http_server/2]).
 
27
-export([start_http_server_ssl/1, start_http_server_ssl/2]).
 
28
-export([hostname/0]).
 
29
-export([connect_bin/3, connect_byte/3, send/3, close/2]).
 
30
-export([copy_file/3, copy_files/2, copy_dirs/2, del_dirs/1]).
 
31
-export([info/4, log/4, debug/4, print/4]).
 
32
-export([check_body/1]).
 
33
-export([millis/0, millis_diff/2, hours/1, minutes/1, seconds/1, sleep/1]).
 
34
-export([oscmd/1]).
 
35
-export([non_pc_tc_maybe_skip/4, os_based_skip/1]).
 
36
-export([flush/0]).
 
37
-export([start_node/1, stop_node/1]).
 
38
 
 
39
%% -- Misc os command and stuff
 
40
 
 
41
oscmd(Cmd) ->
 
42
  string:strip(os:cmd(Cmd), right, $\n).
 
43
 
 
44
%% -- Misc node operation wrapper functions --
 
45
 
 
46
start_node(Name) ->
 
47
    Pa   = filename:dirname(code:which(?MODULE)),
 
48
    Args = case init:get_argument('CC_TEST') of
 
49
               {ok, [[]]} ->
 
50
                   " -pa /clearcase/otp/libraries/snmp/ebin ";
 
51
               {ok, [[Path]]} ->
 
52
                   " -pa " ++ Path;
 
53
               error ->
 
54
                      ""
 
55
              end,
 
56
    A = Args ++ " -pa " ++ Pa,
 
57
    Opts = [{cleanup,false}, {args, A}],
 
58
    case (catch test_server:start_node(Name, slave, Opts)) of
 
59
        {ok, Node} ->
 
60
            Node;
 
61
        Else ->
 
62
            exit({failed_starting_node, Name, Else})
 
63
    end.
 
64
 
 
65
stop_node(Node) ->
 
66
    rpc:cast(Node, erlang, halt, []),
 
67
    await_stopped(Node, 5).
 
68
 
 
69
await_stopped(_, 0) ->
 
70
    ok;
 
71
await_stopped(Node, N) ->
 
72
    Nodes = erlang:nodes(),
 
73
    case lists:member(Node, Nodes) of
 
74
        true ->
 
75
            sleep(1000),
 
76
            await_stopped(Node, N-1);
 
77
        false ->
 
78
            ok
 
79
    end.
 
80
 
 
81
 
 
82
%% ----------------------------------------------------------------
 
83
%% HTTPD starter functions
 
84
%%
 
85
 
 
86
start_http_server(Conf) ->
 
87
    start_http_server(Conf, ?HTTP_DEFAULT_SSL_KIND).
 
88
 
 
89
start_http_server(Conf, essl = _SslTag) ->
 
90
    application:start(crypto), 
 
91
    do_start_http_server(Conf);
 
92
start_http_server(Conf, _SslTag) ->
 
93
    do_start_http_server(Conf).
 
94
 
 
95
do_start_http_server(Conf) ->
 
96
    tsp("start http server with "
 
97
        "~n   Conf: ~p"
 
98
        "~n", [Conf]),
 
99
    application:load(inets), 
 
100
    case application:set_env(inets, services, [{httpd, Conf}]) of
 
101
        ok ->
 
102
            case application:start(inets) of
 
103
                ok ->
 
104
                    ok;
 
105
                Error1 ->
 
106
                    test_server:format("<ERROR> Failed starting application: "
 
107
                                       "~n   Error: ~p"
 
108
                                       "~n", [Error1]),
 
109
                    Error1
 
110
            end;
 
111
        Error2 ->
 
112
            test_server:format("<ERROR> Failed set application env: "
 
113
                               "~n   Error: ~p"
 
114
                               "~n", [Error2]),
 
115
            Error2
 
116
    end.
 
117
            
 
118
start_http_server_ssl(FileName) ->
 
119
    start_http_server_ssl(FileName, ?HTTP_DEFAULT_SSL_KIND).
 
120
 
 
121
start_http_server_ssl(FileName, essl = _SslTag) ->
 
122
    application:start(crypto), 
 
123
    do_start_http_server_ssl(FileName);
 
124
start_http_server_ssl(FileName, _SslTag) ->
 
125
    do_start_http_server_ssl(FileName).
 
126
 
 
127
do_start_http_server_ssl(FileName) ->
 
128
    tsp("start (ssl) http server with "
 
129
        "~n   FileName: ~p"
 
130
        "~n", [FileName]),
 
131
    application:start(ssl),            
 
132
    catch do_start_http_server(FileName).
 
133
 
 
134
 
 
135
%% ----------------------------------------------------------------------
 
136
%% print functions
 
137
%%
 
138
 
 
139
info(F, A, Mod, Line) ->
 
140
    print("INF ", F, A, Mod, Line).
 
141
 
 
142
log(F, A, Mod, Line) ->
 
143
    print("LOG ", F, A, Mod, Line).
 
144
 
 
145
debug(F, A, Mod, Line) ->
 
146
    print("DBG ", F, A, Mod, Line).
 
147
 
 
148
print(P, F, A, Mod, Line) ->
 
149
    io:format("~s[~p:~p:~p] : " ++ F ++ "~n", [P, self(), Mod, Line| A]).
 
150
 
 
151
print(F, A, Mod, Line) ->
 
152
    print("", F, A, Mod, Line).
 
153
 
 
154
hostname() ->
 
155
    from($@, atom_to_list(node())).
 
156
from(H, [H | T]) -> T;
 
157
from(H, [_ | T]) -> from(H, T);
 
158
from(_, []) -> [].
 
159
 
 
160
 
 
161
copy_file(File, From, To) ->
 
162
    file:copy(filename:join(From, File), filename:join(To, File)).
 
163
 
 
164
copy_files(FromDir, ToDir) -> 
 
165
    {ok, Files} = file:list_dir(FromDir),
 
166
    lists:foreach(fun(File) -> 
 
167
                          FullPath = filename:join(FromDir, File),
 
168
                          case filelib:is_file(FullPath) of
 
169
                              true ->
 
170
                                  file:copy(FullPath,
 
171
                                            filename:join(ToDir, File));
 
172
                              false ->
 
173
                                  ok
 
174
                          end
 
175
                  end, Files).
 
176
 
 
177
 
 
178
copy_dirs(FromDirRoot, ToDirRoot) ->
 
179
    {ok, Files} = file:list_dir(FromDirRoot),
 
180
    lists:foreach(
 
181
      fun(FileOrDir) -> 
 
182
              %% Check if it's a directory or a file
 
183
              case filelib:is_dir(filename:join(FromDirRoot, FileOrDir)) of
 
184
                  true ->
 
185
                      FromDir = filename:join([FromDirRoot, FileOrDir]),
 
186
                      ToDir   = filename:join([ToDirRoot, FileOrDir]),
 
187
                      ok      = file:make_dir(ToDir),
 
188
                      copy_dirs(FromDir, ToDir);
 
189
                  false ->
 
190
                      copy_file(FileOrDir, FromDirRoot, ToDirRoot)
 
191
              end
 
192
      end, Files).
 
193
 
 
194
del_dirs(Dir) ->
 
195
    case file:list_dir(Dir) of
 
196
        {ok, []} ->
 
197
            file:del_dir(Dir);
 
198
        {ok, Files} ->
 
199
            lists:foreach(fun(File) ->
 
200
                                  FullPath = filename:join(Dir,File),
 
201
                                  case filelib:is_dir(FullPath) of
 
202
                                      true ->
 
203
                                          del_dirs(FullPath),
 
204
                                          file:del_dir(FullPath);              
 
205
                                      false ->
 
206
                                          file:delete(FullPath)
 
207
                                  end 
 
208
                          end, Files);
 
209
        _ ->
 
210
            ok
 
211
    end.
 
212
 
 
213
check_body(Body) ->
 
214
    case string:rstr(Body, "</html>") of
 
215
        0 ->
 
216
            case string:rstr(Body, "</HTML>") of
 
217
                0 ->
 
218
                    tsp("Body ~p", [Body]),
 
219
                    tsf(did_not_receive_whole_body);
 
220
                _ ->
 
221
                    ok
 
222
            end;
 
223
        _ ->
 
224
            ok
 
225
    end.
 
226
 
 
227
%% ----------------------------------------------------------------
 
228
%% Conditional skip of testcases
 
229
%%
 
230
 
 
231
non_pc_tc_maybe_skip(Config, Condition, File, Line)
 
232
  when is_list(Config) andalso is_function(Condition) ->
 
233
    %% Check if we shall skip the skip
 
234
    case os:getenv("TS_OS_BASED_SKIP") of
 
235
        "false" ->
 
236
            ok;
 
237
        _ ->
 
238
            case lists:keysearch(ts, 1, Config) of
 
239
                {value, {ts, inets}} ->
 
240
                    %% Always run the testcase if we are using our own
 
241
                    %% test-server...
 
242
                    ok;
 
243
                _ ->
 
244
                    case (catch Condition()) of
 
245
                        true ->
 
246
                            skip(non_pc_testcase, File, Line);
 
247
                        _ ->
 
248
                            ok
 
249
                    end
 
250
            end
 
251
    end.
 
252
 
 
253
 
 
254
os_based_skip(any) ->
 
255
    true;
 
256
os_based_skip(Skippable) when is_list(Skippable) ->
 
257
    {OsFam, OsName} =
 
258
        case os:type() of
 
259
            {_Fam, _Name} = FamAndName ->
 
260
                FamAndName;
 
261
            Fam ->
 
262
                {Fam, undefined}
 
263
        end,
 
264
    case lists:member(OsFam, Skippable) of
 
265
        true ->
 
266
            true;
 
267
        false ->
 
268
            case lists:keysearch(OsFam, 1, Skippable) of
 
269
                {value, {OsFam, OsName}} ->
 
270
                    true;
 
271
                {value, {OsFam, OsNames}} when is_list(OsNames) ->
 
272
                    lists:member(OsName, OsNames);
 
273
                _ ->
 
274
                    false
 
275
            end
 
276
    end;
 
277
os_based_skip(_) ->
 
278
    false.
 
279
 
 
280
 
 
281
%% ----------------------------------------------------------------------
 
282
%% Socket functions:
 
283
%% open(SocketType, Host, Port) -> {ok, Socket} | {error, Reason}
 
284
%% SocketType -> ssl | ip_comm
 
285
%% Host       -> atom() | string() | {A, B, C, D} 
 
286
%% Port       -> integer()
 
287
 
 
288
connect_bin(ssl, Host, Port) ->
 
289
    connect(ssl, Host, Port, [binary, {packet,0}]);
 
290
connect_bin(ossl, Host, Port) ->
 
291
    connect(ssl, Host, Port, [{ssl_imp, old}, binary, {packet,0}]);
 
292
connect_bin(essl, Host, Port) ->
 
293
    connect(ssl, Host, Port, [{ssl_imp, new}, binary, {packet,0}, {reuseaddr, true}]);
 
294
connect_bin(ip_comm, Host, Port) ->
 
295
    Opts = [inet6, binary, {packet,0}],
 
296
    connect(ip_comm, Host, Port, Opts).
 
297
 
 
298
    
 
299
connect_byte(ssl, Host, Port) ->
 
300
    connect(ssl, Host, Port, [{packet,0}]);
 
301
connect_byte(ossl, Host, Port) ->
 
302
    connect(ssl, Host, Port, [{ssl_imp, old}, {packet,0}]);
 
303
connect_byte(essl, Host, Port) ->
 
304
    connect(ssl, Host, Port, [{ssl_imp, new}, {packet,0}]);
 
305
connect_byte(ip_comm, Host, Port) ->
 
306
    Opts = [inet6, {packet,0}],
 
307
    connect(ip_comm, Host, Port, Opts).
 
308
 
 
309
 
 
310
connect(ssl, Host, Port, Opts) ->
 
311
    ssl:start(),
 
312
    %% Does not support ipv6 in old ssl 
 
313
    case ssl:connect(Host, Port, Opts) of
 
314
        {ok, Socket} ->
 
315
            {ok, Socket};
 
316
        {error, Reason} ->
 
317
            {error, Reason};
 
318
        Error ->
 
319
            Error
 
320
    end;
 
321
connect(ip_comm, Host, Port, Opts) ->
 
322
    case gen_tcp:connect(Host,Port, Opts) of
 
323
        {ok, Socket} ->
 
324
            %% tsp("connect success"),
 
325
            {ok, Socket};
 
326
        {error, nxdomain} ->
 
327
            tsp("nxdomain opts: ~p", [Opts]),
 
328
            connect(ip_comm, Host, Port, lists:delete(inet6, Opts));
 
329
        {error, eafnosupport}  ->
 
330
            tsp("eafnosupport opts: ~p", [Opts]),
 
331
            connect(ip_comm, Host, Port, lists:delete(inet6, Opts));
 
332
        {error, enetunreach}  ->
 
333
            tsp("eafnosupport opts: ~p", [Opts]),
 
334
            connect(ip_comm, Host, Port, lists:delete(inet6, Opts));
 
335
        {error, {enfile,_}} ->
 
336
            tsp("Error enfile"),
 
337
            {error, enfile};
 
338
        Error ->
 
339
            tsp("Unexpected error: "
 
340
                "~n   Error: ~p"
 
341
                "~nwhen"
 
342
                "~n   Host:  ~p"
 
343
                "~n   Port:  ~p"
 
344
                "~n   Opts:  ~p"
 
345
                "~n", [Error, Host, Port, Opts]),
 
346
            Error
 
347
    end.
 
348
 
 
349
 
 
350
send(ssl, Socket, Data) ->
 
351
    ssl:send(Socket, Data);
 
352
send(ossl, Socket, Data) ->
 
353
    ssl:send(Socket, Data);
 
354
send(essl, Socket, Data) ->
 
355
    ssl:send(Socket, Data);
 
356
send(ip_comm,Socket,Data) ->
 
357
    gen_tcp:send(Socket,Data).
 
358
 
 
359
 
 
360
close(ssl,Socket) ->
 
361
    catch ssl:close(Socket);
 
362
close(ossl,Socket) ->
 
363
    catch ssl:close(Socket);
 
364
close(essl,Socket) ->
 
365
    catch ssl:close(Socket);
 
366
close(ip_comm,Socket) ->
 
367
    catch gen_tcp:close(Socket).
 
368
 
 
369
millis() ->
 
370
    erlang:now().
 
371
 
 
372
millis_diff(A,B) ->
 
373
    T1 = (element(1,A)*1000000) + element(2,A) + (element(3,A)/1000000),
 
374
    T2 = (element(1,B)*1000000) + element(2,B) + (element(3,B)/1000000),
 
375
    T1 - T2.
 
376
 
 
377
hours(N)   -> trunc(N * 1000 * 60 * 60).
 
378
minutes(N) -> trunc(N * 1000 * 60).
 
379
seconds(N) -> trunc(N * 1000).
 
380
 
 
381
 
 
382
sleep(infinity) ->
 
383
    receive
 
384
    after infinity ->
 
385
            ok
 
386
    end;
 
387
sleep(MSecs) ->
 
388
    receive
 
389
    after trunc(MSecs) ->
 
390
            ok
 
391
    end,
 
392
    ok.
 
393
 
 
394
 
 
395
skip(Reason, File, Line) ->
 
396
    exit({skipped, {Reason, File, Line}}).
 
397
 
 
398
flush() ->
 
399
    receive
 
400
        Msg ->
 
401
            [Msg | flush()]
 
402
    after 1000 ->
 
403
            []
 
404
    end.
 
405
 
 
406
 
 
407
tsp(F) ->
 
408
    tsp(F, []).
 
409
tsp(F, A) ->
 
410
    test_server:format("~p ~p:" ++ F ++ "~n", [self(), ?MODULE | A]).
 
411
 
 
412
tsf(Reason) ->
 
413
    test_server:fail(Reason).