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

« back to all changes in this revision

Viewing changes to lib/cosNotification/test/notification_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 1999-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    : notification_SUITE.erl
 
23
%% Purpose : 
 
24
%%--------------------------------------------------------------------
 
25
 
 
26
-module(notification_SUITE).
 
27
 
 
28
%%--------------- INCLUDES -----------------------------------
 
29
-include_lib("orber/include/corba.hrl").
 
30
-include_lib("orber/include/ifr_types.hrl").
 
31
%% cosEvent files.
 
32
-include_lib("cosEvent/include/CosEventChannelAdmin.hrl").
 
33
%% Application files
 
34
-include_lib("cosNotification/include/CosNotification.hrl").
 
35
-include_lib("cosNotification/include/CosNotifyChannelAdmin.hrl").
 
36
-include_lib("cosNotification/include/CosNotifyComm.hrl").
 
37
-include_lib("cosNotification/include/CosNotifyFilter.hrl").
 
38
 
 
39
-include_lib("cosNotification/src/CosNotification_Definitions.hrl").
 
40
 
 
41
-include("idl_output/notify_test.hrl").
 
42
 
 
43
-include_lib("test_server/include/test_server.hrl").
 
44
 
 
45
%%--------------- DEFINES ------------------------------------
 
46
-define(default_timeout, ?t:minutes(20)).
 
47
-define(match(ExpectedRes, Expr),
 
48
        fun() ->
 
49
                AcTuAlReS = (catch (Expr)),
 
50
                case AcTuAlReS of
 
51
                    ExpectedRes ->
 
52
                        io:format("------ CORRECT RESULT ------~n~p~n",
 
53
                                  [AcTuAlReS]),
 
54
                        AcTuAlReS;
 
55
                    _ ->
 
56
                        io:format("###### ERROR ERROR ######~n~p~n",
 
57
                                  [AcTuAlReS]),
 
58
                        ?line exit(AcTuAlReS)
 
59
                end
 
60
        end()).
 
61
 
 
62
-define(defaultQoS,
 
63
        [#'CosNotification_Property'{name='CosNotification':'MaximumBatchSize'(), 
 
64
                                     value=any:create(orber_tc:long(), 100)},
 
65
         #'CosNotification_Property'{name='CosNotification':'PacingInterval'(), 
 
66
                                     value=any:create(orber_tc:unsigned_long_long(), 
 
67
                                                      20000000)},
 
68
         #'CosNotification_Property'{name='CosNotification':'OrderPolicy'(), 
 
69
                                     value=any:create(orber_tc:short(), 
 
70
                                                      'CosNotification':'AnyOrder'())},
 
71
         #'CosNotification_Property'{name='CosNotification':'EventReliability'(), 
 
72
                                     value=any:create(orber_tc:short(), 
 
73
                                                      'CosNotification':'BestEffort'())},
 
74
         #'CosNotification_Property'{name='CosNotification':'ConnectionReliability'(), 
 
75
                                     value=any:create(orber_tc:short(), 
 
76
                                                      'CosNotification':'BestEffort'())},
 
77
         #'CosNotification_Property'{name='CosNotification':'DiscardPolicy'(), 
 
78
                                     value=any:create(orber_tc:short(), 
 
79
                                      'CosNotification':'AnyOrder'())},
 
80
         #'CosNotification_Property'{name='CosNotification':'StartTimeSupported'(), 
 
81
                                     value=any:create(orber_tc:boolean(), false)},
 
82
         #'CosNotification_Property'{name='CosNotification':'StopTimeSupported'(), 
 
83
                                     value=any:create(orber_tc:boolean(), false)},
 
84
         #'CosNotification_Property'{name='CosNotification':'Priority'(), 
 
85
                                     value=any:create(orber_tc:short(), 
 
86
                                      'CosNotification':'DefaultPriority'())}]).
 
87
-define(defaultQoS2,
 
88
        [#'CosNotification_Property'{name='CosNotification':'MaximumBatchSize'(), 
 
89
                                     value=any:create(orber_tc:long(), 1)},
 
90
         #'CosNotification_Property'{name='CosNotification':'PacingInterval'(), 
 
91
                                     value=any:create(orber_tc:unsigned_long_long(), 
 
92
                                                      0)},
 
93
         #'CosNotification_Property'{name='CosNotification':'OrderPolicy'(), 
 
94
                                     value=any:create(orber_tc:short(), 
 
95
                                                      'CosNotification':'AnyOrder'())},
 
96
         #'CosNotification_Property'{name='CosNotification':'EventReliability'(), 
 
97
                                     value=any:create(orber_tc:short(), 
 
98
                                                      'CosNotification':'BestEffort'())},
 
99
         #'CosNotification_Property'{name='CosNotification':'ConnectionReliability'(), 
 
100
                                     value=any:create(orber_tc:short(), 
 
101
                                                      'CosNotification':'BestEffort'())},
 
102
         #'CosNotification_Property'{name='CosNotification':'DiscardPolicy'(), 
 
103
                                     value=any:create(orber_tc:short(), 
 
104
                                      'CosNotification':'AnyOrder'())},
 
105
         #'CosNotification_Property'{name='CosNotification':'StartTimeSupported'(), 
 
106
                                     value=any:create(orber_tc:boolean(), false)},
 
107
         #'CosNotification_Property'{name='CosNotification':'StopTimeSupported'(), 
 
108
                                     value=any:create(orber_tc:boolean(), false)},
 
109
         #'CosNotification_Property'{name='CosNotification':'Priority'(), 
 
110
                                     value=any:create(orber_tc:short(), 
 
111
                                      'CosNotification':'DefaultPriority'())}]).
 
112
-define(defaultAdm,
 
113
        [#'CosNotification_Property'{name='CosNotification':'MaxQueueLength'(), 
 
114
                                     value=any:create(orber_tc:long(), 100)},
 
115
         #'CosNotification_Property'{name='CosNotification':'MaxConsumers'(), 
 
116
                                     value=any:create(orber_tc:long(), 100)},
 
117
         #'CosNotification_Property'{name='CosNotification':'MaxSuppliers'(), 
 
118
                                     value=any:create(orber_tc:long(), 100)}]).
 
119
 
 
120
-define(FAC_OPT, []).
 
121
 
 
122
 
 
123
%%-----------------------------------------------------------------
 
124
%% External exports
 
125
%%-----------------------------------------------------------------
 
126
-export([all/0, suite/0,groups/0,init_per_group/2,end_per_group/2, cases/0, 
 
127
         init_per_suite/1, end_per_suite/1, qos_api/1, adm_api/1,
 
128
         cosevent_api/1, filter_adm_api/1, events_api/1, events2_api/1,
 
129
         event_qos_api/1, filter_api/1, mapping_filter_api/1, subscription_api/1, 
 
130
         init_per_testcase/2, end_per_testcase/2, persistent_max_events_api/1,
 
131
         persistent_timeout_events_api/1, persistent_recover_events_api/1,
 
132
         app_test/1]).
 
133
 
 
134
-export([terminated/1]).
 
135
 
 
136
%%-----------------------------------------------------------------
 
137
%% Func: all/1
 
138
%% Args: 
 
139
%% Returns: 
 
140
%%-----------------------------------------------------------------
 
141
suite() -> [{ct_hooks,[ts_install_cth]}].
 
142
 
 
143
all() -> 
 
144
    cases().
 
145
 
 
146
groups() -> 
 
147
    [].
 
148
 
 
149
init_per_group(_GroupName, Config) ->
 
150
    Config.
 
151
 
 
152
end_per_group(_GroupName, Config) ->
 
153
    Config.
 
154
 
 
155
cases() -> 
 
156
    [persistent_max_events_api,
 
157
     persistent_timeout_events_api,
 
158
     persistent_recover_events_api, mapping_filter_api,
 
159
     filter_api, filter_adm_api, event_qos_api, qos_api,
 
160
     adm_api, cosevent_api, subscription_api, events_api,
 
161
     events2_api, app_test].
 
162
 
 
163
%%-----------------------------------------------------------------
 
164
%% Init and cleanup functions.
 
165
%%-----------------------------------------------------------------
 
166
 
 
167
init_per_testcase(_Case, Config) ->
 
168
    Path = code:which(?MODULE),
 
169
    code:add_pathz(filename:join(filename:dirname(Path), "idl_output")),
 
170
    ?line Dog=test_server:timetrap(?default_timeout),
 
171
    [{watchdog, Dog}|Config].
 
172
 
 
173
 
 
174
end_per_testcase(_Case, Config) ->
 
175
    Path = code:which(?MODULE),
 
176
    code:del_path(filename:join(filename:dirname(Path), "idl_output")),
 
177
    Dog = ?config(watchdog, Config),
 
178
    test_server:timetrap_cancel(Dog),
 
179
    ok.
 
180
 
 
181
init_per_suite(Config) ->
 
182
    Path = code:which(?MODULE),
 
183
    code:add_pathz(filename:join(filename:dirname(Path), "idl_output")),
 
184
    ok = corba:orb_init([{flags, 16#02}, {orber_debug_level, 10}]),
 
185
    orber:jump_start(),
 
186
    cosNotificationApp:install_event(),
 
187
    cosNotificationApp:install(),
 
188
    'oe_notify_test_server':'oe_register'(),
 
189
    cosNotificationApp:start(),
 
190
    if
 
191
        is_list(Config) ->
 
192
            Config;
 
193
        true ->
 
194
            exit("Config not a list")
 
195
    end.
 
196
 
 
197
end_per_suite(Config) ->
 
198
    cosNotificationApp:stop(),
 
199
    Path = code:which(?MODULE),
 
200
    code:del_path(filename:join(filename:dirname(Path), "idl_output")),
 
201
    'oe_notify_test_server':'oe_unregister'(),
 
202
    cosNotificationApp:uninstall(),
 
203
    cosNotificationApp:uninstall_event(),
 
204
    orber:jump_stop(),
 
205
    Config.
 
206
 
 
207
 
 
208
%%-----------------------------------------------------------------
 
209
%%  Tests app file
 
210
%%-----------------------------------------------------------------
 
211
app_test(doc) -> [];
 
212
app_test(suite) -> [];
 
213
app_test(_Config) ->
 
214
    ok=test_server:app_test(cosNotification),
 
215
    ok.
 
216
 
 
217
 
 
218
%%-----------------------------------------------------------------
 
219
%%  Persistent events max limit
 
220
%%-----------------------------------------------------------------
 
221
persistent_max_events_api(doc) -> ["CosNotification QoS EventReliability Persistent", 
 
222
                               ""];
 
223
persistent_max_events_api(suite) -> [];
 
224
persistent_max_events_api(_Config) ->
 
225
    QoSPersistent = 
 
226
        [#'CosNotification_Property'{name='CosNotification':'ConnectionReliability'(), 
 
227
                                     value=any:create(orber_tc:short(), 
 
228
                                                      'CosNotification':'Persistent'())}],
 
229
    QoSEventPersistent = 
 
230
        [#'CosNotification_Property'{name='CosNotification':'EventReliability'(), 
 
231
                                     value=any:create(orber_tc:short(), 
 
232
                                                      'CosNotification':'Persistent'())}],
 
233
    application:set_env(cosNotification, notify, ?MODULE),
 
234
    application:set_env(cosNotification, max_events, 2),
 
235
    application:set_env(cosNotification, timeout_events, 300000),
 
236
    application:set_env(cosNotification, interval_events, 10000),
 
237
    %% Initialize the application.
 
238
    Fac = (catch cosNotificationApp:start_global_factory(?FAC_OPT)),
 
239
    ?match({_,key,_,_,_,_}, Fac),
 
240
    {Ch, _Id1} = (catch 'CosNotifyChannelAdmin_EventChannelFactory':create_channel(Fac, ?defaultQoS2, ?defaultAdm)),
 
241
    ?match({_,key,_,_,_,_}, Ch),
 
242
 
 
243
    ?match(ok, 'CosNotification_QoSAdmin':set_qos(Ch, QoSEventPersistent)),
 
244
    ?match(ok, 'CosNotification_QoSAdmin':set_qos(Ch, QoSPersistent)),
 
245
    
 
246
    %% Create the Admin objects
 
247
    {AdminSupplier, _ASID}=?match({{_,key,_,_,_,_},_},
 
248
        'CosNotifyChannelAdmin_EventChannel':new_for_suppliers(Ch,'AND_OP')),
 
249
    {AdminConsumer, _ACID}=?match({{_,key,_,_,_,_},_}, 
 
250
        'CosNotifyChannelAdmin_EventChannel':new_for_consumers(Ch,'AND_OP')),
 
251
 
 
252
    %% Create Proxies and clients
 
253
    {SequenceProxyPushSupplier,_ID}=?match({{_,key,_,_,_,_},_},
 
254
        'CosNotifyChannelAdmin_ConsumerAdmin':obtain_notification_push_supplier(AdminConsumer, 'SEQUENCE_EVENT')),
 
255
    PushSeqC=?match({_,key,_,_,_,_}, 'notify_test_SeqPushC':oe_create(['PUSH_SEQUENCE',SequenceProxyPushSupplier],
 
256
                                                                      [{local_typecheck, false}])),
 
257
    ?match(ok, 'CosNotifyChannelAdmin_SequenceProxyPushSupplier':connect_sequence_push_consumer(SequenceProxyPushSupplier, PushSeqC)),
 
258
 
 
259
    {SequenceProxyPushConsumer,_ID}=?match({{_,key,_,_,_,_},_},
 
260
        'CosNotifyChannelAdmin_SupplierAdmin':obtain_notification_push_consumer(AdminSupplier, 'SEQUENCE_EVENT')),
 
261
    PushSeqS=?match({_,key,_,_,_,_}, 'notify_test_SeqPushS':oe_create(['PUSH_SEQUENCE',SequenceProxyPushConsumer],
 
262
                                                                      [{local_typecheck, false}])),
 
263
    ?match(ok, 'CosNotifyChannelAdmin_SequenceProxyPushConsumer':connect_sequence_push_supplier(SequenceProxyPushConsumer, PushSeqS)),
 
264
    
 
265
    %% Create a couple of Events to test with.
 
266
    Event = ?not_CreateSE("DomainName","CommunicationsAlarm",
 
267
                          "lost_packet",
 
268
                          [#'CosNotification_Property'{name="priority", 
 
269
                                                       value=any:create(orber_tc:short(), 1)}],
 
270
                          [], any:create(orber_tc:null(), null)),
 
271
    
 
272
    ?match(ok, 'notify_test_SeqPushC':doAction(PushSeqC, {action, action})),
 
273
    
 
274
    %% Push and check the state.
 
275
    ?match(ok,'CosNotifyChannelAdmin_SequenceProxyPushConsumer':push_structured_events(SequenceProxyPushConsumer, [Event])),
 
276
    ?match([], 'notify_test_SeqPushC':doAction(PushSeqC, return_data)),
 
277
    ?match(false, corba_object:non_existent(SequenceProxyPushSupplier)),
 
278
 
 
279
    ?match(ok,'CosNotifyChannelAdmin_SequenceProxyPushConsumer':push_structured_events(SequenceProxyPushConsumer, [Event])),
 
280
    ?match([], 'notify_test_SeqPushC':doAction(PushSeqC, return_data)),
 
281
    ?match(false, corba_object:non_existent(SequenceProxyPushSupplier)),
 
282
    %% Now we've reached the limit. This call will terminate the proxy.
 
283
    %% We cannot check for data at this point since the broken connection
 
284
    %% will result in that the client terminates.
 
285
    ?match(ok,'CosNotifyChannelAdmin_SequenceProxyPushConsumer':push_structured_events(SequenceProxyPushConsumer, [Event])),
 
286
    timer:sleep(5000),
 
287
    ?match(true, corba_object:non_existent(SequenceProxyPushSupplier)),
 
288
    ?match(true, corba_object:non_existent(PushSeqC)),
 
289
 
 
290
 
 
291
    catch corba:dispose(SequenceProxyPushConsumer),
 
292
    catch corba:dispose(SequenceProxyPushSupplier),
 
293
    catch corba:dispose(AdminConsumer),
 
294
    catch corba:dispose(AdminSupplier),
 
295
    catch corba:dispose(Ch),
 
296
    catch cosNotificationApp:stop_factory(Fac),
 
297
    catch corba:dispose(PushSeqS),
 
298
    catch corba:dispose(PushSeqC),
 
299
    application:set_env(cosNotification, notify, undefined),
 
300
    application:set_env(cosNotification, max_events, undefined),
 
301
    application:set_env(cosNotification, timeout_events, undefined),
 
302
    application:set_env(cosNotification, interval_events, undefined),
 
303
    ok.
 
304
 
 
305
terminated(Items) ->
 
306
    io:format("Proxy terminated due to: ~p~n", [Items]).
 
307
 
 
308
%%-----------------------------------------------------------------
 
309
%%  Persistent events timeout
 
310
%%-----------------------------------------------------------------
 
311
persistent_timeout_events_api(doc) -> 
 
312
    ["CosNotification QoS EventReliability Persistent", 
 
313
     ""];
 
314
persistent_timeout_events_api(suite) -> [];
 
315
persistent_timeout_events_api(_Config) ->
 
316
    QoSPersistent = 
 
317
        [#'CosNotification_Property'{name='CosNotification':'ConnectionReliability'(), 
 
318
                                     value=any:create(orber_tc:short(), 
 
319
                                                      'CosNotification':'Persistent'())}],
 
320
    QoSEventPersistent = 
 
321
        [#'CosNotification_Property'{name='CosNotification':'EventReliability'(), 
 
322
                                     value=any:create(orber_tc:short(), 
 
323
                                                      'CosNotification':'Persistent'())}],
 
324
    application:set_env(cosNotification, notify, ?MODULE),
 
325
    application:set_env(cosNotification, max_events, 1000),
 
326
    application:set_env(cosNotification, timeout_events, 4000),
 
327
    application:set_env(cosNotification, interval_events, 1000),
 
328
    %% Initialize the application.
 
329
    Fac = (catch cosNotificationApp:start_global_factory(?FAC_OPT)),
 
330
    ?match({_,key,_,_,_,_}, Fac),
 
331
    {Ch, _Id1} = (catch 'CosNotifyChannelAdmin_EventChannelFactory':create_channel(Fac, ?defaultQoS2, ?defaultAdm)),
 
332
    ?match({_,key,_,_,_,_}, Ch),
 
333
 
 
334
    ?match(ok, 'CosNotification_QoSAdmin':set_qos(Ch, QoSEventPersistent)),
 
335
    ?match(ok, 'CosNotification_QoSAdmin':set_qos(Ch, QoSPersistent)),
 
336
    
 
337
    %% Create the Admin objects
 
338
    {AdminSupplier, _ASID}=?match({{_,key,_,_,_,_},_},
 
339
        'CosNotifyChannelAdmin_EventChannel':new_for_suppliers(Ch,'AND_OP')),
 
340
    {AdminConsumer, _ACID}=?match({{_,key,_,_,_,_},_}, 
 
341
        'CosNotifyChannelAdmin_EventChannel':new_for_consumers(Ch,'AND_OP')),
 
342
 
 
343
    %% Create Proxies and clients
 
344
    {SequenceProxyPushSupplier,_ID}=?match({{_,key,_,_,_,_},_},
 
345
        'CosNotifyChannelAdmin_ConsumerAdmin':obtain_notification_push_supplier(AdminConsumer, 'SEQUENCE_EVENT')),
 
