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

« back to all changes in this revision

Viewing changes to erts/emulator/test/port_SUITE.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
1
%%
2
2
%% %CopyrightBegin%
3
 
%% 
4
 
%% Copyright Ericsson AB 1997-2009. All Rights Reserved.
5
 
%% 
 
3
%%
 
4
%% Copyright Ericsson AB 1997-2011. 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
 
%% 
 
16
%%
17
17
%% %CopyrightEnd%
18
18
%%
19
19
 
73
73
%%
74
74
 
75
75
 
76
 
-export([all/1, init_per_testcase/2, fin_per_testcase/2,
 
76
-export([all/0, suite/0,groups/0,init_per_group/2,end_per_group/2, 
 
77
         init_per_testcase/2, end_per_testcase/2,
77
78
         init_per_suite/1, end_per_suite/1,
78
 
         stream/1, stream_small/1, stream_big/1,
 
79
         stream_small/1, stream_big/1,
79
80
         basic_ping/1, slow_writes/1, bad_packet/1, bad_port_messages/1,
80
 
         multiple_packets/1, mul_basic/1, mul_slow_writes/1,
 
81
         mul_basic/1, mul_slow_writes/1,
81
82
         dying_port/1, port_program_with_path/1,
82
83
         open_input_file_port/1, open_output_file_port/1,
83
84
         iter_max_ports/1, eof/1, input_only/1, output_only/1,
84
85
         name1/1,
85
 
         t_binary/1, options/1, parallell/1, t_exit/1,
 
86
         t_binary/1, parallell/1, t_exit/1,
86
87
         env/1, bad_env/1, cd/1, exit_status/1,
87
 
         tps/1, tps_16_bytes/1, tps_1K/1, line/1, stderr_to_stdout/1,
 
88
         tps_16_bytes/1, tps_1K/1, line/1, stderr_to_stdout/1,
88
89
         otp_3906/1, otp_4389/1, win_massive/1, win_massive_client/1,
89
90
         mix_up_ports/1, otp_5112/1, otp_5119/1, otp_6224/1,
90
91
         exit_status_multi_scheduling_block/1, ports/1,
91
 
         spawn_driver/1,spawn_executable/1]).
 
92
         spawn_driver/1, spawn_executable/1, close_deaf_port/1,
 
93
         unregister_name/1]).
92
94
 
93
95
-export([]).
94
96
 
97
99
-export([otp_3906_forker/5, otp_3906_start_forker_starter/4]).
98
100
-export([env_slave_main/1]).
99
101
 
100
 
-include("test_server.hrl").
 
102
-include_lib("test_server/include/test_server.hrl").
101
103
-include_lib("kernel/include/file.hrl").
102
104
 
103
 
all(suite) ->
104
 
    [
105
 
     otp_6224, stream, basic_ping, slow_writes, bad_packet,
106
 
     bad_port_messages, options, multiple_packets, parallell,
107
 
     dying_port, port_program_with_path,
108
 
     open_input_file_port, open_output_file_port,
109
 
     name1,
110
 
     env, bad_env, cd, exit_status,
111
 
     iter_max_ports, t_exit, tps, line, stderr_to_stdout,
112
 
     otp_3906, otp_4389, win_massive, mix_up_ports,
113
 
     otp_5112, otp_5119,
114
 
     exit_status_multi_scheduling_block,
115
 
     ports, spawn_driver, spawn_executable
116
 
    ].
 
105
suite() -> [{ct_hooks,[ts_install_cth]}].
 
106
 
 
107
all() -> 
 
108
    [otp_6224, {group, stream}, basic_ping, slow_writes,
 
109
     bad_packet, bad_port_messages, {group, options},
 
110
     {group, multiple_packets}, parallell, dying_port,
 
111
     port_program_with_path, open_input_file_port,
 
112
     open_output_file_port, name1, env, bad_env, cd,
 
113
     exit_status, iter_max_ports, t_exit, {group, tps}, line,
 
114
     stderr_to_stdout, otp_3906, otp_4389, win_massive,
 
115
     mix_up_ports, otp_5112, otp_5119,
 
116
     exit_status_multi_scheduling_block, ports, spawn_driver,
 
117
     spawn_executable, close_deaf_port, unregister_name].
 
118
 
 
119
groups() -> 
 
120
    [{stream, [], [stream_small, stream_big]},
 
121
     {options, [], [t_binary, eof, input_only, output_only]},
 
122
     {multiple_packets, [], [mul_basic, mul_slow_writes]},
 
123
     {tps, [], [tps_16_bytes, tps_1K]}].
 
124
 
 
125
init_per_group(_GroupName, Config) ->
 
126
    Config.
 
127
 
 
128
end_per_group(_GroupName, Config) ->
 
129
    Config.
 
130
 
117
131
 
118
132
-define(DEFAULT_TIMEOUT, ?t:minutes(5)).
119
133
 
120
134
init_per_testcase(Case, Config) ->
121
135
    [{testcase, Case} |Config].
122
136
 
123
 
fin_per_testcase(_Case, _Config) ->
 
137
end_per_testcase(_Case, _Config) ->
124
138
    ok.
125
139
 
126
140
init_per_suite(Config) when is_list(Config) ->
189
203
    
190
204
 
191
205
 
192
 
stream(suite) -> [stream_small, stream_big].
193
206
 
