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

« back to all changes in this revision

Viewing changes to lib/orber/test/interceptors_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
%%
 
3
%% %CopyrightBegin%
 
4
%% 
 
5
%% Copyright Ericsson AB 2004-2011. All Rights Reserved.
 
6
%% 
 
7
%% The contents of this file are subject to the Erlang Public License,
 
8
%% Version 1.1, (the "License"); you may not use this file except in
 
9
%% compliance with the License. You should have received a copy of the
 
10
%% Erlang Public License along with this software. If not, it can be
 
11
%% retrieved online at http://www.erlang.org/.
 
12
%% 
 
13
%% Software distributed under the License is distributed on an "AS IS"
 
14
%% basis, WITHOUT WARRANTY OF ANY KIND, either express or implied. See
 
15
%% the License for the specific language governing rights and limitations
 
16
%% under the License.
 
17
%% 
 
18
%% %CopyrightEnd%
 
19
%%
 
20
%%
 
21
%%-----------------------------------------------------------------
 
22
%% File    : interceptors_SUITE.erl
 
23
%% Purpose : 
 
24
%%-----------------------------------------------------------------
 
25
 
 
26
-module(interceptors_SUITE).
 
27
 
 
28
-include_lib("test_server/include/test_server.hrl").
 
29
-include_lib("orber/include/corba.hrl").
 
30
-include_lib("orber/src/orber_iiop.hrl").
 
31
 
 
32
-define(default_timeout, ?t:minutes(3)).
 
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 ######~n~p~n",
 
44
                                  [AcTuAlReS]),
 
45
                        ?line exit(AcTuAlReS)
 
46
                end
 
47
        end()).
 
48
 
 
49
-define(nomatch(Not, Expr),
 
50
        fun() ->
 
51
                AcTuAlReS = (catch (Expr)),
 
52
                case AcTuAlReS of
 
53
                    Not ->
 
54
                        io:format("###### ERROR ERROR ######~n~p~n",
 
55
                                  [AcTuAlReS]),
 
56
                        ?line exit(AcTuAlReS);
 
57
                    _ ->
 
58
                        io:format("------ CORRECT RESULT ------~n~p~n",
 
59
                                  [AcTuAlReS]),
 
60
                        AcTuAlReS
 
61
                end
 
62
        end()).
 
63
 
 
64
 
 
65
%%-----------------------------------------------------------------
 
66
%% External exports
 
67
%%-----------------------------------------------------------------
 
68
-export([all/0, suite/0,groups/0,init_per_suite/1, end_per_suite/1, 
 
69
         init_per_group/2,end_per_group/2]).
 
70
 
 
71
%%-----------------------------------------------------------------
 
72
%% Internal exports
 
73
%%-----------------------------------------------------------------
 
74
-export([in_reply/6, out_request/6]).
 
75
-compile(export_all).
 
76
 
 
77
%%-----------------------------------------------------------------
 
78
%% Func: all/1
 
79
%% Args: 
 
80
%% Returns: 
 
81
%%-----------------------------------------------------------------
 
82
suite() -> [{ct_hooks,[ts_install_cth]}].
 
83
 
 
84
all() -> 
 
85
    [local_pseudo, local_default, local_local, local_global].
 
86
 
 
87
groups() -> 
 
88
    [].
 
89
 
 
90
init_per_suite(Config) ->
 
91
    Config.
 
92
 
 
93
end_per_suite(_Config) ->
 
94
    ok.
 
95
 
 
96
init_per_group(_GroupName, Config) ->
 
97
    Config.
 
98
 
 
99
end_per_group(_GroupName, Config) ->
 
100
    Config.
 
101
 
 
102
 
 
103
%%-----------------------------------------------------------------
 
104
%% Init and cleanup functions.
 
105
%%-----------------------------------------------------------------
 
106
init_per_testcase(_Case, Config) ->
 
107
    ?line Dog=test_server:timetrap(?default_timeout),
 
108
    Path = code:which(?MODULE),
 
109
    code:add_pathz(filename:join(filename:dirname(Path), "idl_output")),
 
110
    corba:orb_init([{flags, (?ORB_ENV_USE_PI bor ?ORB_ENV_LOCAL_TYPECHECKING)}, 
 
111
                    {local_interceptors, {native, [?MODULE]}}]),
 
112
    orber:jump_start(2945),
 
113
    oe_orber_test_server:oe_register(),
 
114
    [{watchdog, Dog}|Config].
 