346
    PushSeqC=?match({_,key,_,_,_,_}, 'notify_test_SeqPushC':oe_create(['PUSH_SEQUENCE',SequenceProxyPushSupplier],
 
347
                                                                      [{local_typecheck, false}])),
 
348
    ?match(ok, 'CosNotifyChannelAdmin_SequenceProxyPushSupplier':connect_sequence_push_consumer(SequenceProxyPushSupplier, PushSeqC)),
 
349
 
 
350
    {SequenceProxyPushConsumer,_ID}=?match({{_,key,_,_,_,_},_},
 
351
        'CosNotifyChannelAdmin_SupplierAdmin':obtain_notification_push_consumer(AdminSupplier, 'SEQUENCE_EVENT')),
 
352
    PushSeqS=?match({_,key,_,_,_,_}, 'notify_test_SeqPushS':oe_create(['PUSH_SEQUENCE',SequenceProxyPushConsumer],
 
353
                                                                      [{local_typecheck, false}])),
 
354
    ?match(ok, 'CosNotifyChannelAdmin_SequenceProxyPushConsumer':connect_sequence_push_supplier(SequenceProxyPushConsumer, PushSeqS)),
 
355
    
 
356
    %% Create a couple of Events to test with.
 
357
    Event = ?not_CreateSE("DomainName","CommunicationsAlarm",
 
358
                          "lost_packet",
 
359
                          [#'CosNotification_Property'{name="priority", 
 
360
                                                       value=any:create(orber_tc:short(), 1)}],
 
361
                          [], any:create(orber_tc:null(), null)),
 
362
    
 
363
    ?match(ok, 'notify_test_SeqPushC':doAction(PushSeqC, {action, action})),
 
364
    
 
365
    %% Push and check the state.
 
366
    ?match(ok,'CosNotifyChannelAdmin_SequenceProxyPushConsumer':push_structured_events(SequenceProxyPushConsumer, [Event])),
 
367
    ?match([], 'notify_test_SeqPushC':doAction(PushSeqC, return_data)),
 
368
    ?match(false, corba_object:non_existent(SequenceProxyPushSupplier)),
 
369
 
 
370
    %% Now we've reached the limit. This call will terminate the proxy.
 
371
    %% We cannot check for data at this point since the broken connection
 
372
    %% will result in that the client terminates.
 
373
    ?match(ok,'CosNotifyChannelAdmin_SequenceProxyPushConsumer':push_structured_events(SequenceProxyPushConsumer, [Event])),
 
374
    timer:sleep(10000),
 
375
    ?match(true, corba_object:non_existent(SequenceProxyPushSupplier)),
 
376
    ?match(true, corba_object:non_existent(PushSeqC)),
 
377
 
 
378
 
 
379
    catch corba:dispose(SequenceProxyPushConsumer),
 
380
    catch corba:dispose(SequenceProxyPushSupplier),
 
381
    catch corba:dispose(AdminConsumer),
 
382
    catch corba:dispose(AdminSupplier),
 
383
    catch corba:dispose(Ch),
 
384
    catch cosNotificationApp:stop_factory(Fac),
 
385
    catch corba:dispose(PushSeqS),
 
386
    catch corba:dispose(PushSeqC),
 
387
    application:set_env(cosNotification, notify, undefined),
 
388
    application:set_env(cosNotification, max_events, undefined),
 
389
    application:set_env(cosNotification, timeout_events, undefined),
 
390
    application:set_env(cosNotification, interval_events, undefined),
 
391
    ok.
 
392
 
 
393
%%-----------------------------------------------------------------
 
394
%%  Persistent events max limit
 
395
%%-----------------------------------------------------------------
 
396
persistent_recover_events_api(doc) -> 
 
397
    ["CosNotification QoS EventReliability Persistent", 
 
398
     ""];
 
399
persistent_recover_events_api(suite) -> [];
 
400
persistent_recover_events_api(_Config) ->
 
401
    QoSPersistent = 
 
402
        [#'CosNotification_Property'{name='CosNotification':'ConnectionReliability'(), 
 
403
                                     value=any:create(orber_tc:short(), 
 
404
                                                      'CosNotification':'Persistent'())}],
 
405
    QoSEventPersistent = 
 
406
        [#'CosNotification_Property'{name='CosNotification':'EventReliability'(), 
 
407
                                     value=any:create(orber_tc:short(), 
 
408
                                                      'CosNotification':'Persistent'())}],
 
409
    application:set_env(cosNotification, notify, ?MODULE),
 
410
    application:set_env(cosNotification, max_events, 1000),
 
411
    application:set_env(cosNotification, timeout_events, 100000),
 
412
    application:set_env(cosNotification, interval_events, 1000),
 
413
    %% Initialize the application.
 
414
    Fac = (catch cosNotificationApp:start_global_factory(?FAC_OPT)),
 
415
    ?match({_,key,_,_,_,_}, Fac),
 
416
    {Ch, _Id1} = (catch 'CosNotifyChannelAdmin_EventChannelFactory':create_channel(Fac, ?defaultQoS2, ?defaultAdm)),
 
417
    ?match({_,key,_,_,_,_}, Ch),
 
418
 
 
419
    ?match(ok, 'CosNotification_QoSAdmin':set_qos(Ch, QoSEventPersistent)),
 
420
    ?match(ok, 'CosNotification_QoSAdmin':set_qos(Ch, QoSPersistent)),
 
421
    
 
422
    %% Create the Admin objects
 
423
    {AdminSupplier, _ASID}=?match({{_,key,_,_,_,_},_},
 
424
        'CosNotifyChannelAdmin_EventChannel':new_for_suppliers(Ch,'AND_OP')),
 
425
    {AdminConsumer, _ACID}=?match({{_,key,_,_,_,_},_}, 
 
426
        'CosNotifyChannelAdmin_EventChannel':new_for_consumers(Ch,'AND_OP')),
 
427
 
 
428
    %% Create Proxies and clients
 
429
    {SequenceProxyPushSupplier,_ID}=?match({{_,key,_,_,_,_},_},
 
430
        'CosNotifyChannelAdmin_ConsumerAdmin':obtain_notification_push_supplier(AdminConsumer, 'SEQUENCE_EVENT')),
 
431
    PushSeqC=?match({_,key,_,_,_,_}, 'notify_test_SeqPushC':oe_create(['PUSH_SEQUENCE',SequenceProxyPushSupplier],
 
432
                                                                      [{local_typecheck, false}])),
 
433
    ?match(ok, 'CosNotifyChannelAdmin_SequenceProxyPushSupplier':connect_sequence_push_consumer(SequenceProxyPushSupplier, PushSeqC)),
 
434
 
 
435
    {SequenceProxyPushConsumer,_ID}=?match({{_,key,_,_,_,_},_},
 
436
        'CosNotifyChannelAdmin_SupplierAdmin':obtain_notification_push_consumer(AdminSupplier, 'SEQUENCE_EVENT')),
 
437
    PushSeqS=?match({_,key,_,_,_,_}, 'notify_test_SeqPushS':oe_create(['PUSH_SEQUENCE',SequenceProxyPushConsumer],
 
438
                                                                      [{local_typecheck, false}])),
 
439
    ?match(ok, 'CosNotifyChannelAdmin_SequenceProxyPushConsumer':connect_sequence_push_supplier(SequenceProxyPushConsumer, PushSeqS)),
 
440
    
 
441
    %% Create a couple of Events to test with.
 
442
    Event = ?not_CreateSE("DomainName","CommunicationsAlarm",
 
443
                           "lost_packet",
 
444
                          [#'CosNotification_Property'{name="priority", 
 
445
                                                       value=any:create(orber_tc:short(), 1)}],
 
446
                          [], any:create(orber_tc:null(), null)),
 
447
    
 
448
    ?match(ok, 'notify_test_SeqPushC':doAction(PushSeqC, {action, action})),
 
449
    
 
450
    %% Push and check the state.
 
451
    ?match(ok,'CosNotifyChannelAdmin_SequenceProxyPushConsumer':push_structured_events(SequenceProxyPushConsumer, [Event])),
 
452
    ?match([], 'notify_test_SeqPushC':doAction(PushSeqC, return_data)),
 
453
    ?match(false, corba_object:non_existent(SequenceProxyPushSupplier)),
 
454
    %% Allow the proxy to try a few times and then change the client behavior
 
455
    timer:sleep(4000),
 
456
    ?match(ok, 'notify_test_SeqPushC':doAction(PushSeqC, {action, undefined})),
 
457
    %% Wait some time so that the proxy timeout has kicked in.
 
458
    timer:sleep(4000),
 
459
 
 
460
    %% Now the communication should work again.
 
461
    ?match([Event], 'notify_test_SeqPushC':doAction(PushSeqC, return_data)),
 
462
    ?match(false, corba_object:non_existent(SequenceProxyPushSupplier)),
 
463
 
 
464
    ?match(ok,'CosNotifyChannelAdmin_SequenceProxyPushConsumer':push_structured_events(SequenceProxyPushConsumer, [Event])),
 
465
    timer:sleep(4000),
 
466
    ?match([Event], 'notify_test_SeqPushC':doAction(PushSeqC, return_data)),
 
467
 
 
468
    catch corba:dispose(SequenceProxyPushConsumer),
 
469
    catch corba:dispose(SequenceProxyPushSupplier),
 
470
    catch corba:dispose(AdminConsumer),
 
471
    catch corba:dispose(AdminSupplier),
 
472
    catch corba:dispose(Ch),
 
473
    catch cosNotificationApp:stop_factory(Fac),
 
474
    catch corba:dispose(PushSeqS),
 
475
    catch corba:dispose(PushSeqC),
 
476
    application:set_env(cosNotification, notify, undefined),
 
477
    application:set_env(cosNotification, max_events, undefined),
 
478
    application:set_env(cosNotification, timeout_events, undefined),
 
479
    application:set_env(cosNotification, interval_events, undefined),
 
480
    ok.
 
481
 
 
482
 
 
483
%%-----------------------------------------------------------------
 
484
%%  CosNotifyFilter::Filter API tests 
 
485
%%-----------------------------------------------------------------
 
486
mapping_filter_api(doc) -> ["CosNotifyFilter::MappingFilter API tests.", ""];
 
487
mapping_filter_api(suite) -> [];
 
488
mapping_filter_api(_Config) ->
 
489
    FiFac = 'CosNotifyFilter_FilterFactory':oe_create(),
 
490
    ?match({_,key,_,_,_,_}, FiFac),
 
491
    
 
492
    Filter = 'CosNotifyFilter_FilterFactory':create_mapping_filter(FiFac,
 
493
                                                                         "EXTENDED_TCL",
 
494
                                                                         any:create(orber_tc:short(), 10)),
 
495
    ?match({_,key,_,_,_,_}, Filter),
 
496
 
 
497
    ?match("EXTENDED_TCL", 'CosNotifyFilter_MappingFilter':'_get_constraint_grammar'(Filter)),
 
498
 
 
499
    %% Test before we add any constarints.
 
500
    ?match([], 'CosNotifyFilter_MappingFilter':get_all_mapping_constraints(Filter)),
 
501
    ?match({'EXCEPTION', {'CosNotifyFilter_ConstraintNotFound', _, 1}},
 
502
                 'CosNotifyFilter_MappingFilter':get_mapping_constraints(Filter, [1])),
 
503
    ?match(ok, 'CosNotifyFilter_MappingFilter':remove_all_mapping_constraints(Filter)),
 
504
 
 
505
    %% Try adding an incorrect constraint_expr
 
506
    ?match({'EXCEPTION',{'CosNotifyFilter_InvalidConstraint',_,_}},
 
507
           'CosNotifyFilter_MappingFilter':add_mapping_constraints(Filter, 
 
508
                        [#'CosNotifyFilter_MappingConstraintPair'
 
509
                         {constraint_expression = #'CosNotifyFilter_ConstraintExp'
 
510
                          {event_types = [#'CosNotification_EventType'
 
511
                                          {domain_name = "name",
 
512
                                           type_name = "type"}],
 
513
                           constraint_expr = "2==2 and 3<"},
 
514
                          result_to_set = any:create(orber_tc:short(), 10)}])),
 
515
    %% Try adding two correct constraint_expr
 
516
    ?line[{_,_,CID1,_},{_,_,CID2,_}]= 
 
517
        ?match([{'CosNotifyFilter_MappingConstraintInfo',_,_,_}, {'CosNotifyFilter_MappingConstraintInfo',_,_,_}],
 
518
           'CosNotifyFilter_MappingFilter':add_mapping_constraints(Filter, 
 
519
                        [#'CosNotifyFilter_MappingConstraintPair'
 
520
                         {constraint_expression = #'CosNotifyFilter_ConstraintExp'
 
521
                          {event_types = [#'CosNotification_EventType'
 
522
                                          {domain_name = "name",
 
523
                                           type_name = "type"}],
 
524
                           constraint_expr = "2==2 and 3<4"},
 
525
                          result_to_set = any:create(orber_tc:short(), 10)},
 
526
                        #'CosNotifyFilter_MappingConstraintPair'
 
527
                         {constraint_expression = #'CosNotifyFilter_ConstraintExp'
 
528
                          {event_types = [#'CosNotification_EventType'
 
529
                                          {domain_name = "name2",
 
530
                                           type_name = "type2"}],
 
531
                           constraint_expr = "$.test._length == 3 and ($.test[0].score + $.test[1].score + $.test[2].score)/3 >=80"},
 
532
                          result_to_set = any:create(orber_tc:short(), 10)}])),
 
533
 
 
534
    ?match([{'CosNotifyFilter_MappingConstraintInfo',_,CID2,_}, {'CosNotifyFilter_MappingConstraintInfo',_,CID1,_}],
 
535
                 'CosNotifyFilter_MappingFilter':get_all_mapping_constraints(Filter)),
 
536
    ?match([{'CosNotifyFilter_MappingConstraintInfo',_,CID1,_}], 
 
537
                 'CosNotifyFilter_MappingFilter':get_mapping_constraints(Filter, [CID1])),
 
538
    ?match(ok, 'CosNotifyFilter_MappingFilter':remove_all_mapping_constraints(Filter)),
 
539
    ?match([], 'CosNotifyFilter_MappingFilter':get_all_mapping_constraints(Filter)),
 
540
 
 
541
    %% Try adding a constraint_expr with using invalid value, i.e., not short.
 
542
    ?match({'EXCEPTION',{'CosNotifyFilter_InvalidValue',_,_,_}},
 
543
           'CosNotifyFilter_MappingFilter':add_mapping_constraints(Filter, 
 
544
                        [#'CosNotifyFilter_MappingConstraintPair'
 
545
                         {constraint_expression = #'CosNotifyFilter_ConstraintExp'
 
546
                          {event_types = [#'CosNotification_EventType'
 
547
                                          {domain_name = "name",
 
548
                                           type_name = "type"}],
 
549
                           constraint_expr = "2==2 and 3<8"},
 
550
                          result_to_set = any:create(orber_tc:long(), 10)}])),
 
551
 
 
552
    %% Try adding one correct and one incorrect constraint_expr
 
553
    ?match({'EXCEPTION',{'CosNotifyFilter_InvalidConstraint',_,_}},
 
554
           'CosNotifyFilter_MappingFilter':add_mapping_constraints(Filter, 
 
555
                        [#'CosNotifyFilter_MappingConstraintPair'
 
556
                         {constraint_expression = #'CosNotifyFilter_ConstraintExp'
 
557
                          {event_types = [#'CosNotification_EventType'
 
558
                                          {domain_name = "name",
 
559
                                           type_name = "type"}],
 
560
                           constraint_expr = "2==2 and 3<"},
 
561
                          result_to_set = any:create(orber_tc:short(), 10)},
 
562
                        #'CosNotifyFilter_MappingConstraintPair'
 
563
                         {constraint_expression = #'CosNotifyFilter_ConstraintExp'
 
564
                          {event_types = [#'CosNotification_EventType'
 
565
                                          {domain_name = "name2",
 
566
                                           type_name = "type2"}],
 
567
                           constraint_expr = "$.test._length == 3 and ($.test[0].score + $.test[1].score + $.test[2].score)/3 >=80"},
 
568
                          result_to_set = any:create(orber_tc:short(), 10)}])),
 
569
 
 
570
    %% Following testcases test different domain_name and type_name, e.g., 
 
571
    %% wildcards etc.
 
572
    [{_,ConInfoData,CID3,_}] = 
 
573
        ?match([{'CosNotifyFilter_MappingConstraintInfo',_,_,_}],
 
574
           'CosNotifyFilter_MappingFilter':add_mapping_constraints(Filter, 
 
575
                        [#'CosNotifyFilter_MappingConstraintPair'
 
576
                         {constraint_expression = #'CosNotifyFilter_ConstraintExp'
 
577
                          {event_types = [#'CosNotification_EventType'
 
578
                                          {domain_name = "domain",
 
579
                                           type_name = ""},
 
580
                                          #'CosNotification_EventType'
 
581
                                          {domain_name = "*",
 
582
                                           type_name = "type"}],
 
583
                           constraint_expr = "2==2 and 3<4"},
 
584
                          result_to_set = any:create(orber_tc:short(), 10)}])),
 
585
 
 
586
    %% Try removing a constraint
 
587
    ?match(ok, 'CosNotifyFilter_MappingFilter':modify_mapping_constraints(Filter,[CID3],[])),
 
588
    ?match([], 'CosNotifyFilter_MappingFilter':get_all_mapping_constraints(Filter)),
 
589
 
 
590
    %% Add e new constraint
 
591
    [{_,_,CID4,_}] = 
 
592
        ?match([{'CosNotifyFilter_MappingConstraintInfo',_,_,_}],
 
593
                 'CosNotifyFilter_MappingFilter':add_mapping_constraints(Filter, 
 
594
                        [#'CosNotifyFilter_MappingConstraintPair'
 
595
                         {constraint_expression = #'CosNotifyFilter_ConstraintExp'
 
596
                          {event_types = [#'CosNotification_EventType'
 
597
                                          {domain_name = "domain1",
 
598
                                           type_name = ""},
 
599
                                          #'CosNotification_EventType'
 
600
                                          {domain_name = "domain2",
 
601
                                           type_name = "*"}],
 
602
                           constraint_expr = "2==2 and 3<4"},
 
603
                          result_to_set = any:create(orber_tc:short(), 10)}])),
 
604
 
 
605
    %% Try to update the constraint associated with CID4 to equal CID3.
 
606
    ?match(ok, 'CosNotifyFilter_MappingFilter':modify_mapping_constraints(Filter,[],
 
607
                         [#'CosNotifyFilter_MappingConstraintInfo'
 
608
                          {constraint_expression=
 
609
                           #'CosNotifyFilter_ConstraintExp'
 
610
                           {event_types =[#'CosNotification_EventType'
 
611
                                          {domain_name = "domain",
 
612
                                           type_name = ""},
 
613
                                          #'CosNotification_EventType'
 
614
                                          {domain_name = "*",
 
615
                                           type_name = "type"}],
 
616
                            constraint_expr = "2==2 and 3<4"},
 
617
                           constraint_id=CID4,
 
618
                           value = any:create(orber_tc:short(), 10)}])),
 
