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

« back to all changes in this revision

Viewing changes to lib/orber/test/orber_firewall_ipv6_in_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
%%
 
2
%% %CopyrightBegin%
 
3
%%
 
4
%% Copyright Ericsson AB 2004-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
 
 
21
-module(orber_firewall_ipv6_in_SUITE).
 
22
 
 
23
-include_lib("test_server/include/test_server.hrl").
 
24
-include_lib("orber/include/corba.hrl").
 
25
-include_lib("orber/COSS/CosNaming/CosNaming.hrl").
 
26
-include_lib("orber/src/orber_iiop.hrl").
 
27
-include_lib("orber/src/ifr_objects.hrl").
 
28
-include("idl_output/orber_test_server.hrl").
 
29
-include_lib("orber/COSS/CosNaming/CosNaming_NamingContextExt.hrl").
 
30
-include_lib("orber/COSS/CosNaming/CosNaming_NamingContext.hrl").
 
31
 
 
32
-define(default_timeout, ?t:minutes(15)).
 
33
 
 
34
-define(match(ExpectedRes,Expr),
 
35
        fun() ->
 
36
                AcTuAlReS = (catch (Expr)),
 
37
                case AcTuAlReS of
 
38
                    ExpectedRes ->
 
39
                        io:format("------ CORRECT RESULT ------~n~p~n",
 
40
                                 [AcTuAlReS]),
 
41
                        AcTuAlReS;
 
42
                    _ ->
 
43
                        io:format("###### ERROR ERROR ######~nRESULT:  ~p~n",
 
44
                                  [AcTuAlReS]),
 
45
                        ?line exit(AcTuAlReS)
 
46
                end
 
47
        end()).
 
48
 
 
49
%%-----------------------------------------------------------------
 
50
%% External exports
 
51
%%-----------------------------------------------------------------
 
52
-export([all/0, suite/0,groups/0,init_per_group/2,end_per_group/2, cases/0, 
 
53
         init_per_suite/1, end_per_suite/1, 
 
54
         init_per_testcase/2, end_per_testcase/2,  
 
55
         deny_port_api/1, deny_port_range_api/1, deny_host_api/1, 
 
56
         deny_peerhost_api/1, allow_port_range_api/1,
 
57
         allow_host_api/1, allow_peerhost_api/1, check_address_api/1]).
 
58
 
 
59
%%-----------------------------------------------------------------
 
60
%% Func: all/1
 
61
%% Args: 
 
62
%% Returns: 
 
63
%%-----------------------------------------------------------------
 
64
suite() -> [{ct_hooks,[ts_install_cth]}].
 
65
 
 
66
all() -> 
 
67
    cases().
 
68
 
 
69
groups() -> 
 
70
    [].
 
71
 
 
72
init_per_group(_GroupName, Config) ->
 
73
    Config.
 
74
 
 
75
end_per_group(_GroupName, Config) ->
 
76
    Config.
 
77
 
 
78
 
 
79
%% NOTE - the fragment test cases must bu first since we explicitly set a request
 
80
%% id. Otherwise, the request-id counter would be increased and we cannot know
 
81
%% what it is.
 
82
cases() -> 
 
83
    [deny_port_api, deny_port_range_api, deny_host_api,
 
84
     deny_peerhost_api, allow_port_range_api, allow_host_api,
 
85
     allow_peerhost_api, check_address_api].
 
86
 
 
87
 
 
88
init_per_testcase(_Case, Config) ->
 
89
    ?line Dog=test_server:timetrap(?default_timeout),
 
90
    orber:jump_start([{iiop_port, 0},
 
91
                      {iiop_out_ports, {5980, 6000}},
 
92
                      {flags, ?ORB_ENV_USE_IPV6}]),
 
93
    [{watchdog, Dog}|Config].
 
94
 
 
95
 
 
96
end_per_testcase(_Case, Config) ->
 
97
    orber:jump_stop(),
 
98
    Dog = ?config(watchdog, Config),
 
99
    test_server:timetrap_cancel(Dog),
 
100
    ok.
 
101
 
 
102
init_per_suite(Config) ->
 
103
    case orber_test_lib:version_ok() of
 
104
        true ->
 
105
            if
 
106
                is_list(Config) ->
 
107
                    Config;
 
108
                true ->
 
109
                    exit("Config not a list")
 
110
            end;
 
111
        Reason ->
 
112
            Reason
 
113
    end.
 
114
 
 
115
end_per_suite(Config) ->
 
116
    Config.
 
117
 
 
118
 
 
119
%%-----------------------------------------------------------------
 
120
%%  Incomming connections - Deny
 