115
 
 
116
 
 
117
end_per_testcase(_Case, Config) ->
 
118
    oe_orber_test_server:oe_unregister(),
 
119
    orber:jump_stop(),
 
120
    Path = code:which(?MODULE),
 
121
    code:del_path(filename:join(filename:dirname(Path), "idl_output")),
 
122
    Dog = ?config(watchdog, Config),
 
123
    test_server:timetrap_cancel(Dog),
 
124
    ok.
 
125
 
 
126
%%-----------------------------------------------------------------
 
127
%% Test Case: local_pseudo
 
128
%% Description: 
 
129
%%-----------------------------------------------------------------
 
130
local_pseudo(doc) -> [""];
 
131
local_pseudo(suite) -> [];
 
132
local_pseudo(_) ->
 
133
    ?match({native, [?MODULE]}, orber:get_local_interceptors()),
 
134
    %% Global settings
 
135
    Obj1 = orber_test_server:oe_create(state,[{pseudo,true}]),
 
136
    Result11 = orber_test_server:testing_iiop_ushort(Obj1, ?USHORTMAX),
 
137
    ?match([?USHORTMAX], put(out_request, undefined)),
 
138
    ?match(Result11, put(in_reply, undefined)),
 
139
    
 
140
    Result12 = ?match({'EXCEPTION',_}, 
 
141
                      orber_test_server:testing_iiop_ushort(Obj1, ?USHORTMAX+1)),
 
142
    ?match([(?USHORTMAX+1)], put(out_request, undefined)),
 
143
    ?nomatch(Result12, put(in_reply, undefined)),
 
144
 
 
145
    Result13 = orber_test_server:testing_iiop_oneway_delay(Obj1, 0),
 
146
    ?match([0], put(out_request, undefined)),
 
147
    ?nomatch(Result13, put(in_reply, undefined)),
 
148
    
 
149
    Result14 = ?match({'EXCEPTION', _}, 
 
150
                      orber_test_server:raise_local_exception(Obj1)),
 
151
    ?match([], put(out_request, undefined)),
 
152
    ?match(Result14, put(in_reply, undefined)),
 
153
 
 
154
    Result15 = ?match({'EXCEPTION',_}, orber_test_server:stop_brutal(Obj1)),
 
155
    ?match([], put(out_request, undefined)),
 
156
    ?match(Result15, put(in_reply, undefined)),
 
157
    
 
158
    %% Per-object
 
159
    Obj2 = orber_test_server:oe_create(state,[{pseudo,true},
 
160
                                              {local_interceptors, false}]),
 
161
    
 
162
    Result21 = orber_test_server:testing_iiop_ushort(Obj2, ?USHORTMAX),
 
163
    ?nomatch([?USHORTMAX], put(out_request, undefined)),
 
164
    ?nomatch(Result21, put(in_reply, undefined)),
 
165
 
 
166
    Obj3 = orber_test_server:oe_create(state,[{pseudo,true},
 
167
                                              {local_interceptors, true}]),
 
168
    
 
169
    Result31 = orber_test_server:testing_iiop_ushort(Obj3, ?USHORTMAX),
 
170
    ?match([?USHORTMAX], put(out_request, undefined)),
 
171
    ?match(Result31, put(in_reply, undefined)),
 
172
 
 
173
    ok.
 
174
 
 
175
%%-----------------------------------------------------------------
 
176
%% Test Case: local_default
 
177
%% Description: 
 
178
%%-----------------------------------------------------------------
 
179
local_default(doc) -> [""];
 
180
local_default(suite) -> [];
 
181
local_default(_) ->
 
182
    ?match({native, [?MODULE]}, orber:get_local_interceptors()),
 
183
    %% Global settings
 
184
    Obj1 = orber_test_server:oe_create(state, []),
 
185
    Result11 = orber_test_server:testing_iiop_ushort(Obj1, ?USHORTMAX),
 
186
    ?match([?USHORTMAX], put(out_request, undefined)),
 
187
    ?match(Result11, put(in_reply, undefined)),
 
188
    
 
189
    Result12 = ?match({'EXCEPTION',_}, 
 
190
                      orber_test_server:testing_iiop_ushort(Obj1, ?USHORTMAX+1)),
 
191
    ?match([(?USHORTMAX+1)], put(out_request, undefined)),
 
192
    ?nomatch(Result12, put(in_reply, undefined)),
 