619
 
 
620
    ?match([{_,ConInfoData,CID4,_}], 'CosNotifyFilter_MappingFilter':get_all_mapping_constraints(Filter)),
 
621
 
 
622
    ?match({'EXCEPTION', {'CosNotifyFilter_ConstraintNotFound', _, CID3}},
 
623
                 'CosNotifyFilter_MappingFilter':get_mapping_constraints(Filter, [CID3])),
 
624
    ?match(ok, 'CosNotifyFilter_MappingFilter':remove_all_mapping_constraints(Filter)),
 
625
    ?match([], 'CosNotifyFilter_MappingFilter':get_all_mapping_constraints(Filter)),
 
626
 
 
627
    ?match([{'CosNotifyFilter_MappingConstraintInfo',_,_,_}],
 
628
           'CosNotifyFilter_MappingFilter':add_mapping_constraints(Filter, 
 
629
                        [#'CosNotifyFilter_MappingConstraintPair'
 
630
                         {constraint_expression = #'CosNotifyFilter_ConstraintExp'
 
631
                          {event_types = [#'CosNotification_EventType'
 
632
                                          {domain_name = "",
 
633
                                           type_name = "type1"},
 
634
                                          #'CosNotification_EventType'
 
635
                                          {domain_name = "*",
 
636
                                           type_name = "type2"}],
 
637
                           constraint_expr = "2==2 and 3<4"},
 
638
                          result_to_set = any:create(orber_tc:short(), 10)}])),
 
639
 
 
640
    ?match([{'CosNotifyFilter_MappingConstraintInfo',_,_,_}],
 
641
           'CosNotifyFilter_MappingFilter':add_mapping_constraints(Filter, 
 
642
                        [#'CosNotifyFilter_MappingConstraintPair'
 
643
                         {constraint_expression = #'CosNotifyFilter_ConstraintExp'
 
644
                          {event_types = [#'CosNotification_EventType'
 
645
                                          {domain_name = "domain1",
 
646
                                           type_name = "type1"},
 
647
                                          #'CosNotification_EventType'
 
648
                                          {domain_name = "domain2",
 
649
                                           type_name = "type2"}],
 
650
                           constraint_expr = "2==2 and 3<4"},
 
651
                          result_to_set = any:create(orber_tc:short(), 10)}])),
 
652
 
 
653
    ?match([{'CosNotifyFilter_MappingConstraintInfo',_,_,_}],
 
654
           'CosNotifyFilter_MappingFilter':add_mapping_constraints(Filter, 
 
655
                        [#'CosNotifyFilter_MappingConstraintPair'
 
656
                         {constraint_expression = #'CosNotifyFilter_ConstraintExp'
 
657
                          {event_types = [#'CosNotification_EventType'
 
658
                                          {domain_name = "dom*",
 
659
                                           type_name = "type1"},
 
660
                                          #'CosNotification_EventType'
 
661
                                          {domain_name = "domain2",
 
662
                                           type_name = "typ*"}],
 
663
                           constraint_expr = "2==2 and 3<4"},
 
664
                          result_to_set = any:create(orber_tc:short(), 10)}])),
 
665
 
 
666
    ?match([{'CosNotifyFilter_MappingConstraintInfo',_,_,_}],
 
667
           'CosNotifyFilter_MappingFilter':add_mapping_constraints(Filter, 
 
668
                        [#'CosNotifyFilter_MappingConstraintPair'
 
669
                         {constraint_expression = #'CosNotifyFilter_ConstraintExp'
 
670
                          {event_types = [#'CosNotification_EventType'
 
671
                                          {domain_name = "dom*1",
 
672
                                           type_name = "type1"},
 
673
                                         #'CosNotification_EventType'
 
674
                                          {domain_name = "domain2",
 
675
                                           type_name = "typ*2"}],
 
676
                           constraint_expr = "2==2 and 3<4"},
 
677
                          result_to_set = any:create(orber_tc:short(), 10)}])),
 
678
 
 
679
    catch corba:dispose(FiFac),
 
680
    catch corba:dispose(Filter),
 
681
    ok.
 
682
 
 
683
 
 
684
%%-----------------------------------------------------------------
 
685
%%  CosNotifyFilter::Filter API tests 
 
686
%%-----------------------------------------------------------------
 
687
filter_api(doc) -> ["CosNotifyFilter::Filter API tests.", ""];
 
688
filter_api(suite) -> [];
 
689
filter_api(_Config) ->
 
690
    Fac = cosNotificationApp:start_global_factory(?FAC_OPT),
 
691
    ?match({_,key,_,_,_,_}, Fac),
 
692
    {Ch, _Id1} = 'CosNotifyChannelAdmin_EventChannelFactory':create_channel(Fac, ?defaultQoS, ?defaultAdm),
 
693
    AC= 'CosNotifyChannelAdmin_EventChannel':for_consumers(Ch),
 
694
 
 
695
    FiFac = 'CosNotifyFilter_FilterFactory':oe_create(),
 
696
    ?match({_,key,_,_,_,_}, FiFac),
 
697
    
 
698
    Filter = 'CosNotifyFilter_FilterFactory':create_filter(FiFac,"EXTENDED_TCL"),
 
699
    ?match({_,key,_,_,_,_}, Filter),
 
700
 
 
701
    ?match("EXTENDED_TCL", 'CosNotifyFilter_Filter':'_get_constraint_grammar'(Filter)),
 
702
 
 
703
    %% Test Callback management.
 
704
    ?match({'EXCEPTION',{'BAD_PARAM',_,_,_}}, 
 
705
                 'CosNotifyFilter_Filter':attach_callback(Filter, Ch)),
 
706
    ?match([], 'CosNotifyFilter_Filter':get_callbacks(Filter)),
 
707
    ?match({'EXCEPTION',{'CosNotifyFilter_CallbackNotFound',_}},
 
708
                 'CosNotifyFilter_Filter':detach_callback(Filter, 0)),
 
709
    ID='CosNotifyFilter_Filter':attach_callback(Filter, AC),
 
710
    ?match([ID], 'CosNotifyFilter_Filter':get_callbacks(Filter)),
 
711
    ?match(ok, 'CosNotifyFilter_Filter':detach_callback(Filter, ID)),
 
712
    ?match([], 'CosNotifyFilter_Filter':get_callbacks(Filter)),
 
713
 
 
714
    %% This callback is just attached so we can test that we can call notify_subscribe.
 
715
    _ID2='CosNotifyFilter_Filter':attach_callback(Filter, AC),
 
716
 
 
717
    %% Test before we add any constarints.
 
718
    ?match([], 'CosNotifyFilter_Filter':get_all_constraints(Filter)),
 
719
    ?match({'EXCEPTION', {'CosNotifyFilter_ConstraintNotFound', _, 1}},
 
720
                 'CosNotifyFilter_Filter':get_constraints(Filter, [1])),
 
721
    ?match(ok, 'CosNotifyFilter_Filter':remove_all_constraints(Filter)),
 
722
 
 
723
    %% Try adding an incorrect constraint_expr
 
724
    ?match({'EXCEPTION',{'CosNotifyFilter_InvalidConstraint',_,_}},
 
725
           'CosNotifyFilter_Filter':add_constraints(Filter, 
 
726
                        [#'CosNotifyFilter_ConstraintExp'{event_types = 
 
727
                                                          [#'CosNotification_EventType'{
 
728
                                                             domain_name = "name",
 
729
                                                             type_name = "type"}],
 
730
                                                          constraint_expr = "2==2 and 3<"}])),
 
731
    %% Try adding two correct constraint_expr
 
732
    ?line[{_,_,CID1},{_,_,CID2}]= 
 
733
        ?match([{'CosNotifyFilter_ConstraintInfo',_,_}, {'CosNotifyFilter_ConstraintInfo',_,_}],
 
734
           'CosNotifyFilter_Filter':add_constraints(Filter, 
 
735
                        [#'CosNotifyFilter_ConstraintExp'{event_types = 
 
736
                                                          [#'CosNotification_EventType'{
 
737
                                                             domain_name = "name",
 
738
                                                             type_name = "type"}],
 
739
                                                          constraint_expr = "2==2 and 3<4"},
 
740
                        #'CosNotifyFilter_ConstraintExp'{event_types = 
 
741
                                                          [#'CosNotification_EventType'{
 
742
                                                              domain_name = "name2",
 
743
                                                             type_name = "type2"}],
 
744
                                                          constraint_expr = "$.test._length == 3 and ($.test[0].score + $.test[1].score + $.test[2].score)/3 >=80"}])),
 
745
 
 
746
    ?match([{'CosNotifyFilter_ConstraintInfo',_,CID2}, {'CosNotifyFilter_ConstraintInfo',_,CID1}],
 
747
                 'CosNotifyFilter_Filter':get_all_constraints(Filter)),
 
748
    ?match([{'CosNotifyFilter_ConstraintInfo',_,CID1}], 
 
749
                 'CosNotifyFilter_Filter':get_constraints(Filter, [CID1])),
 
750
    ?match(ok, 'CosNotifyFilter_Filter':remove_all_constraints(Filter)),
 
751
    ?match([], 'CosNotifyFilter_Filter':get_all_constraints(Filter)),
 
752
 
 
753
    %% Try adding one correct and one incorrect constraint_expr
 
754
    ?match({'EXCEPTION',{'CosNotifyFilter_InvalidConstraint',_,_}},
 
755
           'CosNotifyFilter_Filter':add_constraints(Filter, 
 
756
                        [#'CosNotifyFilter_ConstraintExp'{event_types = 
 
757
                                                          [#'CosNotification_EventType'{
 
758
                                                             domain_name = "name",
 
759
                                                             type_name = "type"}],
 
760
                                                          constraint_expr = "2==2 and 3<"},
 
761
                        #'CosNotifyFilter_ConstraintExp'{event_types = 
 
762
                                                          [#'CosNotification_EventType'{
 
763
                                                             domain_name = "name2",
 
764
                                                             type_name = "type2"}],
 
765
                                                          constraint_expr = "$.test._length == 3 and ($.test[0].score + $.test[1].score + $.test[2].score)/3 >=80"}])),
 
766
 
 
767
    %% Following testcases test different domain_name and type_name, e.g., 
 
768
    %% wildcards etc.
 
769
    [{_,ConInfoData,CID3}] = 
 
770
        ?match([{'CosNotifyFilter_ConstraintInfo',_,_}],
 
771
           'CosNotifyFilter_Filter':add_constraints(Filter, 
 
772
                        [#'CosNotifyFilter_ConstraintExp'{event_types = 
 
773
                                        [#'CosNotification_EventType'{
 
774
                                                      domain_name = "domain",
 
775
                                                      type_name = ""},
 
776
                                         #'CosNotification_EventType'{
 
777
                                                      domain_name = "*",
 
778
                                                      type_name = "type"}],
 
779
                                    constraint_expr = "2==2 and 3<4"}])),
 
780
 
 
781
    %% Try removing a constraint
 
782
    ?match(ok, 'CosNotifyFilter_Filter':modify_constraints(Filter,[CID3],[])),
 
783
    ?match([], 'CosNotifyFilter_Filter':get_all_constraints(Filter)),
 
784
 
 
785
    %% Add e new constraint
 
786
    [{_,_,CID4}] = 
 
787
        ?match([{'CosNotifyFilter_ConstraintInfo',_,_}],
 
788
                 'CosNotifyFilter_Filter':add_constraints(Filter, 
 
789
                        [#'CosNotifyFilter_ConstraintExp'{event_types = 
 
790
                                        [#'CosNotification_EventType'{
 
791
                                                      domain_name = "domain1",
 
792
                                                      type_name = ""},
 
793
                                         #'CosNotification_EventType'{
 
794
                                                      domain_name = "domain2",
 
795
                                                      type_name = "*"}],
 
796
                                    constraint_expr = "2==2 and 3<4"}])),
 
797
 
 
798
    %% Try to update the constraint associated with CID4 to equal CID3.
 
799
    ?match(ok, 'CosNotifyFilter_Filter':modify_constraints(Filter,[],
 
800
                         [#'CosNotifyFilter_ConstraintInfo'{constraint_expression=
 
801
                           #'CosNotifyFilter_ConstraintExp'{event_types = 
 
802
                                        [#'CosNotification_EventType'{
 
803
                                                      domain_name = "domain",
 
804
                                                      type_name = ""},
 
805
                                         #'CosNotification_EventType'{
 
806
                                                      domain_name = "*",
 
807
                                                      type_name = "type"}],
 
808
                                    constraint_expr = "2==2 and 3<4"},
 
809
                          constraint_id=CID4}])),
 
810
 
 
811
    ?match([{_,ConInfoData,CID4}], 'CosNotifyFilter_Filter':get_all_constraints(Filter)),
 
812
 
 
813
    ?match({'EXCEPTION', {'CosNotifyFilter_ConstraintNotFound', _, CID3}},
 
814
                 'CosNotifyFilter_Filter':get_constraints(Filter, [CID3])),
 
815
    ?match(ok, 'CosNotifyFilter_Filter':remove_all_constraints(Filter)),
 
816
    ?match([], 'CosNotifyFilter_Filter':get_all_constraints(Filter)),
 
817
 
 
818
    ?match([{'CosNotifyFilter_ConstraintInfo',_,_}],
 
819
           'CosNotifyFilter_Filter':add_constraints(Filter, 
 
820
                        [#'CosNotifyFilter_ConstraintExp'{event_types = 
 
821
                                        [#'CosNotification_EventType'{
 
822
                                                      domain_name = "",
 
823
                                                      type_name = "type1"},
 
824
                                         #'CosNotification_EventType'{
 
825
                                                      domain_name = "*",
 
826
                                                      type_name = "type2"}],
 
827
                                    constraint_expr = "2==2 and 3<4"}])),
 
828
 
 
829
    ?match([{'CosNotifyFilter_ConstraintInfo',_,_}],
 
830
           'CosNotifyFilter_Filter':add_constraints(Filter, 
 
831
                        [#'CosNotifyFilter_ConstraintExp'{event_types = 
 
832
                                        [#'CosNotification_EventType'{
 
833
                                                      domain_name = "domain1",
 
834
                                                      type_name = "type1"},
 
835
                                         #'CosNotification_EventType'{
 
836
                                                      domain_name = "domain2",
 
837
                                                      type_name = "type2"}],
 
838
                                    constraint_expr = "2==2 and 3<4"}])),
 
839
 
 
840
    ?match([{'CosNotifyFilter_ConstraintInfo',_,_}],
 
841
           'CosNotifyFilter_Filter':add_constraints(Filter, 
 
842
                        [#'CosNotifyFilter_ConstraintExp'{event_types = 
 
843
                                        [#'CosNotification_EventType'{
 
844
                                                      domain_name = "dom*",
 
845
                                                      type_name = "type1"},
 
846
                                         #'CosNotification_EventType'{
 
847
                                                      domain_name = "domain2",
 
848
                                                      type_name = "typ*"}],
 
849
                                    constraint_expr = "2==2 and 3<4"}])),
 
850
 
 
851
    ?match([{'CosNotifyFilter_ConstraintInfo',_,_}],
 
852
           'CosNotifyFilter_Filter':add_constraints(Filter, 
 
853
                        [#'CosNotifyFilter_ConstraintExp'{event_types = 
 
854
                                        [#'CosNotification_EventType'{
 
855
                                                      domain_name = "dom*1",
 
856
                                                      type_name = "type1"},
 
857
                                         #'CosNotification_EventType'{
 
858
                                                      domain_name = "domain2",
 
859
                                                      type_name = "typ*2"}],
 
860
                                    constraint_expr = "2==2 and 3<4"}])),
 
861
 
 
862
    catch corba:dispose(FiFac),
 
863
    catch corba:dispose(Filter),
 
864
    catch corba:dispose(AC),
 
865
    catch corba:dispose(Ch),
 
866
    catch corba:dispose(Fac),
 
867
    ok.
 
868
 
 
869
%%-----------------------------------------------------------------
 
870
%%  Subscription handling API tests 
 
871
%%-----------------------------------------------------------------
 
872
subscription_api(doc) -> ["CosNotification subscription handling", ""];
 
873
subscription_api(suite) -> [];
 
874
subscription_api(_Config) ->
 
875
    %% Initialize the application.
 
876
    Fac = (catch cosNotificationApp:start_global_factory(?FAC_OPT)),
 
877
    ?match({_,key,_,_,_,_}, Fac),
 
878
    {Ch, _Id1} = (catch 'CosNotifyChannelAdmin_EventChannelFactory':create_channel(Fac, ?defaultQoS, ?defaultAdm)),
 
879
    ?match({_,key,_,_,_,_}, Ch),
 
880
 
 
881
    %% Create the Admin objects
 
882
    {AdminSupplier, _ASID}=?match({{_,key,_,_,_,_},_},
 
883
        'CosNotifyChannelAdmin_EventChannel':new_for_suppliers(Ch,'OR_OP')),
 
884
    {AdminConsumer, _ACID}=?match({{_,key,_,_,_,_},_}, 
 
885
        'CosNotifyChannelAdmin_EventChannel':new_for_consumers(Ch,'OR_OP')),
 
886
    
 
887
    %% Create Suppliers Proxies
 
888
    {StructuredProxyPullSupplier,_}=?match({{_,key,_,_,_,_},_},
 
889
        'CosNotifyChannelAdmin_ConsumerAdmin':obtain_notification_pull_supplier(AdminConsumer, 'STRUCTURED_EVENT')),
 
890
    {StructuredProxyPushSupplier,_}=?match({{_,key,_,_,_,_},_},
 
891
        'CosNotifyChannelAdmin_ConsumerAdmin':obtain_notification_push_supplier(AdminConsumer, 'STRUCTURED_EVENT')),
 
892
 
 
893
    %% Now we must create a Client for each proxy and connect them.
 
894
    PushStrC=?match({_,key,_,_,_,_}, 'notify_test_StrPushC':oe_create(['PUSH_STRUCTURED',StructuredProxyPushSupplier],
 
895
                                                                      [{local_typecheck, false}])),
 
896
    ?match(ok, 'CosNotifyChannelAdmin_StructuredProxyPushSupplier':connect_structured_push_consumer(StructuredProxyPushSupplier, PushStrC)),
 
897
    PullStrC=?match({_,key,_,_,_,_}, 'notify_test_StrPullC':oe_create(['PULL_STRUCTURED',StructuredProxyPullSupplier],
 
898
                                                                      [{local_typecheck, false}])),
 
899
    ?match(ok, 'CosNotifyChannelAdmin_StructuredProxyPullSupplier':connect_structured_pull_consumer(StructuredProxyPullSupplier, PullStrC)),
 
900
 
 
901
    %% Create Consumers Proxies
 
902
    {StructuredProxyPullConsumer,_}=?match({{_,key,_,_,_,_},_},
 
903
        'CosNotifyChannelAdmin_SupplierAdmin':obtain_notification_pull_consumer(AdminSupplier, 'STRUCTURED_EVENT')),
 
904
    {StructuredProxyPushConsumer,_}=?match({{_,key,_,_,_,_},_},
 
905
        'CosNotifyChannelAdmin_SupplierAdmin':obtain_notification_push_consumer(AdminSupplier, 'STRUCTURED_EVENT')),
 
906
 
 
907
    %% Now we must create a Client for each proxy and connect them.
 