121
%%-----------------------------------------------------------------
 
122
deny_port_api(doc) -> ["Deny Access due to invalid local port"];
 
123
deny_port_api(suite) -> [];
 
124
deny_port_api(_Config) ->
 
125
    [IP] = ?match([_], orber:host()),
 
126
    {ok, ServerNode, ServerHost} = 
 
127
        ?match({ok,_,_}, orber_test_lib:js_node([{flags, (?ORB_ENV_USE_IPV6 bor 
 
128
                                                          ?ORB_ENV_USE_ACL_INCOMING)},
 
129
                                                 {iiop_acl, [{tcp_in, IP++"/128#7000"}]}])),
 
130
    ServerPort = orber_test_lib:remote_apply(ServerNode, orber, iiop_port, []),
 
131
    ?match({'EXCEPTION', #'CosNaming_NamingContextExt_InvalidAddress'{}}, 
 
132
           corba:string_to_object("corbaloc::1.2@"++ServerHost++":"++integer_to_list(ServerPort)++"/NameService")),
 
133
                                                %    ?line catch orber_test_lib:destroy_node(ServerNode, timeout),
 
134
    ok.
 
135
 
 
136
deny_port_range_api(doc) -> ["Deny Access due to invalid local port range"];
 
137
deny_port_range_api(suite) -> [];
 
138
deny_port_range_api(_Config) ->
 
139
    [IP] = ?match([_], orber:host()),
 
140
    {ok, ServerNode, ServerHost} = 
 
141
        ?match({ok,_,_}, orber_test_lib:js_node([{flags, (?ORB_ENV_USE_IPV6 bor 
 
142
                                                          ?ORB_ENV_USE_ACL_INCOMING)},
 
143
                                                 {iiop_acl, [{tcp_in, IP++"/128#7000/8000"}]}])),
 
144
    ServerPort = orber_test_lib:remote_apply(ServerNode, orber, iiop_port, []),
 
145
    ?match({'EXCEPTION', #'CosNaming_NamingContextExt_InvalidAddress'{}}, 
 
146
           corba:string_to_object("corbaloc::1.2@"++ServerHost++":"++integer_to_list(ServerPort)++"/NameService")),
 
147
%    ?line catch orber_test_lib:destroy_node(ServerNode, timeout),
 
148
    ok.
 
149
 
 
150
 
 
151
deny_host_api(doc) -> ["Deny Access due to invalid host"];
 
152
deny_host_api(suite) -> [];
 
153
deny_host_api(_Config) ->
 
154
    {ok, ServerNode, ServerHost} = 
 
155
        ?match({ok,_,_}, orber_test_lib:js_node([{flags, (?ORB_ENV_USE_IPV6 bor 
 
156
                                                          ?ORB_ENV_USE_ACL_INCOMING)},
 
157
                                                 {iiop_acl, [{tcp_in, "0:0:0:0:0:0:10.1.1.1/128"}]}])),
 
158
    ServerPort = orber_test_lib:remote_apply(ServerNode, orber, iiop_port, []),
 
159
    ?match({'EXCEPTION', #'CosNaming_NamingContextExt_InvalidAddress'{}}, 
 
160
           corba:string_to_object("corbaloc::1.2@"++ServerHost++":"++integer_to_list(ServerPort)++"/NameService")),
 
161
%    ?line catch orber_test_lib:destroy_node(ServerNode, timeout),
 
162
    ok.
 
163
 
 
164
deny_peerhost_api(doc) -> ["Deny Access due to invalid peer host"];
 
165
deny_peerhost_api(suite) -> [];
 
166
deny_peerhost_api(_Config) ->
 
167
    [IP] = ?match([_], orber:host()),
 
168
    {ok, ServerNode, ServerHost} = 
 
169
        ?match({ok,_,_}, 
 
170
               orber_test_lib:js_node([{flags, (?ORB_ENV_USE_IPV6 bor 
 
171
                                                ?ORB_ENV_USE_ACL_INCOMING)},
 
172
                                       {iiop_acl, [{tcp_in, IP++"/128", ["0:0:0:0:0:0:10.1.1.1"]}]}])),
 
173
    ServerPort = orber_test_lib:remote_apply(ServerNode, orber, iiop_port, []),
 
174
    ?match({'EXCEPTION', #'CosNaming_NamingContextExt_InvalidAddress'{}}, 
 
175
           corba:string_to_object("corbaloc::1.2@"++ServerHost++":"++integer_to_list(ServerPort)++"/NameService")),
 
176
%    ?line catch orber_test_lib:destroy_node(ServerNode, timeout),
 
177
    ok.
 
178
 
 
179
%%-----------------------------------------------------------------
 
180
%%  Incomming connections - Allow
 
181
%%-----------------------------------------------------------------
 
182
allow_port_range_api(doc) -> ["Allow Access due to valid local port range"];
 
183
allow_port_range_api(suite) -> [];
 
184
allow_port_range_api(_Config) ->
 
185
    [IP] = ?match([_], orber:host()),
 
186
    {ok, ServerNode, ServerHost} = 
 
187
        ?match({ok,_,_}, orber_test_lib:js_node([{flags, (?ORB_ENV_USE_IPV6 bor 
 
188
                                                          ?ORB_ENV_USE_ACL_INCOMING)},
 
189
                                                 {iiop_acl, [{tcp_in, IP++"/128#5980/6000"}]}])),
 
190
    ServerPort = orber_test_lib:remote_apply(ServerNode, orber, iiop_port, []),
 
191
    IOR = 
 
192
        ?match({'IOP_IOR',_,_},
 
193
               corba:string_to_object("corbaloc::1.2@"++ServerHost++":"++integer_to_list(ServerPort)++"/NameService")),
 
194
    ?match(false, corba_object:not_existent(IOR)),
 
195
%    ?line catch orber_test_lib:destroy_node(ServerNode, timeout),
 
196
    ok.
 
197
 
 
198
 
 
199
allow_host_api(doc) -> ["Allow Access due to valid host"];
 
200
allow_host_api(suite) -> [];
 
201
allow_host_api(_Config) ->
 
202
    [IP] = ?match([_], orber:host()),
 
203
    {ok, ServerNode, ServerHost} = 
 
204
        ?match({ok,_,_}, orber_test_lib:js_node([{flags, (?ORB_ENV_USE_IPV6 bor 
 
205
                                                          ?ORB_ENV_USE_ACL_INCOMING)},
 
206
                                                 {iiop_acl, [{tcp_in, IP++"/128"}]}])),
 
207
    ServerPort = orber_test_lib:remote_apply(ServerNode, orber, iiop_port, []),
 
208
    IOR =
 
209
        ?match({'IOP_IOR',_,_}, 
 
210
               corba:string_to_object("corbaloc::1.2@"++ServerHost++":"++integer_to_list(ServerPort)++"/NameService")),
 
211
    ?match(false, corba_object:not_existent(IOR)),
 
212
 
 
213
%    ?line catch orber_test_lib:destroy_node(ServerNode, timeout),
 
214
    ok.
 
215
 
 
216
allow_peerhost_api(doc) -> ["Allow Access due to valid host"];
 
217
allow_peerhost_api(suite) -> [];
 
218
allow_peerhost_api(_Config) ->
 
219
    [IP] = ?match([_], orber:host()),
 
220
    {ok, ServerNode, ServerHost} = 
 
221
        ?match({ok,_,_}, orber_test_lib:js_node([{flags, (?ORB_ENV_USE_IPV6 bor 
 
222
                                                          ?ORB_ENV_USE_ACL_INCOMING)},
 
223
                                                 {iiop_acl, [{tcp_in, IP++"/128", [IP]}]}])),
 
224
    ServerPort = orber_test_lib:remote_apply(ServerNode, orber, iiop_port, []),
 
225
    IOR = 
 
226
        ?match({'IOP_IOR',_,_}, 
 
227
               corba:string_to_object("corbaloc::1.2@"++ServerHost++":"++integer_to_list(ServerPort)++"/NameService",
 
228
                                      [#'IOP_ServiceContext'
 
229
                                       {context_id=?ORBER_GENERIC_CTX_ID, 
 
230
                                        context_data = {interface, IP}}])),
 
231
    ?match(false, corba_object:not_existent(IOR,
 
232
                                            [#'IOP_ServiceContext'
 
233
                                             {context_id=?ORBER_GENERIC_CTX_ID, 
 
234
                                              context_data = {interface, IP}}])),
 
235
    
 
236
%    ?line catch orber_test_lib:destroy_node(ServerNode, timeout),
 
237
    ok.
 
238
 
 
239
%%-----------------------------------------------------------------
 
240
%%  Test corbaloc strings
 
241
%%-----------------------------------------------------------------
 
242
check_address_api(doc) -> ["Test corbaloc strings"];
 
243
check_address_api(suite) -> [];
 
244
check_address_api(_Config) ->
 
245
    ?match({[[iiop,{1,0},"0:0:0:0:0:FFFF:C02A:2A2A",2809]],"NameService"},
 
246
           orber_cosnaming_utils:addresses(":0:0:0:0:0:FFFF:C02A:2A2A/NameService")),
 
247
    ?match({[[iiop,{1,0},"0:0:0:0:0:FFFF:C02A:2A2A",2809]],[]},
 
248
           orber_cosnaming_utils:addresses(":0:0:0:0:0:FFFF:C02A:2A2A")),
 
249
    ?match({[[iiop,{1,2},"0:0:0:0:0:FFFF:C02A:2A2A",2809]],"NameService"},
 
250
           orber_cosnaming_utils:addresses(":1.2@0:0:0:0:0:FFFF:C02A:2A2A/NameService")),
 
251
    ?match({[[iiop,{1,0},"0:0:0:0:0:FFFF:C02A:2A2A",4001]],"NameService"},
 
252
           orber_cosnaming_utils:addresses(":0:0:0:0:0:FFFF:C02A:2A2A:4001/NameService")),
 
253
    ?match({[[iiop,{1,1},"0:0:0:0:0:FFFF:C02A:2A2A",4001]],"NameService"},
 
254
           orber_cosnaming_utils:addresses(":1.1@0:0:0:0:0:FFFF:C02A:2A2A:4001/NameService")),
 
255
    ?match({[[iiop,{1,1},"0:0:0:0:0:FFFF:C02A:2A2A",4001]],[]},
 
256
           orber_cosnaming_utils:addresses(":1.1@0:0:0:0:0:FFFF:C02A:2A2A:4001")),
 
257
    ?match({[[iiop,{1,1},"0:0:0:0:0:FFFF:C02A:2A2A",4001]],[]},
 
258
           orber_cosnaming_utils:addresses("iiop:1.1@0:0:0:0:0:FFFF:C02A:2A2A:4001")),
 
259
 
 
260
    ?match({[[iiop,{1,0},"0:0:0:0:0:FFFF:10.11.11.11",2809]],"NameService"},
 
261
           orber_cosnaming_utils:addresses(":0:0:0:0:0:FFFF:10.11.11.11/NameService")),
 
262
    ?match({[[iiop,{1,0},"0:0:0:0:0:FFFF:10.11.11.11",2809]],[]},
 
263
           orber_cosnaming_utils:addresses(":0:0:0:0:0:FFFF:10.11.11.11")),
 
264
    ?match({[[iiop,{1,2},"0:0:0:0:0:FFFF:10.11.11.11",2809]],"NameService"},
 
265
           orber_cosnaming_utils:addresses(":1.2@0:0:0:0:0:FFFF:10.11.11.11/NameService")),
 
266
    ?match({[[iiop,{1,0},"0:0:0:0:0:FFFF:10.11.11.11",4001]],"NameService"},
 
267
           orber_cosnaming_utils:addresses(":0:0:0:0:0:FFFF:10.11.11.11:4001/NameService")),
 
268
    ?match({[[iiop,{1,1},"0:0:0:0:0:FFFF:10.11.11.11",4001]],"NameService"},
 
269
           orber_cosnaming_utils:addresses(":1.1@0:0:0:0:0:FFFF:10.11.11.11:4001/NameService")),
 
270
    ?match({[[iiop,{1,1},"0:0:0:0:0:FFFF:10.11.11.11",4001]],[]},
 
271
           orber_cosnaming_utils:addresses(":1.1@0:0:0:0:0:FFFF:10.11.11.11:4001/")),
 
272
    ?match({[[iiop,{1,1},"0:0:0:0:0:FFFF:10.11.11.11",4001]],[]},
 
273
           orber_cosnaming_utils:addresses("iiop:1.1@0:0:0:0:0:FFFF:10.11.11.11:4001/")),
 
274
 
 
275
    ?match({[[iiop,{1,1},"myhost",4001]],[]},
 
276
           orber_cosnaming_utils:addresses("iiop:1.1@myhost:4001")),
 
277
    ?match({[[iiop,{1,1},"myhost.full.name",4001]],"NameService"},
 
278
           orber_cosnaming_utils:addresses("iiop:1.1@myhost.full.name:4001/NameService")),
 
279
    ?match({[[iiop,{1,1},"myhost",4001], 
 
280
             [iiop,{1,1},"myhost.full.name",2809]],"NameService"},
 
281
           orber_cosnaming_utils:addresses("iiop:1.1@myhost:4001,iiop:1.1@myhost.full.name/NameService")),
 
282
 
 
283
    ?match({[[iiop,{1,1},"0:0:0:0:0:FFFF:10.11.11.11",4001],
 
284
             [iiop,{1,1},"0:0:0:0:0:FFFF:C02A:2A2A",4001]], "NameService"},
 
285
           orber_cosnaming_utils:addresses(":1.1@0:0:0:0:0:FFFF:10.11.11.11:4001,:1.1@0:0:0:0:0:FFFF:C02A:2A2A:4001/NameService")),
 
286
    ?match({[[iiop,{1,1},"0:0:0:0:0:FFFF:10.11.11.11",4001],
 
287
             [iiop,{1,1},"0:0:0:0:0:FFFF:C02A:2A2A",4001]], []},
 
288
           orber_cosnaming_utils:addresses(":1.1@0:0:0:0:0:FFFF:10.11.11.11:4001,:1.1@0:0:0:0:0:FFFF:C02A:2A2A:4001")),
 
289
    ?match({[[iiop,{1,0},"0:0:0:0:0:FFFF:10.11.11.11",4001],
 
290
             [iiop,{1,1},"0:0:0:0:0:FFFF:C02A:2A2A",4001]], "NameService"},
 
291
           orber_cosnaming_utils:addresses(":0:0:0:0:0:FFFF:10.11.11.11:4001,:1.1@0:0:0:0:0:FFFF:C02A:2A2A:4001/NameService")),
 
292
    ?match({[[iiop,{1,1},"0:0:0:0:0:FFFF:10.11.11.11",4001],
 
293
             [iiop,{1,0},"0:0:0:0:0:FFFF:C02A:2A2A",4001]], "NameService"},
 
294
           orber_cosnaming_utils:addresses(":1.1@0:0:0:0:0:FFFF:10.11.11.11:4001,:0:0:0:0:0:FFFF:C02A:2A2A:4001/NameService")),
 
295
    ?match({[[iiop,{1,1},"0:0:0:0:0:FFFF:10.11.11.11",2809],
 
296
             [iiop,{1,1},"0:0:0:0:0:FFFF:C02A:2A2A",4001]], "NameService"},
 
297
           orber_cosnaming_utils:addresses(":1.1@0:0:0:0:0:FFFF:10.11.11.11,:1.1@0:0:0:0:0:FFFF:C02A:2A2A:4001/NameService")),
 
298
    ?match({[[iiop,{1,1},"0:0:0:0:0:FFFF:10.11.11.11",4001],
 
299
             [iiop,{1,1},"0:0:0:0:0:FFFF:C02A:2A2A",2809]], "NameService"},
 
300
           orber_cosnaming_utils:addresses(":1.1@0:0:0:0:0:FFFF:10.11.11.11:4001,:1.1@0:0:0:0:0:FFFF:C02A:2A2A/NameService")),
 
301
    ?match({[[iiop,{1,0},"0:0:0:0:0:FFFF:10.11.11.11",2809],
 
302
             [iiop,{1,0},"0:0:0:0:0:FFFF:C02A:2A2A",2809]], "NameService"},
 
303
           orber_cosnaming_utils:addresses(":0:0:0:0:0:FFFF:10.11.11.11,:0:0:0:0:0:FFFF:C02A:2A2A/NameService")),
 
304
    ?match({[[iiop,{1,0},"0:0:0:0:0:FFFF:10.11.11.11",2809],
 
305
             [iiop,{1,0},"0:0:0:0:0:FFFF:C02A:2A2A",2809]], []},
 
306
           orber_cosnaming_utils:addresses(":0:0:0:0:0:FFFF:10.11.11.11,:0:0:0:0:0:FFFF:C02A:2A2A/")),
 
307
    ?match({[[iiop,{1,0},"0:0:0:0:0:FFFF:10.11.11.11",2809],
 
308
             [iiop,{1,0},"0:0:0:0:0:FFFF:C02A:2A2A",2809]], []},
 
309
           orber_cosnaming_utils:addresses("iiop:0:0:0:0:0:FFFF:10.11.11.11,:0:0:0:0:0:FFFF:C02A:2A2A/")),
 
310
 
 
311
    [IP] = ?match([_], orber:host()),
 
312
    {ok, ServerNode, _ServerHost} = 
 
313
        ?match({ok,_,_}, orber_test_lib:js_node([{flags, (?ORB_ENV_USE_IPV6 bor 
 
314
                                                          ?ORB_ENV_USE_ACL_INCOMING)},
 
315
                                                 {iiop_acl, [{tcp_in, IP++"/128"}]}])),
 
316
    ServerPort = orber_test_lib:remote_apply(ServerNode, orber, iiop_port, []),
 
317
    ?match({'IOP_IOR',_,_}, 
 
318
           corba:string_to_object("corbaloc::1.2@"++IP++":"++integer_to_list(ServerPort)++"/NameService")),
 
319
%    ?line catch orber_test_lib:destroy_node(ServerNode, timeout),
 
320
    ok.
 
321
 
 
322