193
 
 
194
    Result13 = orber_test_server:testing_iiop_oneway_delay(Obj1, 0),
 
195
    ?match([0], put(out_request, undefined)),
 
196
    ?nomatch(Result13, put(in_reply, undefined)),
 
197
    
 
198
    Result14 = ?match({'EXCEPTION', _}, 
 
199
                      orber_test_server:raise_local_exception(Obj1)),
 
200
    ?match([], put(out_request, undefined)),
 
201
    ?match(Result14, put(in_reply, undefined)),
 
202
 
 
203
    Result15 = ?match({'EXCEPTION',_}, orber_test_server:stop_brutal(Obj1)),
 
204
    ?match([], put(out_request, undefined)),
 
205
    ?match(Result15, put(in_reply, undefined)),
 
206
    
 
207
    
 
208
    %% Per-object
 
209
    Obj2 = orber_test_server:oe_create(state,[{local_interceptors, false}]),
 
210
    
 
211
    Result21 = orber_test_server:testing_iiop_ushort(Obj2, ?USHORTMAX),
 
212
    ?nomatch([?USHORTMAX], put(out_request, undefined)),
 
213
    ?nomatch(Result21, put(in_reply, undefined)),
 
214
    corba:dispose(Obj2),
 
215
 
 
216
    Obj3 = orber_test_server:oe_create(state,[{local_interceptors, true}]),
 
217
    
 
218
    Result31 = orber_test_server:testing_iiop_ushort(Obj3, ?USHORTMAX),
 
219
    ?match([?USHORTMAX], put(out_request, undefined)),
 
220
    ?match(Result31, put(in_reply, undefined)),
 
221
    corba:dispose(Obj3),
 
222
    ok.
 
223
 
 
224
%%-----------------------------------------------------------------
 
225
%% Test Case: local_local
 
226
%% Description: 
 
227
%%-----------------------------------------------------------------
 
228
local_local(doc) -> [""];
 
229
local_local(suite) -> [];
 
230
local_local(_) ->
 
231
    ?match({native, [?MODULE]}, orber:get_local_interceptors()),
 
232
    %% Global settings
 
233
    Obj1 = orber_test_server:oe_create(state, [{regname, {local, regname}}]),
 
234
    Result11 = orber_test_server:testing_iiop_ushort(Obj1, ?USHORTMAX),
 
235
    ?match([?USHORTMAX], put(out_request, undefined)),
 
236
    ?match(Result11, put(in_reply, undefined)),
 
237
    
 
238
    Result12 = ?match({'EXCEPTION',_}, 
 
239
                      orber_test_server:testing_iiop_ushort(Obj1, ?USHORTMAX+1)),
 
240
    ?match([(?USHORTMAX+1)], put(out_request, undefined)),
 
241
    ?nomatch(Result12, put(in_reply, undefined)),
 
242
 
 
243
    Result13 = orber_test_server:testing_iiop_oneway_delay(Obj1, 0),
 
244
    ?match([0], put(out_request, undefined)),
 
245
    ?nomatch(Result13, put(in_reply, undefined)),
 
246
    
 
247
    Result14 = ?match({'EXCEPTION', _}, 
 
248
                      orber_test_server:raise_local_exception(Obj1)),
 
249
    ?match([], put(out_request, undefined)),
 
250
    ?match(Result14, put(in_reply, undefined)),
 
251
 
 
252
    Result15 = ?match({'EXCEPTION',_}, orber_test_server:stop_brutal(Obj1)),
 
253
    ?match([], put(out_request, undefined)),
 
254
    ?match(Result15, put(in_reply, undefined)),
 
255
    
 
256
    %% Per-object
 
257
    Obj2 = orber_test_server:oe_create(state,[{regname, {local, regname}},
 
258
                                              {local_interceptors, false}]),
 
259
    
 
260
    Result21 = orber_test_server:testing_iiop_ushort(Obj2, ?USHORTMAX),
 
261
    ?nomatch([?USHORTMAX], put(out_request, undefined)),
 
262
    ?nomatch(Result21, put(in_reply, undefined)),
 
263
    corba:dispose(Obj2),
 
264
 
 
265
    Obj3 = orber_test_server:oe_create(state,[{regname, {local, regname}},
 
266
                                              {local_interceptors, true}]),
 
267
    
 
268
    Result31 = orber_test_server:testing_iiop_ushort(Obj3, ?USHORTMAX),
 
269
    ?match([?USHORTMAX], put(out_request, undefined)),
 