194
207
%% Test that we can send a stream of bytes and get it back.
195
208
%% We will send only a small amount of data, to avoid deadlock.
302
315
%% Tests various options (stream and {packet, Number} are implicitly
303
316
%% tested in other test cases).
304
317
 
305
 
options(suite) -> [t_binary, eof, input_only, output_only].
306
318
 
307
319
%% Tests the 'binary' option for a port.
308
320
 
414
426
%% Test that receiving several packages written in the same
415
427
%% write operation works.
416
428
 
417
 
multiple_packets(suite) -> [mul_basic, mul_slow_writes].
418
429
 
419
430
%% Basic test of receiving multiple packages, written in
420
431
%% one operation by the other end.
738
749
    ?line exit(Port, die),
739
750
    ?line receive after infinity -> ok end.
740
751
 
741
 
tps(suite) -> [tps_16_bytes, tps_1K].
742
752
 
743
753
tps_16_bytes(doc) -> "";
744
754
tps_16_bytes(suite) -> [];
876
886
                            "nisse" = os:getenv(Long)
877
887
                    end),
878
888
 
879
 
 
 
889
    
880
890
    ?line env_slave(Temp, [{"must_define_something","some_value"},
881
 
                           {"certainly_not_existing",false},
 
891
                            {"certainly_not_existing",false},
 
892
                           {"ends_with_equal", "value="},
882
893
                           {Long,false},
883
894
                           {"glurf","a glorfy string"}]),
884
895
 
 
896
    %% A lot of non existing variables (mingled with existing)
 
897
    NotExistingList = [{lists:flatten(io_lib:format("V~p_not_existing",[X])),false} 
 
898
                        ||  X <- lists:seq(1,150)],
 
899
    ExistingList = [{lists:flatten(io_lib:format("V~p_existing",[X])),"a_value"} 
 
900
                        ||  X <- lists:seq(1,150)],
 
901
    ?line env_slave(Temp, lists:sort(ExistingList ++ NotExistingList)),
 
902
 
885
903
    ?line test_server:timetrap_cancel(Dog),
886
904
    ok.
887
905
 
1039
1057
-define(OTP_3906_MAX_CONC_OSP, 50).
1040
1058
 
1041
1059
otp_3906(Config, OSName) ->
1042
 
    ?line TSDir = filename:dirname(code:which(test_server)),
1043
 
    ?line {ok, Variables} = file:consult(filename:join(TSDir, "variables")),
 
1060
    ?line DataDir = filename:dirname(proplists:get_value(data_dir,Config)),
 
1061
    ?line {ok, Variables} = file:consult(
 
1062
                              filename:join([DataDir,"..","..",
 
1063
                                             "test_server","variables"])),
1044
1064
    case lists:keysearch('CC', 1, Variables) of
1045
1065
        {value,{'CC', CC}} ->
1046
1066
            SuiteDir = filename:dirname(code:which(?MODULE)),
1434
1454
    ?line test_server:timetrap_cancel(Dog),
1435
1455
    ok.
1436
1456
 
 
1457
unregister_name(Config) when is_list(Config) ->
 
1458
    ?line true = register(crash, open_port({spawn, "sleep 100"}, [])),
 
1459
    ?line true = unregister(crash).
 
1460
 
1437
1461
test_bat_file(Dir) ->
1438
1462
    FN = "tf.bat",
1439
1463
    Full = filename:join([Dir,FN]),
2286
2310
            io:format("~s\n", [erl_ddll:format_error(Error)]),
2287
2311
            Res
2288
2312
    end.
 
2313
 
 
2314
 
 
2315
close_deaf_port(doc) -> ["Send data to port program that does not read it, then close port."
 
2316
                         "Primary targeting Windows to test threaded_handle_closer in sys.c"];
 
2317
close_deaf_port(suite) -> [];
 
2318
close_deaf_port(Config) when is_list(Config) ->
 
2319
    ?line Dog = test_server:timetrap(test_server:seconds(100)),
 
2320
    ?line DataDir = ?config(data_dir, Config),
 
2321
    ?line DeadPort = os:find_executable("dead_port", DataDir),
 
2322
    ?line Port = open_port({spawn,DeadPort++" 60"},[]),
 
2323
    ?line erlang:port_command(Port,"Hello, can you hear me!?!?"),
 
2324
    ?line port_close(Port),
 
2325
 
 
2326
    Res = close_deaf_port_1(0, DeadPort),
 
2327
    io:format("Waiting for OS procs to terminate...\n"),
 
2328
    receive after 5*1000 -> ok end,
 
2329
    ?line test_server:timetrap_cancel(Dog),
 
2330
    Res.
 
2331
 
 
2332
close_deaf_port_1(1000, _) ->
 
2333
    ok;
 
2334
close_deaf_port_1(N, Cmd) ->
 
2335
    Timeout = integer_to_list(random:uniform(5*1000)),
 
2336
    ?line try open_port({spawn_executable,Cmd},[{args,[Timeout]}]) of
 
2337
        Port ->
 
2338
            ?line erlang:port_command(Port,"Hello, can you hear me!?!?"),
 
2339
            ?line port_close(Port),
 
2340
            close_deaf_port_1(N+1, Cmd)
 
2341
    catch
 
2342
        _:eagain ->
 
2343
            {comment, "Could not spawn more than " ++ integer_to_list(N) ++ " OS processes."}
 
2344
    end.
 
2345
    
 
2346