908
    PushStrS=?match({_,key,_,_,_,_}, 'notify_test_StrPushS':oe_create(['PUSH_STRUCTURED',StructuredProxyPushConsumer],
 
909
                                                                      [{local_typecheck, false}])),
 
910
    ?match(ok, 'CosNotifyChannelAdmin_StructuredProxyPushConsumer':connect_structured_push_supplier(StructuredProxyPushConsumer, PushStrS)),
 
911
 
 
912
    PullStrS=?match({_,key,_,_,_,_}, 'notify_test_StrPullS':oe_create(['PULL_STRUCTURED',StructuredProxyPullConsumer],
 
913
                                                                      [{local_typecheck, false}])),
 
914
    ?match(ok, 'CosNotifyChannelAdmin_StructuredProxyPullConsumer':connect_structured_pull_supplier(StructuredProxyPullConsumer, PullStrS)),
 
915
 
 
916
    ES1=[#'CosNotification_EventType'{domain_name = "name1", type_name = "type1"},
 
917
         #'CosNotification_EventType'{domain_name = "name2", type_name = "type2"}],
 
918
    ES2=[#'CosNotification_EventType'{domain_name = "name3", type_name = "type3"},
 
919
         #'CosNotification_EventType'{domain_name = "name4", type_name = "type4"}],
 
920
 
 
921
    %% Initially it should have no associated types. Test that and set that
 
922
    %% all updates should be forwarded to client.
 
923
    ?match([], 'CosNotifyChannelAdmin_StructuredProxyPushConsumer':
 
924
                 obtain_subscription_types(StructuredProxyPushConsumer, 
 
925
                                           'ALL_NOW_UPDATES_ON')),
 
926
    ?match([], 'CosNotifyChannelAdmin_StructuredProxyPullConsumer':
 
927
                 obtain_subscription_types(StructuredProxyPullConsumer, 
 
928
                                           'ALL_NOW_UPDATES_ON')),
 
929
    
 
930
    %% Update the offered types.
 
931
    ?match(ok, 'CosNotifyChannelAdmin_StructuredProxyPushConsumer':
 
932
                 offer_change(StructuredProxyPushConsumer, ES1, [])),
 
933
    ?match(ok, 'CosNotifyChannelAdmin_StructuredProxyPullConsumer':
 
934
                 offer_change(StructuredProxyPullConsumer, ES1, [])),
 
935
 
 
936
    %% To be sure, wait a couple of seconds.
 
937
    timer:sleep(5000),
 
938
    ?match([{'CosNotification_EventType',_,_},
 
939
            {'CosNotification_EventType',_,_}],
 
940
           'notify_test_StrPushC':doAction(PushStrS, return_data)),
 
941
    ?match([{'CosNotification_EventType',_,_},
 
942
            {'CosNotification_EventType',_,_}],
 
943
           'notify_test_StrPullC':doAction(PullStrS, return_data)),
 
944
 
 
945
    %% Update the offered types. Remove ES1 and add ES2.
 
946
    ?match(ok, 'CosNotifyChannelAdmin_StructuredProxyPushConsumer':
 
947
                 offer_change(StructuredProxyPushConsumer, ES2, ES1)),
 
948
    ?match(ok, 'CosNotifyChannelAdmin_StructuredProxyPullConsumer':
 
949
                 offer_change(StructuredProxyPullConsumer, ES2, ES1)),
 
950
 
 
951
    %% To be sure, wait a couple of seconds.
 
952
    timer:sleep(5000),
 
953
    ?match([{'CosNotification_EventType',_,_},
 
954
            {'CosNotification_EventType',_,_}],
 
955
           'notify_test_StrPushC':doAction(PushStrS, return_data)),
 
956
    ?match([{'CosNotification_EventType',_,_},
 
957
            {'CosNotification_EventType',_,_}],
 
958
           'notify_test_StrPullC':doAction(PullStrS, return_data)),
 
959
 
 
960
    %% Now, the objects should only contain 'ES2'. Test it.
 
961
    ?match([{'CosNotification_EventType',_,_},
 
962
            {'CosNotification_EventType',_,_}],
 
963
           'CosNotifyChannelAdmin_StructuredProxyPushConsumer':
 
964
           obtain_subscription_types(StructuredProxyPushConsumer, 
 
965
                                     'ALL_NOW_UPDATES_ON')),
 
966
    ?match([{'CosNotification_EventType',_,_},
 
967
            {'CosNotification_EventType',_,_}],
 
968
           'CosNotifyChannelAdmin_StructuredProxyPullConsumer':
 
969
           obtain_subscription_types(StructuredProxyPullConsumer, 
 
970
                                     'ALL_NOW_UPDATES_ON')),
 
971
 
 
972
    %% Now we will use wildcards, empty strings and test if they really
 
973
    %% are ignored if so requested.
 
974
    ES3=[#'CosNotification_EventType'{domain_name = "name1", type_name = "*"},
 
975
        #'CosNotification_EventType'{domain_name = "*", type_name = "type2"}],
 
976
    ES4=[#'CosNotification_EventType'{domain_name = "name1", type_name = "*"},
 
977
        #'CosNotification_EventType'{domain_name = "name2", type_name = ""}],
 
978
    ES5=[#'CosNotification_EventType'{domain_name = "na*", type_name = "type1"}],
 
979
    ES6=[#'CosNotification_EventType'{domain_name = "n*1", type_name = "type1"}],
 
980
    ES7=[#'CosNotification_EventType'{domain_name = "*1", type_name = "type1"}],
 
981
    ES8=[#'CosNotification_EventType'{domain_name = "n*m*1", type_name = "type1"}],
 
982
    ES9=[#'CosNotification_EventType'{domain_name = "n**1", type_name = "type1"}],
 
983
    ES10=[#'CosNotification_EventType'{domain_name = "nam*1", type_name = "type1"}],
 
984
 
 
985
    Event1 = ?not_CreateSE("name1","type1",
 
986
                           "event_name",
 
987
                           [#'CosNotification_Property'{name="property_name", 
 
988
                                                        value=any:create(orber_tc:short(), 1)}],
 
989
                           [], any:create(orber_tc:null(), null)),
 
990
    Event2 = ?not_CreateSE("name2","type1",
 
991
                           "event_name",
 
992
                           [#'CosNotification_Property'{name="property_name", 
 
993
                                                        value=any:create(orber_tc:short(), 1)}],
 
994
                           [], any:create(orber_tc:null(), null)),
 
995
    Event3 = ?not_CreateSE("mame1","type1",
 
996
                           "event_name",
 
997
                           [#'CosNotification_Property'{name="property_name", 
 
998
                                                        value=any:create(orber_tc:short(), 1)}],
 
999
                           [], any:create(orber_tc:null(), null)),
 
1000
    Event4 = ?not_CreateSE("naame1","type1",
 
1001
                           "event_name",
 
1002
                           [#'CosNotification_Property'{name="property_name", 
 
1003
                                                        value=any:create(orber_tc:short(), 1)}],
 
1004
                           [], any:create(orber_tc:null(), null)),
 
1005
    Event5 = ?not_CreateSE("nname1","type1",
 
1006
                           "event_name",
 
1007
                           [#'CosNotification_Property'{name="property_name", 
 
1008
                                                        value=any:create(orber_tc:short(), 1)}],
 
1009
                           [], any:create(orber_tc:null(), null)),
 
1010
    Event6 = ?not_CreateSE("name12","type1",
 
1011
                           "event_name",
 
1012
                           [#'CosNotification_Property'{name="property_name", 
 
1013
                                                        value=any:create(orber_tc:short(), 1)}],
 
1014
                           [], any:create(orber_tc:null(), null)),
 
1015
 
 
1016
    ?match(ok, 'CosNotifyChannelAdmin_StructuredProxyPullSupplier':
 
1017
                 subscription_change(StructuredProxyPullSupplier, ES3, [])),
 
1018
 
 
1019
    ?match(ok,'CosNotifyChannelAdmin_StructuredProxyPushConsumer':push_structured_event(StructuredProxyPushConsumer, Event1)),
 
1020
 
 
1021
    ?match(Event1, 'notify_test_StrPullC':doAction(PullStrC, pull_str)),
 
1022
 
 
1023
    ?match(ok, 'CosNotifyChannelAdmin_StructuredProxyPullSupplier':
 
1024
                 subscription_change(StructuredProxyPullSupplier, ES4, ES3)),
 
1025
    ?match(ok,'CosNotifyChannelAdmin_StructuredProxyPushConsumer':push_structured_event(StructuredProxyPushConsumer, Event1)),
 
1026
    ?match(Event1, 'notify_test_StrPullC':doAction(PullStrC, pull_str)),
 
1027
 
 
1028
    ?match(ok, 'CosNotifyChannelAdmin_StructuredProxyPullSupplier':
 
1029
                 subscription_change(StructuredProxyPullSupplier, ES5, ES4)),
 
1030
    ?match(ok,'CosNotifyChannelAdmin_StructuredProxyPushConsumer':push_structured_event(StructuredProxyPushConsumer, Event1)),
 
1031
    ?match(Event1, 'notify_test_StrPullC':doAction(PullStrC, pull_str)),
 
1032
 
 
1033
    ?match(ok, 'CosNotifyChannelAdmin_StructuredProxyPullSupplier':
 
1034
                 subscription_change(StructuredProxyPullSupplier, ES6, ES5)),
 
1035
    ?match(ok,'CosNotifyChannelAdmin_StructuredProxyPushConsumer':push_structured_event(StructuredProxyPushConsumer, Event1)),
 
1036
    ?match(Event1, 'notify_test_StrPullC':doAction(PullStrC, pull_str)),
 
1037
 
 
1038
    ?match(ok, 'CosNotifyChannelAdmin_StructuredProxyPullSupplier':
 
1039
                 subscription_change(StructuredProxyPullSupplier, ES7, ES6)),
 
1040
    ?match(ok,'CosNotifyChannelAdmin_StructuredProxyPushConsumer':push_structured_event(StructuredProxyPushConsumer, Event1)),
 
1041
    ?match(Event1, 'notify_test_StrPullC':doAction(PullStrC, pull_str)),
 
1042
 
 
1043
    ?match(ok, 'CosNotifyChannelAdmin_StructuredProxyPullSupplier':
 
1044
                 subscription_change(StructuredProxyPullSupplier, ES8, ES7)),
 
1045
    ?match(ok,'CosNotifyChannelAdmin_StructuredProxyPushConsumer':push_structured_event(StructuredProxyPushConsumer, Event1)),
 
1046
    ?match(Event1, 'notify_test_StrPullC':doAction(PullStrC, pull_str)),
 
1047
 
 
1048
    ?match(ok, 'CosNotifyChannelAdmin_StructuredProxyPullSupplier':
 
1049
                 subscription_change(StructuredProxyPullSupplier, ES9, ES8)),
 
1050
    ?match(ok,'CosNotifyChannelAdmin_StructuredProxyPushConsumer':push_structured_event(StructuredProxyPushConsumer, Event1)),
 
1051
    ?match(Event1, 'notify_test_StrPullC':doAction(PullStrC, pull_str)),
 
1052
 
 
1053
    ?match(ok,'CosNotifyChannelAdmin_StructuredProxyPushConsumer':push_structured_event(StructuredProxyPushConsumer, Event2)),
 
1054
    ?match(ok,'CosNotifyChannelAdmin_StructuredProxyPushConsumer':push_structured_event(StructuredProxyPushConsumer, Event3)),
 
1055
 
 
1056
    timer:sleep(5000),
 
1057
    ?match({_NilStrEvent,false}, 'notify_test_StrPullC':doAction(PullStrC, try_pull_str)),
 
1058
 
 
1059
    ?match(ok, 'CosNotifyChannelAdmin_StructuredProxyPullSupplier':
 
1060
                 subscription_change(StructuredProxyPullSupplier, ES10, ES9)),
 
1061
    ?match(ok,'CosNotifyChannelAdmin_StructuredProxyPushConsumer':push_structured_event(StructuredProxyPushConsumer, Event1)),
 
1062
    ?match(Event1, 'notify_test_StrPullC':doAction(PullStrC, pull_str)),
 
1063
 
 
1064
    ?match(ok,'CosNotifyChannelAdmin_StructuredProxyPushConsumer':push_structured_event(StructuredProxyPushConsumer, Event4)),
 
1065
    ?match(ok,'CosNotifyChannelAdmin_StructuredProxyPushConsumer':push_structured_event(StructuredProxyPushConsumer, Event5)),
 
1066
    ?match(ok,'CosNotifyChannelAdmin_StructuredProxyPushConsumer':push_structured_event(StructuredProxyPushConsumer, Event6)),
 
1067
 
 
1068
    timer:sleep(5000),
 
1069
    ?match({_NilStrEvent,false}, 'notify_test_StrPullC':doAction(PullStrC, try_pull_str)),
 
1070
 
 
1071
 
 
1072
    catch corba:dispose(StructuredProxyPushConsumer),
 
1073
    catch corba:dispose(StructuredProxyPullConsumer),
 
1074
    catch corba:dispose(StructuredProxyPushSupplier),
 
1075
    catch corba:dispose(StructuredProxyPullSupplier),
 
1076
    catch corba:dispose(AdminConsumer),
 
1077
    catch corba:dispose(AdminSupplier),
 
1078
    catch corba:dispose(Ch),
 
1079
    catch cosNotificationApp:stop_factory(Fac),
 
1080
 
 
1081
    timer:sleep(5000),
 
1082
    ?match(true, corba_object:non_existent(PullStrS)),
 
1083
    ?match(true, corba_object:non_existent(PushStrS)),
 
1084
    ?match(true, corba_object:non_existent(PullStrC)),
 
1085
    ?match(true, corba_object:non_existent(PushStrC)),
 
1086
 
 
1087
    ok.
 
1088
 
 
1089
%%-----------------------------------------------------------------
 
1090
%%  Filter admin API tests 
 
1091
%%-----------------------------------------------------------------
 
1092
filter_adm_api(doc) -> ["CosNotification filter admin tests", ""];
 
1093
filter_adm_api(suite) -> [];
 
1094
filter_adm_api(_Config) ->
 
1095
    Fac = (catch cosNotificationApp:start_global_factory(?FAC_OPT)),
 
1096
    ?match({_,key,_,_,_,_}, Fac),
 
1097
    {Ch, _Id1} = (catch 'CosNotifyChannelAdmin_EventChannelFactory':create_channel(Fac, ?defaultQoS, ?defaultAdm)),
 
1098
    ?match({_,key,_,_,_,_}, Ch),
 
1099
 
 
1100
    FiFac = 'CosNotifyFilter_FilterFactory':oe_create(),
 
1101
    ?match({_,key,_,_,_,_}, FiFac),
 
1102
    
 
1103
    Filter = 'CosNotifyFilter_FilterFactory':create_filter(FiFac,"EXTENDED_TCL"),
 
1104
    ?match({_,key,_,_,_,_}, Filter),
 
1105
 
 
1106
    AC=?match({_,key,_,_,_,_},
 
1107
                    'CosNotifyChannelAdmin_EventChannel':for_consumers(Ch)),
 
1108
    filter_tests('CosNotifyChannelAdmin_ConsumerAdmin', AC, Filter, Ch),
 
1109
 
 
1110
    AS=?match({_,key,_,_,_,_},
 
1111
                    'CosNotifyChannelAdmin_EventChannel':for_suppliers(Ch)),
 
1112
    filter_tests('CosNotifyChannelAdmin_SupplierAdmin', AS, Filter, Ch),
 
1113
 
 
1114
    PushS=?match({_,key,_,_,_,_},
 
1115
                       'CosNotifyChannelAdmin_ConsumerAdmin':obtain_push_supplier(AC)),
 
1116
    filter_tests('CosNotifyChannelAdmin_ProxyPushSupplier', PushS, Filter, Ch),
 
1117
 
 
1118
    PullS=?match({_,key,_,_,_,_},
 
1119
                       'CosNotifyChannelAdmin_ConsumerAdmin':obtain_pull_supplier(AC)),
 
1120
    filter_tests('CosNotifyChannelAdmin_ProxyPullSupplier', PullS, Filter, Ch),
 
1121
 
 
1122
    PushC=?match({_,key,_,_,_,_},
 
1123
                       'CosNotifyChannelAdmin_SupplierAdmin':obtain_push_consumer(AS)),
 
1124
    filter_tests('CosNotifyChannelAdmin_ProxyPushConsumer', PushC, Filter, Ch),
 
1125
 
 
1126
    PullC=?match({_,key,_,_,_,_},
 
1127
                       'CosNotifyChannelAdmin_SupplierAdmin':obtain_pull_consumer(AS)),
 
1128
    filter_tests('CosNotifyChannelAdmin_ProxyPullConsumer', PullC, Filter, Ch),
 
1129
 
 
1130
    catch corba:dispose(FiFac),
 
1131
    catch corba:dispose(Filter),
 
1132
    catch corba:dispose(PushS),
 
1133
    catch corba:dispose(PullS),
 
1134
    catch corba:dispose(PushC),
 
1135
    catch corba:dispose(PullC),
 
1136
    catch corba:dispose(AC),
 
1137
    catch corba:dispose(AS),
 
1138
    catch corba:dispose(Ch),
 
1139
    catch cosNotificationApp:stop_factory(Fac),
 
1140
    ok.
 
1141
 
 
1142
filter_tests(Mod, Obj, Filter, Ch) ->
 
1143
    io:format("############ TESTING MODULE ~p FILTER ############~n", [Mod]),
 
1144
    %% No filter added.
 
1145
    ?match([], Mod:get_all_filters(Obj)),
 
1146
    ?match(ok, Mod:remove_all_filters(Obj)),
 
1147
    ?match({'EXCEPTION',{'CosNotifyFilter_FilterNotFound',_}},
 
1148
                 Mod:get_filter(Obj, 0)),
 
1149
    %% Try add a Filter which is not a filter.
 
1150
    ?match({'EXCEPTION',{'BAD_PARAM',_,_,_}}, Mod:add_filter(Obj, Ch)),
 
1151
    %% Try to remove a single filter.
 
1152
    ?match({'EXCEPTION',{'CosNotifyFilter_FilterNotFound',_}},
 
1153
                 Mod:remove_filter(Obj, 0)),
 
1154
    ID = Mod:add_filter(Obj, Filter),
 
1155
    ?match([ID], Mod:get_all_filters(Obj)),
 
1156
    ?match(Filter, Mod:get_filter(Obj, ID)),
 
1157
    ?match(ok, Mod:remove_filter(Obj, ID)),
 
1158
    ?match([], Mod:get_all_filters(Obj)),
 
1159
    ID2 = Mod:add_filter(Obj, Filter),
 
1160
    ?match([ID2], Mod:get_all_filters(Obj)),
 
1161
    ?match(ok, Mod:remove_all_filters(Obj)),
 
1162
    ?match([], Mod:get_all_filters(Obj)),
 
1163
    ok.
 
1164
 
 
1165
%%-----------------------------------------------------------------
 
1166
%%  Creating different event pushing and pulling API tests 
 
1167
%%-----------------------------------------------------------------
 
1168
events_api(doc) -> ["CosNotification event pushing and pulling tests", ""];
 
1169
events_api(suite) -> [];
 
1170
events_api(_Config) ->
 
1171
    %% Initialize the application.
 
1172
    Fac = (catch cosNotificationApp:start_global_factory(?FAC_OPT)),
 
1173
    ?match({_,key,_,_,_,_}, Fac),
 
1174
    {Ch, Id1} = (catch 'CosNotifyChannelAdmin_EventChannelFactory':create_channel(Fac, ?defaultQoS, ?defaultAdm)),
 
1175
    ?match({_,key,_,_,_,_}, Ch),
 
1176
    events_api_helper(Fac, Ch, Id1).
 
1177
 
 
1178
events2_api(doc) -> ["CosNotification event pushing and pulling tests II", ""];
 
1179
events2_api(suite) -> [];
 
1180
events2_api(_Config) ->
 
1181
    %% Initialize the application.
 
1182
    Fac = (catch cosNotificationApp:start_global_factory(?FAC_OPT)),
 
1183
    ?match({_,key,_,_,_,_}, Fac),
 
1184
    {Ch, Id1} = (catch 'CosNotifyChannelAdmin_EventChannelFactory':create_channel(Fac, ?defaultQoS2, ?defaultAdm)),
 
1185
    ?match({_,key,_,_,_,_}, Ch),
 
1186
    events_api_helper(Fac, Ch, Id1).
 
1187
 
 
1188
events_api_helper(Fac, Ch, _Id1) ->
 
1189
    %% Now we will set up a test environment, with the following structure:
 
1190
    %%
 
1191
    %%                              Channel
 
1192
    %%                              /      \
 
1193
    %%                    Supplier Adm    Consumer Adm
 
1194
    %%                            /          \
 
1195
    %%                  1 proxy of each possible type
 
1196
    %%                  To each proxy we will connect a test client
 
1197
    %%                  The events will flow in ===>> direction.
 
1198
    %%
 
1199
    %% For the supplier Admins this include:
 
1200
    %% - ProxyPushConsumer
 
1201
    %% - SequenceProxyPushConsumer 
 
1202
    %% - StructuredProxyPushConsumer
 
1203
    %% - ProxyPullConsumer
 
1204
    %% - SequenceProxyPullConsumer 
 
1205
    %% - StructuredProxyPullConsumer
 
1206
    %%
 
1207
    %% For the consumer Admins this include:
 
1208
    %% - ProxyPushSupplier
 
1209
    %% - SequenceProxyPushSupplier
 
1210
    %% - StructuredProxyPushSupplier
 
1211
    %% - ProxyPullSupplier
 
1212
    %% - SequenceProxyPullSupplier
 
1213
    %% - StructuredProxyPullSupplier
 
1214
    %% 
 
1215
    %%
 
1216
    %% We will not use any Filters to begin with, just want to make sure we can
 
1217
    %% deliver events from all start- to end-points.
 
1218
    
 
1219
    %% Create the Admin objects
 
1220
    {AdminSupplier, _ASID}=?match({{_,key,_,_,_,_},_},
 
1221
        'CosNotifyChannelAdmin_EventChannel':new_for_suppliers(Ch,'AND_OP')),
 
1222
    {AdminConsumer, _ACID}=?match({{_,key,_,_,_,_},_}, 
 
1223
        'CosNotifyChannelAdmin_EventChannel':new_for_consumers(Ch,'AND_OP')),
 
1224
    
 
1225
    %% Create Suppliers Proxies
 
1226
    {ProxyPullSupplier,_ID1}=?match({{_,key,_,_,_,_},_},
 
1227
        'CosNotifyChannelAdmin_ConsumerAdmin':obtain_notification_pull_supplier(AdminConsumer, 'ANY_EVENT')),
 
1228
    {StructuredProxyPullSupplier,_ID2}=?match({{_,key,_,_,_,_},_},
 
1229
        'CosNotifyChannelAdmin_ConsumerAdmin':obtain_notification_pull_supplier(AdminConsumer, 'STRUCTURED_EVENT')),
 
1230
    {SequenceProxyPullSupplier,_ID3}=?match({{_,key,_,_,_,_},_},
 
1231
        'CosNotifyChannelAdmin_ConsumerAdmin':obtain_notification_pull_supplier(AdminConsumer, 'SEQUENCE_EVENT')),
 
1232
    
 
1233
    {ProxyPushSupplier,_I4D}=?match({{_,key,_,_,_,_},_},
 
1234
        'CosNotifyChannelAdmin_ConsumerAdmin':obtain_notification_push_supplier(AdminConsumer, 'ANY_EVENT')),
 
1235
    {StructuredProxyPushSupplier,_ID5}=?match({{_,key,_,_,_,_},_},
 
1236
        'CosNotifyChannelAdmin_ConsumerAdmin':obtain_notification_push_supplier(AdminConsumer, 'STRUCTURED_EVENT')),
 
1237
    {SequenceProxyPushSupplier,_ID6}=?match({{_,key,_,_,_,_},_},
 
1238
        'CosNotifyChannelAdmin_ConsumerAdmin':obtain_notification_push_supplier(AdminConsumer, 'SEQUENCE_EVENT')),
 
1239
 
 
1240
    %% Now we must create a Client for each proxy and connect them.
 
1241
    PushAnyC=?match({_,key,_,_,_,_}, 'notify_test_AnyPushC':oe_create(['PUSH_ANY', ProxyPushSupplier],
 
1242
                                                                      [{local_typecheck, false}])),
 
1243
    ?match(ok, 'CosNotifyChannelAdmin_ProxyPushSupplier':connect_any_push_consumer(ProxyPushSupplier, PushAnyC)),
 
1244
 
 
1245
    PushStrC=?match({_,key,_,_,_,_}, 'notify_test_StrPushC':oe_create(['PUSH_STRUCTURED',StructuredProxyPushSupplier],
 
1246
                                                                      [{local_typecheck, false}])),
 
1247
    ?match(ok, 'CosNotifyChannelAdmin_StructuredProxyPushSupplier':connect_structured_push_consumer(StructuredProxyPushSupplier, PushStrC)),
 
1248
 
 
1249
    PushSeqC=?match({_,key,_,_,_,_}, 'notify_test_SeqPushC':oe_create(['PUSH_SEQUENCE',SequenceProxyPushSupplier],
 
1250
                                                                      [{local_typecheck, false}])),
 
1251
    ?match(ok, 'CosNotifyChannelAdmin_SequenceProxyPushSupplier':connect_sequence_push_consumer(SequenceProxyPushSupplier, PushSeqC)),
 
1252
 
 
1253
    PullAnyC=?match({_,key,_,_,_,_}, 'notify_test_AnyPullC':oe_create(['PULL_ANY', ProxyPullSupplier],
 
1254
                                                                      [{local_typecheck, false}])),
 
1255
    ?match(ok, 'CosNotifyChannelAdmin_ProxyPullSupplier':connect_any_pull_consumer(ProxyPullSupplier, PullAnyC)),
 
1256
 
 
1257
    PullStrC=?match({_,key,_,_,_,_}, 'notify_test_StrPullC':oe_create(['PULL_STRUCTURED',StructuredProxyPullSupplier],
 
1258
                                                                      [{local_typecheck, false}])),
 
1259
    ?match(ok, 'CosNotifyChannelAdmin_StructuredProxyPullSupplier':connect_structured_pull_consumer(StructuredProxyPullSupplier, PullStrC)),
 
1260
 
 
1261
    PullSeqC=?match({_,key,_,_,_,_}, 'notify_test_SeqPullC':oe_create(['PULL_SEQUENCE',SequenceProxyPullSupplier],
 
1262
                                                                      [{local_typecheck, false}])),
 
1263
    ?match(ok, 'CosNotifyChannelAdmin_SequenceProxyPullSupplier':connect_sequence_pull_consumer(SequenceProxyPullSupplier, PullSeqC)),
 
1264
 
 
1265
    
 
1266
    %% Create Consumers Proxies
 
1267
    {ProxyPullConsumer,_ID7}=?match({{_,key,_,_,_,_},_},
 
1268
        'CosNotifyChannelAdmin_SupplierAdmin':obtain_notification_pull_consumer(AdminSupplier, 'ANY_EVENT')),
 
1269
    {StructuredProxyPullConsumer,_ID8}=?match({{_,key,_,_,_,_},_},
 
1270
        'CosNotifyChannelAdmin_SupplierAdmin':obtain_notification_pull_consumer(AdminSupplier, 'STRUCTURED_EVENT')),
 
1271
    {SequenceProxyPullConsumer,_ID9}=?match({{_,key,_,_,_,_},_},
 
1272
        'CosNotifyChannelAdmin_SupplierAdmin':obtain_notification_pull_consumer(AdminSupplier, 'SEQUENCE_EVENT')),
 
1273
 
 
1274
    {ProxyPushConsumer,_ID10}=?match({{_,key,_,_,_,_},_},
 
1275
        'CosNotifyChannelAdmin_SupplierAdmin':obtain_notification_push_consumer(AdminSupplier, 'ANY_EVENT')),
 
1276
    {StructuredProxyPushConsumer,_ID11}=?match({{_,key,_,_,_,_},_},
 
1277
        'CosNotifyChannelAdmin_SupplierAdmin':obtain_notification_push_consumer(AdminSupplier, 'STRUCTURED_EVENT')),
 
1278
    {SequenceProxyPushConsumer,_ID12}=?match({{_,key,_,_,_,_},_},
 
1279
        'CosNotifyChannelAdmin_SupplierAdmin':obtain_notification_push_consumer(AdminSupplier, 'SEQUENCE_EVENT')),
 
1280
 
 
1281
    %% Now we must create a Client for each proxy and connect them.
 
1282
    PushAnyS=?match({_,key,_,_,_,_}, 'notify_test_AnyPushS':oe_create(['PUSH_ANY', ProxyPushConsumer],
 
1283
                                                                      [{local_typecheck, false}])),
 
1284
    ?match(ok, 'CosNotifyChannelAdmin_ProxyPushConsumer':connect_any_push_supplier(ProxyPushConsumer, PushAnyS)),
 
1285
 
 
1286
    PushStrS=?match({_,key,_,_,_,_}, 'notify_test_StrPushS':oe_create(['PUSH_STRUCTURED',StructuredProxyPushConsumer],
 
1287
                                                                      [{local_typecheck, false}])),
 
1288
    ?match(ok, 'CosNotifyChannelAdmin_StructuredProxyPushConsumer':connect_structured_push_supplier(StructuredProxyPushConsumer, PushStrS)),
 
1289
 
 
1290
    PushSeqS=?match({_,key,_,_,_,_}, 'notify_test_SeqPushS':oe_create(['PUSH_SEQUENCE',SequenceProxyPushConsumer],
 
1291
                                                                      [{local_typecheck, false}])),
 
1292
    ?match(ok, 'CosNotifyChannelAdmin_SequenceProxyPushConsumer':connect_sequence_push_supplier(SequenceProxyPushConsumer, PushSeqS)),
 
1293
 
 
1294
    PullAnyS=?match({_,key,_,_,_,_}, 'notify_test_AnyPullS':oe_create(['PULL_ANY', ProxyPullConsumer],
 
1295
                                                                      [{local_typecheck, false}])),
 
1296
    ?match(ok, 'CosNotifyChannelAdmin_ProxyPullConsumer':connect_any_pull_supplier(ProxyPullConsumer, PullAnyS)),
 
1297
 
 
1298
    PullStrS=?match({_,key,_,_,_,_}, 'notify_test_StrPullS':oe_create(['PULL_STRUCTURED',StructuredProxyPullConsumer],
 
1299
                                                                      [{local_typecheck, false}])),
 
1300
    ?match(ok, 'CosNotifyChannelAdmin_StructuredProxyPullConsumer':connect_structured_pull_supplier(StructuredProxyPullConsumer, PullStrS)),
 
1301
 
 
1302
    PullSeqS=?match({_,key,_,_,_,_}, 'notify_test_SeqPullS':oe_create(['PULL_SEQUENCE',SequenceProxyPullConsumer],
 
1303
                                                                      [{local_typecheck, false}])),
 
1304
    ?match(ok, 'CosNotifyChannelAdmin_SequenceProxyPullConsumer':connect_sequence_pull_supplier(SequenceProxyPullConsumer, PullSeqS)),
 
1305
 
 
1306
    
 
1307
    %% Create a couple of Events to test with.
 
1308
    Event = ?not_CreateSE("DomainName","CommunicationsAlarm",
 
1309
                          "lost_packet",
 
1310
                          [#'CosNotification_Property'{name="priority", 
 
1311
                                                       value=any:create(orber_tc:short(), 1)}],
 
1312
                          [], any:create(orber_tc:null(), null)),
 
1313
 
 
1314
    Event2 = ?not_CreateSE("DomainName","TemperatureAlarm",
 
1315
                           "over_heated",
 
1316
                           [#'CosNotification_Property'{name="priority", 
 
1317
                                                        value=any:create(orber_tc:short(), 10)}],
 
1318
                           [], any:create(orber_tc:null(), null)),
 
1319
 
 
1320
 
 
1321
    AnyEvent = any:create(orber_tc:long(), 100),
 
1322
 
 
1323
    StrEvent = ?not_CreateSE("","%ANY","",[],[],AnyEvent),
 
1324
    NilAnyEvent = any:create(orber_tc:null(), null),
 
1325
    NilStrEvent = ?not_CreateSE("","","",[],[],NilAnyEvent),
 
1326
 
 
1327
    ConvertedStr = any:create('CosNotification_StructuredEvent':tc(), Event),
 
1328
 
 
1329
    io:format("###################### PUSH STRUCTURED ########################"),
 
1330
 
 
1331
    %% Test with pushing a structured event.
 
1332
    ?match(ok,'CosNotifyChannelAdmin_StructuredProxyPushConsumer':push_structured_event(StructuredProxyPushConsumer, Event)),
 
1333
 
 
1334
    %% Wait for a while so we are sure that all events have been delivered as far
 
1335
    %% as the Notification service can automatically.
 
1336
    timer:sleep(5000),
 
1337
 
 
1338
    %% Check if the Clients have received and stored the events.
 
1339
    ?match([{any,_,Event}], 'notify_test_AnyPushC':doAction(PushAnyC, return_data)),
 
1340
    ?match([Event], 'notify_test_StrPushC':doAction(PushStrC, return_data)),
 
1341
    ?match([Event], 'notify_test_SeqPushC':doAction(PushSeqC, return_data)),
 
1342
 
 
1343
    %% Instruct the Clients to pull the events and check if they match.
 
1344
    ?match({any,_,Event}, 'notify_test_AnyPullC':doAction(PullAnyC, pull_any)),
 
1345
    ?match(Event, 'notify_test_StrPullC':doAction(PullStrC, pull_str)),
 
1346
    ?match([Event], 'notify_test_SeqPullC':doAction(PullSeqC, {pull_seq,1})),
 
1347
 
 
1348
    io:format("###################### PUSH SEQUENCE ########################"),
 
1349
 
 
1350
    %% Create an Event Sequence and push it.
 
1351
    EventSeq = [Event, Event2],
 
1352
    
 
1353
    %% Test with pushing a event sequence.
 
1354
    ?match(ok,'CosNotifyChannelAdmin_SequenceProxyPushConsumer':push_structured_events(SequenceProxyPushConsumer, EventSeq)),
 
1355
 
 
1356
    %% Wait for a while so we are sure that all events have been delivered as far
 
1357
    %% as the Notification service can automatically.
 
1358
    timer:sleep(5000),
 
1359
                
 
1360
    %% Instruct the Clients to pull the events and check if they match.
 
1361
    ?match({any,_,Event}, 'notify_test_AnyPullC':doAction(PullAnyC, pull_any)),
 
1362
    ?match(Event, 'notify_test_StrPullC':doAction(PullStrC, pull_str)),
 
1363
    ?match([Event,Event2], 'notify_test_SeqPullC':doAction(PullSeqC, {pull_seq,2})),
 
1364
    ?match({any,_,Event2}, 'notify_test_AnyPullC':doAction(PullAnyC, pull_any)),
 
1365
    ?match(Event2, 'notify_test_StrPullC':doAction(PullStrC, pull_str)),
 
1366
 
 
1367
    %% Check if the Push Clients have received and stored the events.
 
1368
    ?match([{any,_,Event}, {any,_,Event2}], 'notify_test_AnyPushC':doAction(PushAnyC, return_data)),
 
1369
    ?match([Event, Event2], 'notify_test_StrPushC':doAction(PushStrC, return_data)),
 
1370
    ?match([Event, Event2], 'notify_test_SeqPushC':doAction(PushSeqC, return_data)),
 
1371
 
 
1372
    io:format("######################  PUSH ANY ########################"),
 
1373
 
 
1374
    %% Test with pushing an any event.
 
1375
    ?match(ok,'CosEventChannelAdmin_ProxyPushConsumer':push(ProxyPushConsumer, AnyEvent)),
 
1376
 
 
1377
    %% Wait for a while so we are sure that all events have been delivered as far
 
1378
    %% as the Notification service can automatically.
 
1379
    timer:sleep(5000),
 
1380
 
 
1381
    %% Check if the Clients have received and stored the events.
 
1382
    ?match([AnyEvent], 'notify_test_AnyPushC':doAction(PushAnyC, return_data)),
 
1383
    ?match([StrEvent], 'notify_test_StrPushC':doAction(PushStrC, return_data)),
 
1384
    ?match([StrEvent], 'notify_test_SeqPushC':doAction(PushSeqC, return_data)),
 
1385
 
 
1386
    %% Instruct the Clients to pull the events and check if they match.
 
1387
    ?match(AnyEvent, 'notify_test_AnyPullC':doAction(PullAnyC, pull_any)),
 
1388
    ?match(StrEvent, 'notify_test_StrPullC':doAction(PullStrC, pull_str)),
 
1389
    ?match([StrEvent], 'notify_test_SeqPullC':doAction(PullSeqC, {pull_seq,10})),
 
1390
 
 
1391
 
 
1392
 
 
1393
    io:format("###################### PUSH CONVERTED ANY #############"),
 
1394
 
 
1395
    %% Test with pushing a structured event.
 
1396
    ?match(ok,'CosNotifyChannelAdmin_StructuredProxyPushConsumer':push_structured_event(StructuredProxyPushConsumer, StrEvent)),
 
1397
 
 
1398
    %% Wait for a while so we are sure that all events have been delivered as far
 
1399
    %% as the Notification service can automatically.
 
1400
    timer:sleep(5000),
 
1401
 
 
1402
    %% Check if the Clients have received and stored the events.
 
1403
    ?match([AnyEvent], 'notify_test_AnyPushC':doAction(PushAnyC, return_data)),
 
1404
    ?match([StrEvent], 'notify_test_StrPushC':doAction(PushStrC, return_data)),
 
1405
    ?match([StrEvent], 'notify_test_SeqPushC':doAction(PushSeqC, return_data)),
 
1406
 
 
1407
    %% Instruct the Clients to pull the events and check if they match.
 
1408
    ?match(AnyEvent, 'notify_test_AnyPullC':doAction(PullAnyC, pull_any)),
 
1409
    ?match(StrEvent, 'notify_test_StrPullC':doAction(PullStrC, pull_str)),
 
1410
    ?match([StrEvent], 'notify_test_SeqPullC':doAction(PullSeqC, {pull_seq,1})),
 
1411
 
 
1412
 
 
1413
    io:format("###################### PUSH CONVERTED STRUCTURED ########"),
 
1414
 
 
1415
    %% Test with pushing an any event.
 
1416
    ?match(ok,'CosEventChannelAdmin_ProxyPushConsumer':push(ProxyPushConsumer, ConvertedStr)),
 
1417
 
 
1418
    %% Wait for a while so we are sure that all events have been delivered as far
 
1419
    %% as the Notification service can automatically.
 
1420
    timer:sleep(5000),
 
1421
 
 
1422
    %% Check if the Clients have received and stored the events.
 
1423
    ?match([ConvertedStr], 'notify_test_AnyPushC':doAction(PushAnyC, return_data)),
 
1424
    ?match([Event], 'notify_test_StrPushC':doAction(PushStrC, return_data)),
 
1425
    ?match([Event], 'notify_test_SeqPushC':doAction(PushSeqC, return_data)),
 
1426
 
 
1427
    %% Instruct the Clients to pull the events and check if they match.
 
1428
    ?match(ConvertedStr, 'notify_test_AnyPullC':doAction(PullAnyC, pull_any)),
 
1429
    ?match(Event, 'notify_test_StrPullC':doAction(PullStrC, pull_str)),
 
1430
    ?match([Event], 'notify_test_SeqPullC':doAction(PullSeqC, {pull_seq,10})),
 
1431
 
 
1432
 
 
1433
    io:format("###################### TRY PULL ########################"),
 
1434
 
 
1435
    %% Now we will push an any event after a delay. This means that try_pull-functions,
 
1436
    %% since it's not blocking, will return, [], NilAny or NilStructured events and 
 
1437
    %% the Boolean false.
 
1438
    spawn(notify_test_impl, delay, [ProxyPushConsumer, AnyEvent, 20000, 
 
1439
                                    'CosEventChannelAdmin_ProxyPushConsumer',push]),
 
1440
    ?match([], 'notify_test_AnyPushC':doAction(PushAnyC, return_data)),
 
1441
    ?match([], 'notify_test_StrPushC':doAction(PushStrC, return_data)),
 
1442
    ?match([], 'notify_test_SeqPushC':doAction(PushSeqC, return_data)),
 
1443
 
 
1444
    %% Instruct the Clients to pull the events and check if they match.
 
1445
    ?match({NilAnyEvent,false}, 'notify_test_AnyPullC':doAction(PullAnyC, try_pull_any)),
 
1446
    ?match({NilStrEvent,false}, 'notify_test_StrPullC':doAction(PullStrC, try_pull_str)),
 
1447
    ?match({[],false}, 'notify_test_SeqPullC':doAction(PullSeqC, {try_pull_seq,10})),
 
1448
 
 
1449
 
 
1450
    %% Instruct the Clients to pull the events and check if they match.
 
1451
    %% Pull is blocking so in the print-out we should see that nothing
 
1452
    %% is returned until the pushed event reaches the end proxies.
 
1453
    ?match(AnyEvent, 'notify_test_AnyPullC':doAction(PullAnyC, pull_any)),
 
1454
    ?match(StrEvent, 'notify_test_StrPullC':doAction(PullStrC, pull_str)),
 
1455
    ?match([StrEvent], 'notify_test_SeqPullC':doAction(PullSeqC, {pull_seq,1})),
 
1456
 
 
1457
    %% To make sure there are no other circumstanses which lead to a delay we
 
1458
    %% hold for some time.
 
1459
    timer:sleep(5000),
 
1460
    %% Check if the Clients have received and stored the events.
 
1461
    ?match([AnyEvent], 'notify_test_AnyPushC':doAction(PushAnyC, return_data)),
 
1462
    ?match([StrEvent], 'notify_test_StrPushC':doAction(PushStrC, return_data)),
 
1463
    ?match([StrEvent], 'notify_test_SeqPushC':doAction(PushSeqC, return_data)),
 
1464
 
 
1465
    %% Test with pushing a event sequence but only pull sequences of length 1.
 
1466
    ?match(ok,'CosNotifyChannelAdmin_SequenceProxyPushConsumer':push_structured_events(SequenceProxyPushConsumer, EventSeq)),
 
1467
 
 
1468
    %% Wait for a while so we are sure that all events have been delivered as far
 
1469
    %% as the Notification service can automatically.
 
1470
    timer:sleep(5000),
 
1471
    %% Pull 1 event at a time.
 
1472
    ?match([Event], 'notify_test_SeqPullC':doAction(PullSeqC, {pull_seq,1})),
 
1473
    ?match([Event2], 'notify_test_SeqPullC':doAction(PullSeqC, {pull_seq,1})),
 
1474
 
 
1475
    %% Following cases already tested; done for clean up.
 
1476
    ?match({any,_,Event}, 'notify_test_AnyPullC':doAction(PullAnyC, pull_any)),
 
1477
    ?match(Event, 'notify_test_StrPullC':doAction(PullStrC, pull_str)),
 
1478
    ?match({any,_,Event2}, 'notify_test_AnyPullC':doAction(PullAnyC, pull_any)),
 
1479
    ?match(Event2, 'notify_test_StrPullC':doAction(PullStrC, pull_str)),
 
1480
    ?match([{any,_,Event}, {any,_,Event2}], 'notify_test_AnyPushC':doAction(PushAnyC, return_data)),
 
1481
    ?match([Event, Event2], 'notify_test_StrPushC':doAction(PushStrC, return_data)),
 
1482
    ?match([Event, Event2], 'notify_test_SeqPushC':doAction(PushSeqC, return_data)),
 
1483
    %% clean up done
 
1484
 
 
1485
 
 
1486
    io:format("###################### PROXY PULLER ########################"),
 
1487
 
 
1488
    %% Now we will just add Events to a cleint and wait for the Notification service
 
1489
    %% to pull the events and forward them to the consumer clients.
 
1490
    ?match(ok, 'notify_test_SeqPushC':doAction(PullAnyS, {set_data, [AnyEvent]})),
 
1491
    
 
1492
 
 
1493
    %% Instruct the Clients to pull the events and check if they match.
 
1494
    %% Pull is blocking so in the print-out we should see that nothing
 
1495
    %% is returned until the pushed event reaches the end proxies.
 
1496
    ?match(AnyEvent, 'notify_test_AnyPullC':doAction(PullAnyC, pull_any)),
 
1497
    ?match(StrEvent, 'notify_test_StrPullC':doAction(PullStrC, pull_str)),
 
1498
    ?match([StrEvent], 'notify_test_SeqPullC':doAction(PullSeqC, {pull_seq,10})),
 
1499
 
 
1500
    %% To make sure there are no other circumstanses which lead to a delay we
 
1501
    %% hold for some time.
 
1502
    timer:sleep(5000),
 
1503
    %% Check if the Clients have received and stored the events.
 
1504
    ?match([AnyEvent], 'notify_test_AnyPushC':doAction(PushAnyC, return_data)),
 
1505
    ?match([StrEvent], 'notify_test_StrPushC':doAction(PushStrC, return_data)),
 
1506
    ?match([StrEvent], 'notify_test_SeqPushC':doAction(PushSeqC, return_data)),
 
1507
 
 
1508
    io:format("###################### SUSPENDED CONNECTION ################"),
 
1509
 
 
1510
 
 
1511
    %% Suspend the connections
 
1512
    ?match(ok,'CosNotifyChannelAdmin_SequenceProxyPushSupplier':suspend_connection(SequenceProxyPushSupplier)),
 
1513
    ?match(ok,'CosNotifyChannelAdmin_StructuredProxyPushSupplier':suspend_connection(StructuredProxyPushSupplier)),
 
1514
 
 
1515
    %% Test with pushing a event sequence.
 
1516
    ?match(ok,'CosNotifyChannelAdmin_SequenceProxyPushConsumer':push_structured_events(SequenceProxyPushConsumer, EventSeq)),
 
1517
 
 
1518
    %% Wait for a while so we are sure that all events have been delivered as far
 
1519
    %% as the Notification service can automatically.
 
1520
    timer:sleep(5000),
 
1521
 
 
1522
    %% Instruct the Clients to pull the events and check if they match.
 
1523
    ?match({any,_,Event}, 'notify_test_AnyPullC':doAction(PullAnyC, pull_any)),
 
1524
    ?match(Event, 'notify_test_StrPullC':doAction(PullStrC, pull_str)),
 
1525
    ?match([Event,Event2], 'notify_test_SeqPullC':doAction(PullSeqC, {pull_seq,2})),
 
1526
    ?match({any,_,Event2}, 'notify_test_AnyPullC':doAction(PullAnyC, pull_any)),
 
1527
    ?match(Event2, 'notify_test_StrPullC':doAction(PullStrC, pull_str)),
 
1528
 
 
1529
    %% Check if the Any Client have received and stored the events.
 
1530
    ?match([{any,_,Event}, {any,_,Event2}], 'notify_test_AnyPushC':doAction(PushAnyC, return_data)),
 
1531
 
 
1532
    %% Check if the other Clients have received any events. Error if have.
 
1533
    ?match([], 'notify_test_StrPushC':doAction(PushStrC, return_data)),
 
1534
    ?match([], 'notify_test_SeqPushC':doAction(PushSeqC, return_data)),
 
1535
 
 
1536
    ?match(ok,'CosNotifyChannelAdmin_SequenceProxyPushSupplier':resume_connection(SequenceProxyPushSupplier)),
 
1537
    ?match(ok,'CosNotifyChannelAdmin_StructuredProxyPushSupplier':resume_connection(StructuredProxyPushSupplier)),
 
1538
 
 
1539
    %% To be sure the test case don't fail due to time-race, sleep.
 
1540
    timer:sleep(5000),
 
1541
 
 
1542
    ?match([Event, Event2], 'notify_test_StrPushC':doAction(PushStrC, return_data)),
 
1543
    ?match([Event, Event2], 'notify_test_SeqPushC':doAction(PushSeqC, return_data)),
 
1544
 
 
1545
 
 
1546
    io:format("###################### FILTER EVENTS #######################"),
 
1547
 
 
1548
    %% Now we will add filters and see if the system behaves correctly.
 
1549
    FiFac = 'CosNotifyFilter_FilterFactory':oe_create(),
 
1550
    Filter = 'CosNotifyFilter_FilterFactory':create_filter(FiFac,"EXTENDED_TCL"),
 
1551
    %% Add constraints to the Filter
 
1552
    ?line[{_,_,CID1},{_,_,CID2}]= 
 
1553
        ?match([{'CosNotifyFilter_ConstraintInfo',_,_}, {'CosNotifyFilter_ConstraintInfo',_,_}],
 
1554
               'CosNotifyFilter_Filter':add_constraints(Filter, 
 
1555
                        [#'CosNotifyFilter_ConstraintExp'{event_types = 
 
1556
                                                          [#'CosNotification_EventType'{
 
1557
                                                             domain_name = "Spare*",
 
1558
                                                             type_name = "MOVIE"}],
 
1559
                                                          constraint_expr = "$type_name == 'MOVIE' and (('groucho' in $starlist) + ('chico' in $starlist) + ('harpo' in $starlist) + ('zeppo' in $starlist) + ('gummo' in $starlist)) > 2"},
 
1560
                        #'CosNotifyFilter_ConstraintExp'{event_types = 
 
1561
                                                          [#'CosNotification_EventType'{
 
1562
                                                              domain_name = "*",
 
1563
                                                             type_name = "TestResults"}],
 
1564
                                                          constraint_expr = "$test._length == 3 and ($test[0].score + $test[1].score + $test[2].score)/3 >=80"}])),
 