270
    ?match(Result31, put(in_reply, undefined)),
 
271
    corba:dispose(Obj3),
 
272
    ok.
 
273
 
 
274
%%-----------------------------------------------------------------
 
275
%% Test Case: local_global
 
276
%% Description: 
 
277
%%-----------------------------------------------------------------
 
278
local_global(doc) -> [""];
 
279
local_global(suite) -> [];
 
280
local_global(_) ->
 
281
    ?match({native, [?MODULE]}, orber:get_local_interceptors()),
 
282
    %% Global settings
 
283
    Obj1 = orber_test_server:oe_create(state, [{regname, {global, regname}}]),
 
284
    Result11 = orber_test_server:testing_iiop_ushort(Obj1, ?USHORTMAX),
 
285
    ?match([?USHORTMAX], put(out_request, undefined)),
 
286
    ?match(Result11, put(in_reply, undefined)),
 
287
    
 
288
    Result12 = ?match({'EXCEPTION',_}, 
 
289
                      orber_test_server:testing_iiop_ushort(Obj1, ?USHORTMAX+1)),
 
290
    ?match([(?USHORTMAX+1)], put(out_request, undefined)),
 
291
    ?nomatch(Result12, put(in_reply, undefined)),
 
292
 
 
293
    Result13 = orber_test_server:testing_iiop_oneway_delay(Obj1, 0),
 
294
    ?match([0], put(out_request, undefined)),
 
295
    ?nomatch(Result13, put(in_reply, undefined)),
 
296
    
 
297
    Result14 = ?match({'EXCEPTION', _}, 
 
298
                      orber_test_server:raise_local_exception(Obj1)),
 
299
    ?match([], put(out_request, undefined)),
 
300
    ?match(Result14, put(in_reply, undefined)),
 
301
 
 
302
    Result15 = ?match({'EXCEPTION',_}, orber_test_server:stop_brutal(Obj1)),
 
303
    ?match([], put(out_request, undefined)),
 
304
    ?match(Result15, put(in_reply, undefined)),
 
305
    
 
306
    %% Per-object
 
307
    Obj2 = orber_test_server:oe_create(state,[{regname, {global, regname}},
 
308
                                              {local_interceptors, false}]),
 
309
    
 
310
    Result21 = orber_test_server:testing_iiop_ushort(Obj2, ?USHORTMAX),
 
311
    ?nomatch([?USHORTMAX], put(out_request, undefined)),
 
312
    ?nomatch(Result21, put(in_reply, undefined)),
 
313
    corba:dispose(Obj2),
 
314
 
 
315
    Obj3 = orber_test_server:oe_create(state,[{regname, {global, regname}},
 
316
                                              {local_interceptors, true}]),
 
317
    
 
318
    Result31 = orber_test_server:testing_iiop_ushort(Obj3, ?USHORTMAX),
 
319
    ?match([?USHORTMAX], put(out_request, undefined)),
 
320
    ?match(Result31, put(in_reply, undefined)),
 
321
    corba:dispose(Obj3),
 
322
    ok.
 
323
 
 
324
 
 
325
 
 
326
 
 
327
%%-----------------------------------------------------------------
 
328
%% Local functions
 
329
%%-----------------------------------------------------------------
 
330
%%-----------------------------------------------------------------
 
331
%% function : in_reply
 
332
%%-----------------------------------------------------------------
 
333
in_reply(Ref, _ObjKey, Ctx, Op, Reply, _Args) ->
 
334
    error_logger:info_msg("=============== in_reply =================
 
335
Connection: ~p
 
336
Operation : ~p
 
337
Reply     : ~p
 
338
Context   : ~p
 
339
==========================================~n", 
 
340
                          [Ref, Op, Reply, Ctx]),
 
341
    put(in_reply, Reply),
 
342
    {Reply, "NewArgs"}.
 
343
 
 
344
%%-----------------------------------------------------------------
 
345
%% function : out_request
 
346
%%-----------------------------------------------------------------
 
347
out_request(Ref, _ObjKey, Ctx, Op, Params, _Args) ->
 
348
    error_logger:info_msg("=============== out_request ==============
 
349
Connection: ~p
 
350
Operation : ~p
 
351
Parameters: ~p
 
352
Context   : ~p
 
353
==========================================~n", 
 
354
                          [Ref, Op, Params, Ctx]),
 
355
    put(out_request, Params),
 
356
    {Params, "NewArgs"}.