1565
 
 
1566
    ?match([{'CosNotifyFilter_ConstraintInfo',_,CID2}, {'CosNotifyFilter_ConstraintInfo',_,CID1}],
 
1567
                 'CosNotifyFilter_Filter':get_all_constraints(Filter)),
 
1568
    ?match([{'CosNotifyFilter_ConstraintInfo',_,CID1}], 
 
1569
                 'CosNotifyFilter_Filter':get_constraints(Filter, [CID1])),
 
1570
 
 
1571
    %% Associate the Filter with different objects.
 
1572
    %% Since we use the same filter for both objects the events will never reach the admin.
 
1573
    _FilterID = 'CosNotifyChannelAdmin_ConsumerAdmin':add_filter(AdminConsumer, Filter),
 
1574
 
 
1575
    _FilterID2 = 'CosNotifyChannelAdmin_StructuredProxyPushConsumer':add_filter(StructuredProxyPushConsumer, Filter),
 
1576
    event_filtering(FiFac, Filter, AdminConsumer, StructuredProxyPushConsumer, PushAnyC, 
 
1577
                          PushStrC, PushSeqC, PullAnyC, PullStrC, PullSeqC),
 
1578
    %% Remove the proxy filter so we can check if the events are filtered correctly by the admin.
 
1579
    ?match(ok, 'CosNotifyChannelAdmin_StructuredProxyPushConsumer':remove_all_filters(StructuredProxyPushConsumer)),
 
1580
    event_filtering(FiFac, Filter, AdminConsumer, StructuredProxyPushConsumer, PushAnyC, 
 
1581
                          PushStrC, PushSeqC, PullAnyC, PullStrC, PullSeqC),
 
1582
 
 
1583
 
 
1584
    catch corba:dispose(Filter),
 
1585
    catch corba:dispose(FiFac),
 
1586
    catch corba:dispose(SequenceProxyPushConsumer),
 
1587
    catch corba:dispose(StructuredProxyPushConsumer),
 
1588
    catch corba:dispose(ProxyPushConsumer),
 
1589
    catch corba:dispose(SequenceProxyPullConsumer),
 
1590
    catch corba:dispose(StructuredProxyPullConsumer),
 
1591
    catch corba:dispose(ProxyPullConsumer),
 
1592
    catch corba:dispose(SequenceProxyPushSupplier),
 
1593
    catch corba:dispose(StructuredProxyPushSupplier),
 
1594
    catch corba:dispose(ProxyPushSupplier),
 
1595
    catch corba:dispose(SequenceProxyPullSupplier),
 
1596
    catch corba:dispose(StructuredProxyPullSupplier),
 
1597
    catch corba:dispose(ProxyPullSupplier),
 
1598
    catch corba:dispose(AdminConsumer),
 
1599
    catch corba:dispose(AdminSupplier),
 
1600
    catch corba:dispose(Ch),
 
1601
    catch cosNotificationApp:stop_factory(Fac),
 
1602
    %% The Clients should have terminated by now. Check if it is so.
 
1603
    timer:sleep(5000),
 
1604
    ?match(true, corba_object:non_existent(PullSeqS)),
 
1605
    ?match(true, corba_object:non_existent(PullStrS)),
 
1606
    ?match(true, corba_object:non_existent(PullAnyS)),
 
1607
    ?match(true, corba_object:non_existent(PushSeqS)),
 
1608
    ?match(true, corba_object:non_existent(PushStrS)),
 
1609
    ?match(true, corba_object:non_existent(PushAnyS)),
 
1610
    ?match(true, corba_object:non_existent(PullSeqC)),
 
1611
    ?match(true, corba_object:non_existent(PullStrC)),
 
1612
    ?match(true, corba_object:non_existent(PullAnyC)),
 
1613
    ?match(true, corba_object:non_existent(PushSeqC)),
 
1614
    ?match(true, corba_object:non_existent(PushStrC)),
 
1615
    ?match(true, corba_object:non_existent(PushAnyC)),
 
1616
    ok.
 
1617
 
 
1618
event_filtering(_FiFac, _Filter, _AdminConsumer, StructuredProxyPushConsumer, PushAnyC, PushStrC, PushSeqC, PullAnyC, PullStrC, PullSeqC) ->
 
1619
    NilAnyEvent = any:create(orber_tc:null(), null),
 
1620
    NilStrEvent = ?not_CreateSE("","","",[],[],NilAnyEvent),
 
1621
 
 
1622
    TrueEvent1 = ?not_CreateSE("SpareTime","MOVIE",
 
1623
                                         "EventName", 
 
1624
                                         [#'CosNotification_Property'{name="starlist", 
 
1625
                                                                      value=any:create(orber_tc:sequence(orber_tc:string(0),0),
 
1626
                                                                                       ["groucho", "harpo", "sam", "gummo"])}],
 
1627
                                         [], any:create(orber_tc:null(), null)),
 
1628
    TrueEvent2 = ?not_CreateSE("Studies","TestResults",
 
1629
                                         "EventName", [],
 
1630
                                         [#'CosNotification_Property'{name="test", 
 
1631
                                                                      value=any:create(orber_tc:array(notify_test_data:tc(),3),
 
1632
                                                                                       {#notify_test_data{score=75,
 
1633
                                                                                                         name="name"},
 
1634
                                                                                        #notify_test_data{score=80,
 
1635
                                                                                                         name="name"},
 
1636
                                                                                        #notify_test_data{score=85,
 
1637
                                                                                                         name="name"}})}],
 
1638
                                         any:create(orber_tc:null(), null)),
 
1639
 
 
1640
    FalseEvent1 = ?not_CreateSE("SpareTime","MOVIE",
 
1641
                                         "EventName", 
 
1642
                                         [#'CosNotification_Property'{name="starlist", 
 
1643
                                                                      value=any:create(orber_tc:sequence(orber_tc:string(0),0),
 
1644
                                                                                       ["frodo", "bilbo", "sam", "gummo"])}],
 
1645
                                         [], any:create(orber_tc:null(), null)),
 
1646
    FalseEvent2 = ?not_CreateSE("Studies","TestResults",
 
1647
                                         "EventName", [],
 
1648
                                         [#'CosNotification_Property'{name="test", 
 
1649
                                                                      value=any:create(orber_tc:array(notify_test_data:tc(),3),
 
1650
                                                                                       {#notify_test_data{score=75,
 
1651
                                                                                                         name="name"},
 
1652
                                                                                        #notify_test_data{score=80,
 
1653
                                                                                                         name="name"},
 
1654
                                                                                        #notify_test_data{score=80,
 
1655
                                                                                                         name="name"}})}],
 
1656
                                         any:create(orber_tc:null(), null)),
 
1657
    %% Test with pushing the first structured event that should not be filtered away.
 
1658
    ?match(ok,'CosNotifyChannelAdmin_StructuredProxyPushConsumer':push_structured_event(StructuredProxyPushConsumer, TrueEvent1)),
 
1659
 
 
1660
    %% Wait for a while so we are sure that all events have been delivered as far
 
1661
    %% as the Notification service can automatically.
 
1662
    timer:sleep(5000),
 
1663
 
 
1664
    %% Check if the Clients have received and stored the events.
 
1665
    ?match([{any,_,TrueEvent1}], 'notify_test_AnyPushC':doAction(PushAnyC, return_data)),
 
1666
    ?match([TrueEvent1], 'notify_test_StrPushC':doAction(PushStrC, return_data)),
 
1667
    ?match([TrueEvent1], 'notify_test_SeqPushC':doAction(PushSeqC, return_data)),
 
1668
 
 
1669
    %% Instruct the Clients to pull the events and check if they match.
 
1670
    ?match({any,_,TrueEvent1}, 'notify_test_AnyPullC':doAction(PullAnyC, pull_any)),
 
1671
    ?match(TrueEvent1, 'notify_test_StrPullC':doAction(PullStrC, pull_str)),
 
1672
    ?match([TrueEvent1], 'notify_test_SeqPullC':doAction(PullSeqC, {pull_seq,1})),
 
1673
 
 
1674
    %% Test with pushing the second structured event that should not be filtered away.
 
1675
    ?match(ok,'CosNotifyChannelAdmin_StructuredProxyPushConsumer':push_structured_event(StructuredProxyPushConsumer, TrueEvent2)),
 
1676
 
 
1677
    %% Wait for a while so we are sure that all events have been delivered as far
 
1678
    %% as the Notification service can automatically.
 
1679
    timer:sleep(5000),
 
1680
 
 
1681
    %% Check if the Clients have received and stored the events.
 
1682
    ?match([{any,_,TrueEvent2}], 'notify_test_AnyPushC':doAction(PushAnyC, return_data)),
 
1683
    ?match([TrueEvent2], 'notify_test_StrPushC':doAction(PushStrC, return_data)),
 
1684
    ?match([TrueEvent2], 'notify_test_SeqPushC':doAction(PushSeqC, return_data)),
 
1685
 
 
1686
    %% Instruct the Clients to pull the events and check if they match.
 
1687
    ?match({any,_,TrueEvent2}, 'notify_test_AnyPullC':doAction(PullAnyC, pull_any)),
 
1688
    ?match(TrueEvent2, 'notify_test_StrPullC':doAction(PullStrC, pull_str)),
 
1689
    ?match([TrueEvent2], 'notify_test_SeqPullC':doAction(PullSeqC, {pull_seq,1})),
 
1690
 
 
1691
    %% Test with pushing the first structured event that should be filtered away.
 
1692
    ?match(ok,'CosNotifyChannelAdmin_StructuredProxyPushConsumer':push_structured_event(StructuredProxyPushConsumer, FalseEvent1)),
 
1693
 
 
1694
    %% Wait for a while so we are sure that all events have been delivered as far
 
1695
    %% as the Notification service can automatically.
 
1696
    timer:sleep(5000),
 
1697
 
 
1698
    %% Check if the Clients have received and stored the events.
 
1699
    ?match([], 'notify_test_AnyPushC':doAction(PushAnyC, return_data)),
 
1700
    ?match([], 'notify_test_StrPushC':doAction(PushStrC, return_data)),
 
1701
    ?match([], 'notify_test_SeqPushC':doAction(PushSeqC, return_data)),
 
1702
 
 
1703
    %% Instruct the Clients to pull the events and check if they match.
 
1704
    ?match({NilAnyEvent,false}, 'notify_test_AnyPullC':doAction(PullAnyC, try_pull_any)),
 
1705
    ?match({NilStrEvent,false}, 'notify_test_StrPullC':doAction(PullStrC, try_pull_str)),
 
1706
    ?match({[],false}, 'notify_test_SeqPullC':doAction(PullSeqC, {try_pull_seq,10})),
 
1707
 
 
1708
    %% Test with pushing the second structured event that should be filtered away.
 
1709
    ?match(ok,'CosNotifyChannelAdmin_StructuredProxyPushConsumer':push_structured_event(StructuredProxyPushConsumer, FalseEvent2)),
 
1710
 
 
1711
    %% Wait for a while so we are sure that all events have been delivered as far
 
1712
    %% as the Notification service can automatically.
 
1713
    timer:sleep(5000),
 
1714
 
 
1715
    %% Check if the Clients have received and stored the events.
 
1716
    ?match([], 'notify_test_AnyPushC':doAction(PushAnyC, return_data)),
 
1717
    ?match([], 'notify_test_StrPushC':doAction(PushStrC, return_data)),
 
1718
    ?match([], 'notify_test_SeqPushC':doAction(PushSeqC, return_data)),
 
1719
 
 
1720
    %% Instruct the Clients to pull the events and check if they match.
 
1721
    ?match({NilAnyEvent,false}, 'notify_test_AnyPullC':doAction(PullAnyC, try_pull_any)),
 
1722
    ?match({NilStrEvent,false}, 'notify_test_StrPullC':doAction(PullStrC, try_pull_str)),
 
1723
    ?match({[],false}, 'notify_test_SeqPullC':doAction(PullSeqC, {try_pull_seq,10})).
 
1724
    
 
1725
 
 
1726
 
 
1727
%%-----------------------------------------------------------------
 
1728
%%  Creating different cosEvent API tests 
 
1729
%%-----------------------------------------------------------------
 
1730
cosevent_api(doc) -> ["CosNotification Objects tested with CosEvent API", ""];
 
1731
cosevent_api(suite) -> [];
 
1732
cosevent_api(_Config) ->
 
1733
    Fac = (catch cosNotificationApp:start_global_factory(?FAC_OPT)),
 
1734
    ?match({_,key,_,_,_,_}, Fac),
 
1735
    {Ch, _Id1} = (catch 'CosNotifyChannelAdmin_EventChannelFactory':create_channel(Fac, ?defaultQoS, ?defaultAdm)),
 
1736
    ?match({_,key,_,_,_,_}, Ch),
 
1737
    AC=?match({_,key,_,_,_,_},
 
1738
                    'CosEventChannelAdmin_EventChannel':for_consumers(Ch)),
 
1739
    AS=?match({_,key,_,_,_,_},
 
1740
                    'CosEventChannelAdmin_EventChannel':for_suppliers(Ch)),
 
1741
 
 
1742
    PushS=?match({_,key,_,_,_,_},
 
1743
                       'CosEventChannelAdmin_ConsumerAdmin':obtain_push_supplier(AC)),
 
1744
    PullS=?match({_,key,_,_,_,_},
 
1745
                       'CosEventChannelAdmin_ConsumerAdmin':obtain_pull_supplier(AC)),
 
1746
 
 
1747
    PushC=?match({_,key,_,_,_,_},
 
1748
                       'CosEventChannelAdmin_SupplierAdmin':obtain_push_consumer(AS)),
 
1749
    PullC=?match({_,key,_,_,_,_},
 
1750
                       'CosEventChannelAdmin_SupplierAdmin':obtain_pull_consumer(AS)),
 
1751
 
 
1752
    PushAnyC=?match({_,key,_,_,_,_},
 
1753
                          'notify_test_AnyPushC':oe_create(['PUSH_ANY', PushC],
 
1754
                                                           [{local_typecheck, false}])),
 
1755
    PushStrC=?match({_,key,_,_,_,_},
 
1756
                          'notify_test_StrPushC':oe_create(['PUSH_STRUCTURED',false],
 
1757
                                                           [{local_typecheck, false}])),
 
1758
    PushSeqC=?match({_,key,_,_,_,_},
 
1759
                          'notify_test_SeqPushC':oe_create(['PUSH_SEQUENCE',false],
 
1760
                                                           [{local_typecheck, false}])),
 
1761
 
 
1762
    PullAnyC=?match({_,key,_,_,_,_},
 
1763
                          'notify_test_AnyPullC':oe_create(['PULL_ANY', PullC],
 
1764
                                                           [{local_typecheck, false}])),
 
1765
    PullStrC=?match({_,key,_,_,_,_},
 
1766
                          'notify_test_StrPullC':oe_create(['PULL_STRUCTURED',false],
 
1767
                                                           [{local_typecheck, false}])),
 
1768
    PullSeqC=?match({_,key,_,_,_,_},
 
1769
                          'notify_test_SeqPullC':oe_create(['PULL_SEQUENCE',false],
 
1770
                                                           [{local_typecheck, false}])),
 
1771
 
 
1772
    PushAnyS=?match({_,key,_,_,_,_},
 
1773
                          'notify_test_AnyPushS':oe_create(['PUSH_ANY', PushC],
 
1774
                                                           [{local_typecheck, false}])),
 
1775
    PushStrS=?match({_,key,_,_,_,_},
 
1776
                          'notify_test_StrPushS':oe_create(['PUSH_STRUCTURED',false],
 
1777
                                                           [{local_typecheck, false}])),
 
1778
    PushSeqS=?match({_,key,_,_,_,_},
 
1779
                          'notify_test_SeqPushS':oe_create(['PUSH_SEQUENCE',false],
 
1780
                                                           [{local_typecheck, false}])),
 
1781
 
 
1782
    PullAnyS=?match({_,key,_,_,_,_},
 
1783
                          'notify_test_AnyPullS':oe_create(['PULL_ANY', PullS],
 
1784
                                                           [{local_typecheck, false}])),
 
1785
    PullStrS=?match({_,key,_,_,_,_},
 
1786
                          'notify_test_StrPullS':oe_create(['PULL_STRUCTURED',false],
 
1787
                                                           [{local_typecheck, false}])),
 
1788
    PullSeqS=?match({_,key,_,_,_,_},
 
1789
                          'notify_test_SeqPullS':oe_create(['PULL_SEQUENCE',false],
 
1790
                                                           [{local_typecheck, false}])),
 
1791
 
 
1792
    %% In the OMG specification Proxies do not inherrit from CosEvent. Must use
 
1793
    %% Notify interface.
 
1794
    ?match({'EXCEPTION',{'BAD_PARAM',_,_,_}},
 
1795
                 'CosEventChannelAdmin_ProxyPullConsumer':connect_pull_supplier(PullC, PushStrS)),
 
1796
 
 
1797
    ?match(ok, 
 
1798
                 'CosEventChannelAdmin_ProxyPushSupplier':connect_push_consumer(PushS, PushAnyC)),
 
1799
    ?match(ok, 
 
1800
                 'CosEventChannelAdmin_ProxyPullSupplier':connect_pull_consumer(PullS, PullAnyC)),
 
1801
 
 
1802
    ?match(ok, 
 
1803
                 'CosEventChannelAdmin_ProxyPushConsumer':connect_push_supplier(PushC, PushAnyS)),
 
1804
    ?match(ok, 
 
1805
                 'CosEventChannelAdmin_ProxyPullConsumer':connect_pull_supplier(PullC, PullAnyS)),
 
1806
 
 
1807
    ?match({'EXCEPTION',{'CosEventChannelAdmin_AlreadyConnected',_}},
 
1808
                 'CosEventChannelAdmin_ProxyPullConsumer':connect_pull_supplier(PullC, PullAnyS)),
 
1809
 
 
1810
    ?match({'EXCEPTION',{'CosEventChannelAdmin_AlreadyConnected',_}},
 
1811
                 'CosNotifyChannelAdmin_ProxyPullConsumer':connect_pull_supplier(PullC, PullAnyS)),
 
1812
 
 
1813
    ?match(true, corba_object:is_a(PushS, "IDL:omg.org/CosNotifyChannelAdmin/ProxyPushSupplier:1.0")),
 
1814
    ?match(true, corba_object:is_a(PushS, "IDL:omg.org/CosEventChannelAdmin/ProxyPushSupplier:1.0")),
 
1815
 
 
1816
    catch corba:dispose(PushStrC),
 
1817
    catch corba:dispose(PushSeqC),
 
1818
    catch corba:dispose(PullStrC),
 
1819
    catch corba:dispose(PullSeqC),
 
1820
    catch corba:dispose(PushStrS),
 
1821
    catch corba:dispose(PushSeqS),
 
1822
    catch corba:dispose(PullStrS),
 
1823
    catch corba:dispose(PullSeqS),
 
1824
    catch corba:dispose(PushS),
 
1825
    catch corba:dispose(PullS),
 
1826
    catch corba:dispose(PushC),
 
1827
    catch corba:dispose(PullC),
 
1828
    catch corba:dispose(AC),
 
1829
    catch corba:dispose(AS),
 
1830
    catch corba:dispose(Ch),
 
1831
    catch cosNotificationApp:stop_factory(Fac),
 
1832
 
 
1833
    %% The Clients should have terminated by now. Check if it is so.
 
1834
    timer:sleep(5000),
 
1835
    ?match(true, corba_object:non_existent(PullAnyS)),
 
1836
    ?match(true, corba_object:non_existent(PushAnyS)),
 
1837
    ?match(true, corba_object:non_existent(PullAnyC)),
 
1838
    ?match(true, corba_object:non_existent(PushAnyC)),
 
1839
 
 
1840
 
 
1841
    ok.
 
1842
 
 
1843
%%-----------------------------------------------------------------
 
1844
%%  AdminPropertiesAdmin API tests 
 
1845
%%-----------------------------------------------------------------
 
1846
adm_api(doc) -> ["CosNotification AdminPropertiesAdmin tests", ""];
 
1847
adm_api(suite) -> [];
 
1848
adm_api(_Config) ->
 
1849
    Fac = (catch cosNotificationApp:start_global_factory(?FAC_OPT)),
 
1850
    ?match({_,key,_,_,_,_}, Fac),
 
1851
 
 
1852
    %% We need a few AdminProp:s to "play" with.
 
1853
    MQ0 = [#'CosNotification_Property'{name='CosNotification':'MaxQueueLength'(), 
 
1854
                                       value=any:create(orber_tc:long(), 0)}],
 
1855
    MC0 = [#'CosNotification_Property'{name='CosNotification':'MaxConsumers'(), 
 
1856
                                       value=any:create(orber_tc:long(), 0)}],
 
1857
    MS0 = [#'CosNotification_Property'{name='CosNotification':'MaxSuppliers'(), 
 
1858
                                       value=any:create(orber_tc:long(), 0)}],
 
1859
    MQError1 = [#'CosNotification_Property'{name='CosNotification':'MaxQueueLength'(), 
 
1860
                                            value=any:create(orber_tc:'float'(), 1.5)}],
 
1861
    MQError2 = [#'CosNotification_Property'{name='CosNotification':'MaxQueueLength'(), 
 
1862
                                            value=any:create(orber_tc:long(), -1)}],
 
1863
 
 
1864
    {Ch, _Id1} = (catch 'CosNotifyChannelAdmin_EventChannelFactory':create_channel(Fac, ?defaultQoS, ?defaultAdm)),
 
1865
    ?match({_,key,_,_,_,_}, Ch),
 
1866
 
 
1867
    %% Set new admin
 
1868
    ?match(ok, 'CosNotification_AdminPropertiesAdmin':set_admin(Ch, MQ0)),
 
1869
    %% It should be a list of three items. If we support more admin:s this 
 
1870
    %% must be updated.
 
1871
    ?match([_,_,_], 'CosNotification_AdminPropertiesAdmin':get_admin(Ch)),
 
1872
 
 
1873
    %% Try to set admin with an uncorrect value, i.e., not integer >= 0.
 
1874
    ?match({'EXCEPTION',{'CosNotification_UnsupportedAdmin',_,_}},
 
1875
                 'CosNotification_AdminPropertiesAdmin':set_admin(Ch, MQError1)),
 
1876
    ?match({'EXCEPTION',{'CosNotification_UnsupportedAdmin',_,_}},
 
1877
                 'CosNotification_AdminPropertiesAdmin':set_admin(Ch, MQError2)),
 
1878
 
 
1879
    %% Try setting the other two admins and chech if the value is correct.
 
1880
    ?match(ok, 'CosNotification_AdminPropertiesAdmin':set_admin(Ch, MC0)),
 
1881
    ?match([_,_,_], 'CosNotification_AdminPropertiesAdmin':get_admin(Ch)),
 
1882
 
 
1883
    ?match(ok, 'CosNotification_AdminPropertiesAdmin':set_admin(Ch, MS0)),
 
1884
    ?match([_,_,_], 'CosNotification_AdminPropertiesAdmin':get_admin(Ch)),
 
1885
 
 
1886
    catch corba:dispose(Ch),
 
1887
    catch cosNotificationApp:stop_factory(Fac),
 
1888
    ok.
 
1889
 
 
1890
 
 
1891
%%-----------------------------------------------------------------
 
1892
%%  QoSAdm API tests 
 
1893
%%-----------------------------------------------------------------
 
1894
qos_api(doc) -> ["CosNotification QoSAdmin tests", ""];
 
1895
qos_api(suite) -> [];
 
1896
qos_api(_Config) ->
 
1897
    Fac = (catch cosNotificationApp:start_global_factory(?FAC_OPT)),
 
1898
    ?match({_,key,_,_,_,_}, Fac),
 
1899
 
 
1900
    {Ch, _Id1} = (catch 'CosNotifyChannelAdmin_EventChannelFactory':create_channel(Fac, ?defaultQoS, ?defaultAdm)),
 
1901
    ?match({_,key,_,_,_,_}, Ch),
 
1902
 
 
1903
 
 
1904
    QoSPersistent = [#'CosNotification_Property'{name='CosNotification':'ConnectionReliability'(), 
 
1905
                                                 value=any:create(orber_tc:short(), 
 
1906
                                                                  'CosNotification':'Persistent'())}],
 
1907
    QoSBestEffort = [#'CosNotification_Property'{name='CosNotification':'ConnectionReliability'(), 
 
1908
                                                 value=any:create(orber_tc:short(), 
 
1909
                                                                  'CosNotification':'BestEffort'())}],
 
1910
 
 
1911
    QoSEventPersistent = [#'CosNotification_Property'{name='CosNotification':'EventReliability'(), 
 
1912
                                                 value=any:create(orber_tc:short(), 
 
1913
                                                                  'CosNotification':'Persistent'())}],
 
1914
    QoSEventBestEffort = [#'CosNotification_Property'{name='CosNotification':'EventReliability'(), 
 
1915
                                                 value=any:create(orber_tc:short(), 
 
1916
                                                                  'CosNotification':'BestEffort'())}],
 
1917
    
 
1918
    QoSOKMaxBatchSize = [#'CosNotification_Property'{name='CosNotification':'MaximumBatchSize'(), 
 
1919
                                                     value=any:create(orber_tc:long(), 200)}],
 
1920
    QoSToHighMaxBatchSize = [#'CosNotification_Property'{name='CosNotification':'MaximumBatchSize'(), 
 
1921
                                                         value=any:create(orber_tc:long(), 100000000)}],
 
1922
    
 
1923
    QoSToLowMaxBatchSize = [#'CosNotification_Property'{name='CosNotification':'MaximumBatchSize'(), 
 
1924
                                                        value=any:create(orber_tc:long(), -1)}],
 
1925
 
 
1926
    QoSOKStopTimeSupp = [#'CosNotification_Property'{name='CosNotification':'StopTimeSupported'(), 
 
1927
                                                     value=any:create(orber_tc:boolean(), true)}],
 
1928
    QoSWrongStopTimeSupp = [#'CosNotification_Property'{name="StopTimeSupp", 
 
1929
                                                        value=any:create(orber_tc:boolean(), true)}],
 
1930
    
 
1931
    QoSOKStartTimeSupp = [#'CosNotification_Property'{name='CosNotification':'StartTimeSupported'(), 
 
1932
                                                      value=any:create(orber_tc:boolean(), true)}],
 
1933
    QoSWrongStartTimeSupp = [#'CosNotification_Property'{name="StartTimeSupp", 
 
1934
                                                         value=any:create(orber_tc:boolean(), true)}],
 
1935
    QoSOKTimout = [#'CosNotification_Property'{name='CosNotification':'Timeout'(), 
 
1936
                                               value=any:create(orber_tc:unsigned_long_long(), 100)}],
 
1937
    
 
1938
 
 
1939
    %% The most complex QoS to set is ConnectionReliability, and the reason for this
 
1940
    %% is that we cannot set the Channel to offer best effort while its children
 
1941
    %% offer persistent. A child may only offer Persistent if its parent do, which
 
1942
    %% is why we must check the following:
 
1943
    %%           
 
1944
    %%                    #    Persistent        Change to       Best Effort
 
1945
    %%            _____
 
1946
    %%           |     | (1)                         ->       Check if children BE
 
1947
    %%           |Chann| (2)      ok                 <-
 
1948
    %%            -----
 
1949
    %%              |
 
1950
    %%            _____
 
1951
    %%           |     | (3)                         ->      Check if children BE
 
1952
    %%           |Admin| (4)  Check if parent Pers.  <-      
 
1953
    %%            -----
 
1954
    %%              |
 
1955
    %%            _____
 
1956
    %%           |     | (5)                         ->               ok
 
1957
    %%           |Proxy| (6) Check if parent Pers.   <-
 
1958
    %%            -----
 
1959
    %% NOTE: a parent always exists but we may change the QoS before creating any
 
1960
    %% childrens. The cases (2) and (5) is always ok, i.e., no need to confirm
 
1961
    %% with parent or children.
 
1962
 
 
1963
    %% We only have a channel. At the moment we can set ConnectionReliability
 
1964
    %% without asking anyone.
 
1965
    Q1='CosNotification_QoSAdmin':get_qos(Ch),
 
1966
    ?match({ok, _}, 'CosNotification_QoSAdmin':validate_qos(Ch, QoSBestEffort)),
 
1967
 
 
1968
    ?match(ok, 'CosNotification_QoSAdmin':set_qos(Ch, QoSPersistent)),
 
1969
    %% Match if no problems occur if we try to set QoS as is.
 
1970
    ?match(ok, 'CosNotification_QoSAdmin':set_qos(Ch, QoSPersistent)),
 
1971
 
 
1972
    %% Check validate.
 
1973
    ?match(ok, 'CosNotification_QoSAdmin':set_qos(Ch, QoSEventPersistent)),
 
1974
    ?match({ok, _}, 'CosNotification_QoSAdmin':validate_qos(Ch, QoSOKTimout)),
 
1975
    ?match({ok, _}, 'CosNotification_QoSAdmin':validate_qos(Ch, QoSEventBestEffort)),
 
1976
    ?match(ok, 'CosNotification_QoSAdmin':set_qos(Ch, QoSEventBestEffort)),
 
1977
    ?match({ok, _}, 'CosNotification_QoSAdmin':validate_qos(Ch, QoSOKTimout)),
 
1978
 
 
1979
    Q2='CosNotification_QoSAdmin':get_qos(Ch),
 
1980
    ?match(ok, 'CosNotification_QoSAdmin':set_qos(Ch, QoSBestEffort)),
 
1981
    ?match(Q1, 'CosNotification_QoSAdmin':get_qos(Ch)),
 
1982
 
 
1983
    %% Now we add an Admin object. An Admin object cannot switch ConnectionReliability
 
1984
    %% to BestEffort without checking with its children or Persistent without
 
1985
    %% confirming this with its Parent. At the moment, however, we only have a parent.
 
1986
    {CAdm, Id2} = 'CosNotifyChannelAdmin_EventChannel':new_for_consumers(Ch, 'AND_OP'),
 
1987
    ?match(Q1,'CosNotification_QoSAdmin':get_qos(CAdm)),
 
1988
    ?match({'EXCEPTION',{'CosNotification_UnsupportedQoS',_,_}},
 
1989
           'CosNotification_QoSAdmin':set_qos(CAdm, QoSPersistent)),
 
1990
    ?match(Q1, 'CosNotification_QoSAdmin':get_qos(CAdm)),
 
1991
    ?match(ok, 'CosNotification_QoSAdmin':set_qos(CAdm, QoSBestEffort)),
 
1992
    ?match(Q1, 'CosNotification_QoSAdmin':get_qos(CAdm)),
 
1993
 
 
1994
    %% Check if we can extract the Admin from the channel correctly.
 
1995
    ?match([0,Id2],'CosNotifyChannelAdmin_EventChannel':get_all_consumeradmins(Ch)),
 
1996
    ?match(CAdm,'CosNotifyChannelAdmin_EventChannel':get_consumeradmin(Ch, Id2)),
 
1997
    ?match(Ch, 'CosNotifyChannelAdmin_ConsumerAdmin':'_get_MyChannel'(CAdm)),
 
1998
    ?match(Id2, 'CosNotifyChannelAdmin_ConsumerAdmin':'_get_MyID'(CAdm)),
 
1999
 
 
2000
    %% Change the channel to provide Persistent service. Now we can set the 
 
2001
    %% Admin service to Persistent to. (4)
 
2002
    ?match(ok, 'CosNotification_QoSAdmin':set_qos(Ch, QoSPersistent)),
 
2003
    ?match(ok, 'CosNotification_QoSAdmin':set_qos(CAdm, QoSPersistent)),
 
2004
    ?match(Q2, 'CosNotification_QoSAdmin':get_qos(CAdm)),
 
2005
 
 
2006
    %% Since the Admin object now provide Persistent the Channel cannot switch
 
2007
    %% to BestEffort. (1)
 
2008
    ?match({'EXCEPTION',{'CosNotification_UnsupportedQoS',_,_}},
 
2009
           'CosNotification_QoSAdmin':set_qos(Ch, QoSBestEffort)),
 
2010
    %% Should still match Persistent.
 
2011
    ?match(Q2, 'CosNotification_QoSAdmin':get_qos(Ch)),
 
2012
    {PSup, _Id3} = 'CosNotifyChannelAdmin_ConsumerAdmin':obtain_notification_push_supplier(CAdm, 'ANY_EVENT'),
 
2013
    ?match(Q2, 'CosNotification_QoSAdmin':get_qos(CAdm)),
 
2014
    ?match('PUSH_ANY', 'CosNotifyChannelAdmin_ProxyPushConsumer':'_get_MyType'(PSup)),
 
2015
    ?match(CAdm, 'CosNotifyChannelAdmin_ProxyPushConsumer':'_get_MyAdmin'(PSup)),
 
2016
    ?match(Q2, 'CosNotification_QoSAdmin':get_qos(PSup)),
 
2017
 
 
2018
    %% At this point they all offer persistent connection, which means we have
 
2019
    %% to start with the proxy if we want to change to Best Effort. Hence,
 
2020
    %% the following two cases will fail.
 
2021
    ?match({'EXCEPTION',{'CosNotification_UnsupportedQoS',_,_}},
 
2022
           'CosNotification_QoSAdmin':set_qos(Ch, QoSBestEffort)),
 
2023
    ?match({'EXCEPTION',{'CosNotification_UnsupportedQoS',_,_}},
 
2024
           'CosNotification_QoSAdmin':set_qos(CAdm, QoSBestEffort)),
 
2025
    ?match(ok, 'CosNotification_QoSAdmin':set_qos(PSup, QoSBestEffort)),
 
2026
    %% Still not possible to change channel to Best Effort.
 
2027
    ?match({'EXCEPTION',{'CosNotification_UnsupportedQoS',_,_}},
 
2028
           'CosNotification_QoSAdmin':set_qos(Ch, QoSBestEffort)),
 
2029
    ?match(ok, 'CosNotification_QoSAdmin':set_qos(CAdm, QoSBestEffort)),
 
2030
    %% Now we change the channel to Best Effort.
 
2031
    ?match(ok, 'CosNotification_QoSAdmin':set_qos(Ch, QoSBestEffort)),
 
2032
    
 
2033
    %% Test if really are Best Effort
 
2034
    ?match(Q1, 'CosNotification_QoSAdmin':get_qos(Ch)),
 
2035
    ?match(Q1, 'CosNotification_QoSAdmin':get_qos(CAdm)),
 
2036
    ?match(Q1, 'CosNotification_QoSAdmin':get_qos(PSup)),
 
2037
 
 
2038
    %% Testing MaximumBatchSize (The highest value is defined in 
 
2039
    %% CosNotification_Common.erl
 
2040
    ?match(ok, 'CosNotification_QoSAdmin':set_qos(Ch, QoSOKMaxBatchSize)),
 
2041
    ?match({'EXCEPTION',{'CosNotification_UnsupportedQoS',_,_}},
 
2042
           'CosNotification_QoSAdmin':set_qos(Ch, QoSToHighMaxBatchSize)),
 
2043
    ?match({'EXCEPTION',{'CosNotification_UnsupportedQoS',_,_}},
 
2044
           'CosNotification_QoSAdmin':set_qos(Ch, QoSToLowMaxBatchSize)),
 
2045
 
 
2046
    ?match(ok, 'CosNotification_QoSAdmin':set_qos(Ch, QoSOKStartTimeSupp)),
 
2047
    ?match(ok, 'CosNotification_QoSAdmin':set_qos(Ch, QoSOKStopTimeSupp)),
 
2048
    ?match({'EXCEPTION',{'CosNotification_UnsupportedQoS',_,_}},
 
2049
           'CosNotification_QoSAdmin':set_qos(Ch, QoSWrongStartTimeSupp)),
 
2050
    ?match({'EXCEPTION',{'CosNotification_UnsupportedQoS',_,_}},
 
2051
           'CosNotification_QoSAdmin':set_qos(Ch, QoSWrongStopTimeSupp)),
 
2052
 
 
2053
    catch corba:dispose(CAdm),
 
2054
    catch corba:dispose(PSup),
 
2055
    catch corba:dispose(Ch),
 
2056
    cosNotificationApp:stop_factory(Fac),
 
2057
    ok.
 
2058
 
 
2059
%%-----------------------------------------------------------------
 
2060
%%  QoSAdm API tests 
 
2061
%%-----------------------------------------------------------------
 
2062
event_qos_api(doc) -> ["CosNotification QoSAdmin tests", ""];
 
2063
event_qos_api(suite) -> [];
 
2064
event_qos_api(_Config) ->
 
2065
    Fac = (catch cosNotificationApp:start_global_factory(?FAC_OPT)),
 
2066
    ?match({_,key,_,_,_,_}, Fac),
 
2067
    
 
2068
    %% Create some objects to test with. We start with default settings.
 
2069
    {Ch, _Id1} = (catch 'CosNotifyChannelAdmin_EventChannelFactory':create_channel(Fac, ?defaultQoS, ?defaultAdm)),
 
2070
    {CAdm, _Id2} = 'CosNotifyChannelAdmin_EventChannel':new_for_consumers(Ch, 'AND_OP'),
 
2071
    {PSup, _Id3} = 'CosNotifyChannelAdmin_ConsumerAdmin':obtain_notification_push_supplier(CAdm, 'ANY_EVENT'),
 
2072
 
 
2073
    %% Try setting an unsupported QoS.
 
2074
    ?match({'EXCEPTION',{'CosNotification_UnsupportedQoS',_,_}},
 
2075
           'CosNotifyChannelAdmin_ProxyConsumer':
 
2076
           validate_event_qos(PSup, 
 
2077
                              [#'CosNotification_Property'{name="Unsupported QoS", 
 
2078
                                                           value=any:create(orber_tc:short(), 1)}])),
 
2079
    %% Try setting min and max priority.
 
2080
    ?match({ok, _}, 'CosNotifyChannelAdmin_ProxyConsumer':
 
2081
           validate_event_qos(PSup, 
 
2082
                              [#'CosNotification_Property'{name=?not_Priority, 
 
2083
                                                           value=any:create(orber_tc:short(), 
 
2084
                                                                            ?not_LowestPriority)},
 
2085
                               #'CosNotification_Property'{name=?not_Priority, 
 
2086
                                                           value=any:create(orber_tc:short(), 
 
2087
                                                                            ?not_HighestPriority)}])),
 
2088
    %% Try setting priority values which are 1 to high and 1 to low respectively.
 
2089
    ?match({'EXCEPTION',{'MARSHAL',_,_,_}},
 
2090
           'CosNotifyChannelAdmin_ProxyConsumer':
 
2091
           validate_event_qos(PSup, 
 
2092
                              [#'CosNotification_Property'{name=?not_Priority, 
 
2093
                                                           value=any:create(orber_tc:short(), 
 
2094
                                                                            ?not_LowestPriority-1)},
 
2095
                               #'CosNotification_Property'{name=?not_Priority, 
 
2096
                                                           value=any:create(orber_tc:short(), 
 
2097
                                                                            ?not_HighestPriority+1)}])),
 
2098
    %% Try setting start- and stop-time (false default). Note the value associated 
 
2099
    %% with this property is not really a short but that is not what we are testing 
 
2100
    %% here so...
 
2101
    ?match({'EXCEPTION',{'CosNotification_UnsupportedQoS',_,_}},
 
2102
           'CosNotifyChannelAdmin_ProxyConsumer':
 
2103
           validate_event_qos(PSup, 
 
2104
                              [#'CosNotification_Property'{name=?not_StartTime, 
 
2105
                                                           value=any:create(orber_tc:short(), 0)}])),
 
2106
    ?match({'EXCEPTION',{'CosNotification_UnsupportedQoS',_,_}},
 
2107
           'CosNotifyChannelAdmin_ProxyConsumer':
 
2108
           validate_event_qos(PSup, 
 
2109
                              [#'CosNotification_Property'{name=?not_StopTime, 
 
2110
                                                           value=any:create(orber_tc:short(), 0)}])),
 
2111
    %% Allow StopTime
 
2112
    ?match(ok, 'CosNotification_QoSAdmin':set_qos(PSup, [#'CosNotification_Property'{name='CosNotification':'StopTimeSupported'(), 
 
2113
                                                                                   value=any:create(orber_tc:boolean(), true)}])),
 
2114
    ?match({ok,_},
 
2115
           'CosNotifyChannelAdmin_ProxyConsumer':
 
2116
           validate_event_qos(PSup, 
 
2117
                              [#'CosNotification_Property'{name=?not_StopTime, 
 
2118
                                                           value=any:create(orber_tc:short(), 0)}])),
 
2119
    %% Allow StartTime
 
2120
    ?match(ok, 'CosNotification_QoSAdmin':set_qos(PSup, [#'CosNotification_Property'{name='CosNotification':'StartTimeSupported'(), 
 
2121
                                                                                   value=any:create(orber_tc:boolean(), true)}])),
 
2122
    ?match({ok,_},
 
2123
           'CosNotifyChannelAdmin_ProxyConsumer':
 
2124
           validate_event_qos(PSup, 
 
2125
                              [#'CosNotification_Property'{name=?not_StopTime, 
 
2126
                                                           value=any:create(orber_tc:short(), 0)},
 
2127
                              #'CosNotification_Property'{name=?not_StartTime, 
 
2128
                                                          value=any:create(orber_tc:short(), 0)}])),
 
2129
 
 
2130
    %% We must reset StopTime since we cannot guarantee that an event will be delivered
 
2131
    %% if risk beeing discarded due to a delay.
 
2132
    ?match(ok, 'CosNotification_QoSAdmin':set_qos(PSup, [#'CosNotification_Property'{name='CosNotification':'StopTimeSupported'(), 
 
2133
                                                                                     value=any:create(orber_tc:boolean(), false)}])),
 
2134
    %% Does it accept Best Effort EventReliability? Must always be true.
 
2135
    ?match({ok,_},
 
2136
           'CosNotifyChannelAdmin_ProxyConsumer':
 
2137
           validate_event_qos(PSup, 
 
2138
                              [#'CosNotification_Property'{name=?not_EventReliability, 
 
2139
                                                           value=any:create(orber_tc:short(), ?not_BestEffort)}])),
 
2140
    %% Default is Best Effort; test if we can set Persistent EventReliability.
 
2141
    ?match({'EXCEPTION',{'CosNotification_UnsupportedQoS',_,_}},
 
2142
           'CosNotifyChannelAdmin_ProxyConsumer':
 
2143
           validate_event_qos(PSup, 
 
2144
                              [#'CosNotification_Property'{name=?not_EventReliability, 
 
2145
                                                           value=any:create(orber_tc:short(), ?not_Persistent)}])),
 
2146
 
 
2147
    %% Set Persistent
 
2148
    QoSPersistent = [#'CosNotification_Property'{name='CosNotification':'ConnectionReliability'(), 
 
2149
                                                 value=any:create(orber_tc:short(), 
 
2150
                                                                  'CosNotification':'Persistent'())}],
 
2151
    ?match(ok, 'CosNotification_QoSAdmin':set_qos(Ch, QoSPersistent)),
 
2152
    ?match(ok, 'CosNotification_QoSAdmin':set_qos(CAdm, QoSPersistent)),
 
2153
    ?match(ok, 'CosNotification_QoSAdmin':set_qos(PSup, QoSPersistent)),
 
2154
 
 
2155
    %% Does it accept Best Effort EventReliability? Must always be true.
 
2156
    ?match({ok, _},
 
2157
           'CosNotifyChannelAdmin_ProxyConsumer':
 
2158
           validate_event_qos(PSup, 
 
2159
                              [#'CosNotification_Property'{name=?not_EventReliability, 
 
2160
                                                           value=any:create(orber_tc:short(), ?not_BestEffort)}])),
 
2161
    %% Test if we can use Persistent EventReliability.
 
2162
    ?match({'EXCEPTION',{'CosNotification_UnsupportedQoS',_,_}},
 
2163
           'CosNotifyChannelAdmin_ProxyConsumer':
 
2164
           validate_event_qos(PSup, 
 
2165
                              [#'CosNotification_Property'{name=?not_EventReliability, 
 
2166
                                                           value=any:create(orber_tc:short(), ?not_Persistent)}])),
 
2167
    QoSEventPersistent = [#'CosNotification_Property'{name='CosNotification':'EventReliability'(), 
 
2168
                                                 value=any:create(orber_tc:short(), 
 
2169
                                                                  'CosNotification':'Persistent'())}],
 
2170
    ?match(ok, 'CosNotification_QoSAdmin':set_qos(Ch, QoSEventPersistent)),
 
2171
    ?match({'EXCEPTION',{'CosNotification_UnsupportedQoS',_,_}}, 
 
2172
           'CosNotification_QoSAdmin':set_qos(CAdm, QoSEventPersistent)),
 
2173
    ?match({'EXCEPTION',{'CosNotification_UnsupportedQoS',_,_}}, 
 
2174
           'CosNotification_QoSAdmin':set_qos(PSup, QoSEventPersistent)),
 
2175
 
 
2176
    ?match(ok, 'CosNotification_QoSAdmin':set_qos(PSup, [#'CosNotification_Property'{name='CosNotification':'StopTimeSupported'(), 
 
2177
                                                                                     value=any:create(orber_tc:boolean(), true)}])),
 
2178
    ?match({ok,_},
 
2179
           'CosNotifyChannelAdmin_ProxyConsumer':
 
2180
           validate_event_qos(PSup, 
 
2181
                              [#'CosNotification_Property'{name=?not_StopTime, 
 
2182
                                                           value=any:create(orber_tc:short(), 0)},
 
2183
                              #'CosNotification_Property'{name=?not_StartTime, 
 
2184
                                                          value=any:create(orber_tc:short(), 0)}])),
 
2185
    catch corba:dispose(CAdm),
 
2186
    catch corba:dispose(PSup),
 
2187
    catch corba:dispose(Ch),
 
2188
    cosNotificationApp:stop_factory(Fac),
 
2189
    ok.
 
2190
 
 
2191
%%-----------------------------------------------------------------
 
2192
%% Internal functions
 
2193
%%-----------------------------------------------------------------
 
2194
 
 
2195
%%-------------------- End of Module ------------------------------