~clint-fewbar/ubuntu/precise/erlang/merge-15b

« back to all changes in this revision

Viewing changes to lib/cosNotification/test/eventDB_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 2000-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    : eventDB_SUITE.erl
 
23
%% Purpose : 
 
24
%%--------------------------------------------------------------------
 
25
 
 
26
-module(eventDB_SUITE).
 
27
%%--------------- INCLUDES -----------------------------------
 
28
-include_lib("orber/include/corba.hrl").
 
29
-include_lib("orber/include/ifr_types.hrl").
 
30
%% cosEvent files.
 
31
-include_lib("cosEvent/include/CosEventChannelAdmin.hrl").
 
32
%% cosTime files.
 
33
-include_lib("cosTime/include/TimeBase.hrl").
 
34
%% Application files
 
35
-include_lib("cosNotification/include/CosNotification.hrl").
 
36
-include_lib("cosNotification/include/CosNotifyChannelAdmin.hrl").
 
37
-include_lib("cosNotification/include/CosNotifyComm.hrl").
 
38
-include_lib("cosNotification/include/CosNotifyFilter.hrl").
 
39
 
 
40
-include_lib("cosNotification/src/CosNotification_Definitions.hrl").
 
41
 
 
42
-include("idl_output/notify_test.hrl").
 
43
 
 
44
-include_lib("test_server/include/test_server.hrl").
 
45
 
 
46
%%--------------- DEFINES ------------------------------------
 
47
-define(default_timeout, ?t:minutes(20)).
 
48
-define(match(ExpectedRes, Expr),
 
49
        fun() ->
 
50
                AcTuAlReS = (catch (Expr)),
 
51
                case AcTuAlReS of
 
52
                    ExpectedRes ->
 
53
                        io:format("------ CORRECT RESULT ------~n~p~n",
 
54
                                  [AcTuAlReS]),
 
55
                        AcTuAlReS;
 
56
                    _ ->
 
57
                        io:format("###### ERROR ERROR ######~n~p~n",
 
58
                                  [AcTuAlReS]),
 
59
                        ?line exit(AcTuAlReS)
 
60
                end
 
61
        end()).
 
62
 
 
63
 
 
64
-define(EVENT1, ?not_CreateSE("","event1","",
 
65
                              [#'CosNotification_Property'
 
66
                               {name="Priority", 
 
67
                                value=any:create(orber_tc:short(), 0)},
 
68
                               #'CosNotification_Property'
 
69
                               {name="StartTime", 
 
70
                                 value=any:create('TimeBase_UtcT':tc(), 
 
71
                                                  #'TimeBase_UtcT'
 
72
                                                  {time=900000000, 
 
73
                                                   inacclo=0, inacchi=0, tdf=2})},
 
74
                               #'CosNotification_Property'
 
75
                               {name="StopTime", 
 
76
                                 value=any:create('TimeBase_UtcT':tc(), 
 
77
                                                  #'TimeBase_UtcT'
 
78
                                                  {time=900000000, 
 
79
                                                   inacclo=0, inacchi=0, tdf=2})},
 
80
                               #'CosNotification_Property'
 
81
                               {name="Timeout", 
 
82
                                 value=any:create(orber_tc:unsigned_long_long(), 900000000)}],
 
83
                              [], any:create(orber_tc:null(), null))).
 
84
-define(EVENT2, ?not_CreateSE("","event2","",
 
85
                              [#'CosNotification_Property'
 
86
                               {name="Priority", 
 
87
                                value=any:create(orber_tc:short(), 0)},
 
88
                               #'CosNotification_Property'
 
89
                               {name="StartTime", 
 
90
                                 value=any:create('TimeBase_UtcT':tc(), 
 
91
                                                  #'TimeBase_UtcT'
 
92
                                                  {time=800000000, 
 
93
                                                   inacclo=0, inacchi=0, tdf=2})},
 
94
                               #'CosNotification_Property'
 
95
                               {name="StopTime", 
 
96
                                 value=any:create('TimeBase_UtcT':tc(), 
 
97
                                                  #'TimeBase_UtcT'
 
98
                                                  {time=800000000, 
 
99
                                                   inacclo=0, inacchi=0, tdf=2})},
 
100
                               #'CosNotification_Property'
 
101
                               {name="Timeout", 
 
102
                                value=any:create(orber_tc:unsigned_long_long(), 800000000)}],
 
103
                              [], any:create(orber_tc:null(), null))).
 
104
-define(EVENT3, ?not_CreateSE("","event3","",
 
105
                              [#'CosNotification_Property'
 
106
                               {name="Priority", 
 
107
                                value=any:create(orber_tc:short(), 0)},
 
108
                               #'CosNotification_Property'
 
109
                               {name="StartTime", 
 
110
                                 value=any:create('TimeBase_UtcT':tc(), 
 
111
                                                  #'TimeBase_UtcT'
 
112
                                                  {time=700000000, 
 
113
                                                   inacclo=0, inacchi=0, tdf=2})},
 
114
                               #'CosNotification_Property'
 
115
                               {name="StopTime", 
 
116
                                 value=any:create('TimeBase_UtcT':tc(), 
 
117
                                                  #'TimeBase_UtcT'
 
118
                                                  {time=700000000, 
 
119
                                                   inacclo=0, inacchi=0, tdf=2})},
 
120
                               #'CosNotification_Property'
 
121
                               {name="Timeout", 
 
122
                                value=any:create(orber_tc:unsigned_long_long(), 700000000)}],
 
123
                              [], any:create(orber_tc:null(), null))).
 
124
-define(EVENT4, ?not_CreateSE("","event4","",
 
125
                              [#'CosNotification_Property'
 
126
                               {name="Priority", 
 
127
                                value=any:create(orber_tc:short(), 2)},
 
128
                               #'CosNotification_Property'
 
129
                               {name="StartTime", 
 
130
                                 value=any:create('TimeBase_UtcT':tc(), 
 
131
                                                  #'TimeBase_UtcT'
 
132
                                                  {time=300000000, 
 
133
                                                   inacclo=0, inacchi=0, tdf=2})},
 
134
                               #'CosNotification_Property'
 
135
                               {name="StopTime", 
 
136
                                 value=any:create('TimeBase_UtcT':tc(), 
 
137
                                                  #'TimeBase_UtcT'
 
138
                                                  {time=300000000, 
 
139
                                                   inacclo=0, inacchi=0, tdf=2})},
 
140
                               #'CosNotification_Property'
 
141
                               {name="Timeout", 
 
142
                                value=any:create(orber_tc:unsigned_long_long(), 300000000)}],
 
143
                              [], any:create(orber_tc:null(), null))).
 
144
-define(EVENT5, ?not_CreateSE("","event5","",
 
145
                              [#'CosNotification_Property'
 
146
                               {name="Priority", 
 
147
                                value=any:create(orber_tc:short(), 2)},
 
148
                               #'CosNotification_Property'
 
149
                               {name="StartTime", 
 
150
                                 value=any:create('TimeBase_UtcT':tc(), 
 
151
                                                  #'TimeBase_UtcT'
 
152
                                                  {time=200000000, 
 
153
                                                   inacclo=0, inacchi=0, tdf=2})},
 
154
                               #'CosNotification_Property'
 
155
                               {name="StopTime", 
 
156
                                 value=any:create('TimeBase_UtcT':tc(), 
 
157
                                                  #'TimeBase_UtcT'
 
158
                                                  {time=200000000, 
 
159
                                                   inacclo=0, inacchi=0, tdf=2})},
 
160
                               #'CosNotification_Property'
 
161
                               {name="Timeout", 
 
162
                                value=any:create(orber_tc:unsigned_long_long(), 200000000)}],
 
163
                              [], any:create(orber_tc:null(), null))).
 
164
-define(EVENT6, ?not_CreateSE("","event6","",
 
165
                              [#'CosNotification_Property'
 
166
                               {name="Priority", 
 
167
                                value=any:create(orber_tc:short(), 0)},
 
168
                               #'CosNotification_Property'
 
169
                               {name="StartTime", 
 
170
                                 value=any:create('TimeBase_UtcT':tc(), 
 
171
                                                  #'TimeBase_UtcT'
 
172
                                                  {time=500000000, 
 
173
                                                   inacclo=0, inacchi=0, tdf=2})},
 
174
                               #'CosNotification_Property'
 
175
                               {name="StopTime", 
 
176
                                 value=any:create('TimeBase_UtcT':tc(), 
 
177
                                                  #'TimeBase_UtcT'
 
178
                                                  {time=500000000, 
 
179
                                                   inacclo=0, inacchi=0, tdf=2})},
 
180
                               #'CosNotification_Property'
 
181
                               {name="Timeout", 
 
182
                                value=any:create(orber_tc:unsigned_long_long(), 500000000)}],
 
183
                              [], any:create(orber_tc:null(), null))).
 
184
-define(EVENT7, ?not_CreateSE("","event7","",
 
185
                              [#'CosNotification_Property'
 
186
                               {name="Priority", 
 
187
                                value=any:create(orber_tc:short(), -1)},
 
188
                               #'CosNotification_Property'
 
189
                               {name="StartTime", 
 
190
                                 value=any:create('TimeBase_UtcT':tc(), 
 
191
                                                  #'TimeBase_UtcT'
 
192
                                                  {time=400000000, 
 
193
                                                   inacclo=0, inacchi=0, tdf=2})},
 
194
                               #'CosNotification_Property'
 
195
                               {name="StopTime", 
 
196
                                 value=any:create('TimeBase_UtcT':tc(), 
 
197
                                                  #'TimeBase_UtcT'
 
198
                                                  {time=400000000, 
 
199
                                                   inacclo=0, inacchi=0, tdf=2})},
 
200
                               #'CosNotification_Property'
 
201
                               {name="Timeout", 
 
202
                                value=any:create(orber_tc:unsigned_long_long(), 400000000)}],
 
203
                              [], any:create(orber_tc:null(), null))).
 
204
-define(EVENT8, ?not_CreateSE("","event8","",
 
205
                              [#'CosNotification_Property'
 
206
                               {name="Priority", 
 
207
                                value=any:create(orber_tc:short(), -1)},
 
208
                               #'CosNotification_Property'
 
209
                               {name="StartTime", 
 
210
                                 value=any:create('TimeBase_UtcT':tc(), 
 
211
                                                  #'TimeBase_UtcT'
 
212
                                                  {time=600000000, 
 
213
                                                   inacclo=0, inacchi=0, tdf=2})},
 
214
                               #'CosNotification_Property'
 
215
                               {name="StopTime", 
 
216
                                 value=any:create('TimeBase_UtcT':tc(), 
 
217
                                                  #'TimeBase_UtcT'
 
218
                                                  {time=600000000, 
 
219
                                                   inacclo=0, inacchi=0, tdf=2})},
 
220
                               #'CosNotification_Property'
 
221
                               {name="Timeout", 
 
222
                                value=any:create(orber_tc:unsigned_long_long(), 600000000)}],
 
223
                              [], any:create(orber_tc:null(), null))).
 
224
-define(EVENT9, ?not_CreateSE("","event9","",
 
225
                              [#'CosNotification_Property'
 
226
                               {name="Priority", 
 
227
                                value=any:create(orber_tc:short(), 0)},
 
228
                               #'CosNotification_Property'
 
229
                               {name="StartTime", 
 
230
                                 value=any:create('TimeBase_UtcT':tc(), 
 
231
                                                  #'TimeBase_UtcT'
 
232
                                                  {time=100000000, 
 
233
                                                   inacclo=0, inacchi=0, tdf=2})},
 
234
                               #'CosNotification_Property'
 
235
                               {name="StopTime", 
 
236
                                 value=any:create('TimeBase_UtcT':tc(), 
 
237
                                                  #'TimeBase_UtcT'
 
238
                                                  {time=100000000, 
 
239
                                                   inacclo=0, inacchi=0, tdf=2})},
 
240
                               #'CosNotification_Property'
 
241
                               {name="Timeout", 
 
242
                                 value=any:create(orber_tc:unsigned_long_long(), 100000000)}],
 
243
                              [], any:create(orber_tc:null(), null))).
 
244
 
 
245
-define(EVENTS, [?EVENT1, ?EVENT2, ?EVENT3, ?EVENT4, ?EVENT5, ?EVENT6, ?EVENT7, 
 
246
                 ?EVENT8, ?EVENT9]).
 
247
 
 
248
 
 
249
-define(PRIOORDER, [?EVENT4, ?EVENT5, ?EVENT1, ?EVENT2, ?EVENT3, ?EVENT6, ?EVENT9, 
 
250
                    ?EVENT7, ?EVENT8]).
 
251
 
 
252
-define(FIFOORDER, ?EVENTS).
 
253
 
 
254
-define(DEADLINEORDER, [?EVENT9, ?EVENT5, ?EVENT4, ?EVENT7, ?EVENT6, ?EVENT8, ?EVENT3,
 
255
                       ?EVENT2, ?EVENT1]).
 
256
 
 
257
-define(NO_OF_EVENTS, 9).
 
258
 
 
259
%%-----------------------------------------------------------------
 
260
%% External exports
 
261
%%-----------------------------------------------------------------
 
262
-export([all/0, suite/0,groups/0,init_per_group/2,end_per_group/2, 
 
263
         cases/0, init_per_suite/1, end_per_suite/1, reorder_api/1, 
 
264
         lookup_api/1,
 
265
         discard_api/1, max_events_api/1, gc_api/1, auto_gc_api/1,
 
266
         start_stop_time_api/1, mapping_filter_api/1, persisten_event_api/1,
 
267
         init_per_testcase/2, end_per_testcase/2]).
 
268
 
 
269
%%-----------------------------------------------------------------
 
270
%% Func: all/1
 
271
%% Args: 
 
272
%% Returns: 
 
273
%%-----------------------------------------------------------------
 
274
suite() -> [{ct_hooks,[ts_install_cth]}].
 
275
 
 
276
all() -> 
 
277
    cases().
 
278
 
 
279
groups() -> 
 
280
    [].
 
281
 
 
282
init_per_group(_GroupName, Config) ->
 
283
    Config.
 
284
 
 
285
end_per_group(_GroupName, Config) ->
 
286
    Config.
 
287
 
 
288
 
 
289
cases() -> 
 
290
    [persisten_event_api, start_stop_time_api,
 
291
     mapping_filter_api, max_events_api, discard_api,
 
292
     reorder_api, lookup_api, gc_api, auto_gc_api].
 
293
 
 
294
 
 
295
        
 
296
%%-----------------------------------------------------------------
 
297
%% Init and cleanup functions.
 
298
%%-----------------------------------------------------------------
 
299
 
 
300
init_per_testcase(_Case, Config) ->
 
301
    ?line Dog=test_server:timetrap(?default_timeout),
 
302
    [{watchdog, Dog}|Config].
 
303
 
 
304
 
 
305
end_per_testcase(_Case, Config) ->
 
306
    Dog = ?config(watchdog, Config),
 
307
    test_server:timetrap_cancel(Dog),
 
308
    ok.
 
309
 
 
310
init_per_suite(Config) ->
 
311
    Path = code:which(?MODULE),
 
312
    code:add_pathz(filename:join(filename:dirname(Path), "idl_output")),
 
313
    orber:jump_start(),
 
314
    cosTime:install_time(),
 
315
    cosTime:start(),
 
316
    if
 
317
        is_list(Config) ->
 
318
            Config;
 
319
        true ->
 
320
            exit("Config not a list")
 
321
    end.
 
322
 
 
323
end_per_suite(Config) ->
 
324
    Path = code:which(?MODULE),
 
325
    code:del_path(filename:join(filename:dirname(Path), "idl_output")),
 
326
    cosTime:stop(),
 
327
    cosTime:uninstall_time(),
 
328
    orber:jump_stop(),
 
329
    Config.
 
330
 
 
331
 
 
332
%%-----------------------------------------------------------------
 
333
%%  cosNotification_eventDB lookup API tests 
 
334
%%-----------------------------------------------------------------
 
335
mapping_filter_api(doc) -> ["The event DB is used to store events which cannot be", 
 
336
                            "delivered at once. This case is supposed to test", 
 
337
                            "that the events are delivered in the correct order", 
 
338
                            "if a MappingFilter have benn associated.", 
 
339
                     ""];
 
340
mapping_filter_api(suite) -> [];
 
341
mapping_filter_api(_Config) ->
 
342
    InitQoS       = ?not_CreateInitQoS(),
 
343
    InitQoS2      = ?not_SetMaxEventsPerConsumer(InitQoS,100),
 
344
    InitQoS3      = ?not_SetStartTimeSupported(InitQoS2, false),
 
345
    InitQoS4      = ?not_SetStopTimeSupported(InitQoS3, true),
 
346
    QoS           = ?not_SetDiscardPolicy(InitQoS4, ?not_AnyOrder),
 
347
 
 
348
    PriorityQoS   = ?not_SetOrderPolicy(QoS, ?not_PriorityOrder),
 
349
    DeadlineQoS   = ?not_SetOrderPolicy(QoS, ?not_DeadlineOrder),
 
350
 
 
351
    %% "Calculate" data once:
 
352
    %% NOTE! Even though the an Event do not match any of the constarints the
 
353
    %% default value will be used. Hence, the events will not be stored in the
 
354
    %% way described in the definitions above. For example, when using deadline order
 
355
    %% all the events will be stored in FIFO order since the usag of a MappingFilter
 
356
    %% all evnts will have the same deadline (except event6).
 
357
    Events        = ?EVENTS,
 
358
    PrioOrder     = [?EVENT6, ?EVENT1, ?EVENT2, ?EVENT3, ?EVENT4, ?EVENT5, ?EVENT7, 
 
359
                     ?EVENT8, ?EVENT9], 
 
360
    DeadlineOrder = [?EVENT1, ?EVENT2, ?EVENT3, ?EVENT4, ?EVENT5, ?EVENT7, ?EVENT8, 
 
361
                     ?EVENT9],
 
362
 
 
363
 
 
364
    FiFac = 'CosNotifyFilter_FilterFactory':oe_create(),
 
365
    ?match({_,key,_,_,_,_}, FiFac),
 
366
    
 
367
    PrioFilter = 'CosNotifyFilter_FilterFactory':
 
368
        create_mapping_filter(FiFac, "EXTENDED_TCL", any:create(orber_tc:short(), 0)),
 
369
    DLFilter = 'CosNotifyFilter_FilterFactory':
 
370
        create_mapping_filter(FiFac, "EXTENDED_TCL", any:create(orber_tc:unsigned_long_long(), 1000000000)),
 
371
    
 
372
    ?match([_],
 
373
           'CosNotifyFilter_MappingFilter':add_mapping_constraints(PrioFilter, 
 
374
                        [#'CosNotifyFilter_MappingConstraintPair'
 
375
                         {constraint_expression = #'CosNotifyFilter_ConstraintExp'
 
376
                          {event_types = [#'CosNotification_EventType'
 
377
                                          {domain_name = "",
 
378
                                           type_name = "event6"}],
 
379
                           constraint_expr = "2==2"},
 
380
                          result_to_set = any:create(orber_tc:short(), 10)}])),
 
381
    ?match([_],
 
382
           'CosNotifyFilter_MappingFilter':add_mapping_constraints(DLFilter, 
 
383
                        [#'CosNotifyFilter_MappingConstraintPair'
 
384
                         {constraint_expression = #'CosNotifyFilter_ConstraintExp'
 
385
                          {event_types = [#'CosNotification_EventType'
 
386
                                          {domain_name = "",
 
387
                                           type_name = "event6"}],
 
388
                           constraint_expr = "2==2"},
 
389
                          result_to_set = any:create(orber_tc:unsigned_long_long(), 200000000)}])),
 
390
 
 
391
 
 
392
    do_lookup(PriorityQoS, Events, PrioOrder, "Priority Order", undefined, PrioFilter, 0),
 
393
    do_lookup(DeadlineQoS, Events, DeadlineOrder, "Deadline Order", DLFilter, undefined, 23000),
 
394
    ok.
 
395
 
 
396
do_lookup(QoS, Events, Return, Txt, DLFilter, PrioFilter, Timeout) ->
 
397
    io:format("#################### ~s ###################~n", [Txt]),
 
398
    Ref  = cosNotification_eventDB:create_db(QoS, 60, 50, undefined),
 
399
    create_loop(Events, Ref, DLFilter, PrioFilter),
 
400
    timer:sleep(Timeout),
 
401
    ?match({Return,_}, cosNotification_eventDB:get_events(Ref, ?NO_OF_EVENTS)),
 
402
    cosNotification_eventDB:destroy_db(Ref).
 
403
 
 
404
%%-----------------------------------------------------------------
 
405
%%  cosNotification_eventDB discard API tests 
 
406
%%-----------------------------------------------------------------
 
407
discard_api(doc) -> ["The event DB is used to store events which cannot be", 
 
408
                     "delivered at once. If MaxEvents limit is reached there", 
 
409
                     "different ways we can discard the. This case will test", 
 
410
                     "all permutations of order and discard policies.",
 
411
                     ""];
 
412
discard_api(suite) -> [];
 
413
discard_api(_Config) ->
 
414
    InitQoS1    = ?not_CreateInitQoS(),
 
415
    InitQoS2    = ?not_SetPriority(InitQoS1, 10),
 
416
    InitQoS3    = ?not_SetStartTimeSupported(InitQoS2, false),
 
417
    QoS         = ?not_SetMaxEventsPerConsumer(InitQoS3, 5),
 
418
    %% The different order policies. To each order we must apply every possible
 
419
    %% discard policy to each order policy setting. We also have to test and
 
420
    %% change the policies for each setting.
 
421
    AnyQoS      = ?not_SetOrderPolicy(QoS, ?not_AnyOrder),
 
422
    PriorityQoS = ?not_SetOrderPolicy(QoS, ?not_PriorityOrder),
 
423
    FifoQoS     = ?not_SetOrderPolicy(QoS, ?not_FifoOrder),
 
424
    DeadlineQoS = ?not_SetOrderPolicy(QoS, ?not_DeadlineOrder),
 
425
 
 
426
    Events        = ?EVENTS,
 
427
 
 
428
    %% Test using Any discard policy
 
429
    do_discard(Events, ?not_SetDiscardPolicy(AnyQoS, ?not_AnyOrder), 
 
430
               [?EVENT4, ?EVENT5, ?EVENT1, ?EVENT2, ?EVENT3],
 
431
               "Discard and Order eq. Any"),
 
432
    do_discard(Events, ?not_SetDiscardPolicy(PriorityQoS, ?not_AnyOrder), 
 
433
               [?EVENT4, ?EVENT5, ?EVENT1, ?EVENT2, ?EVENT3],
 
434
               "Discard Any and Order Priority"),
 
435
    do_discard(Events, ?not_SetDiscardPolicy(FifoQoS, ?not_AnyOrder), 
 
436
               [?EVENT1, ?EVENT2, ?EVENT3, ?EVENT4, ?EVENT5],
 
437
               "Discard Any and Order Fifo"),
 
438
    do_discard(Events, ?not_SetDiscardPolicy(DeadlineQoS, ?not_AnyOrder), 
 
439
               [?EVENT5, ?EVENT4, ?EVENT3, ?EVENT2, ?EVENT1],
 
440
               "Discard Any and Order Deadline"),
 
441
    
 
442
    %% Test using RejectNewEvents discard policy
 
443
    do_discard(Events, ?not_SetDiscardPolicy(AnyQoS, ?not_RejectNewEvents), 
 
444
               [?EVENT4, ?EVENT5, ?EVENT1, ?EVENT2, ?EVENT3],
 
445
               "Discard RejectNewEvents and Order Any"),
 
446
    do_discard(Events, ?not_SetDiscardPolicy(PriorityQoS, ?not_RejectNewEvents), 
 
447
               [?EVENT4, ?EVENT5, ?EVENT1, ?EVENT2, ?EVENT3],
 
448
               "Discard RejectNewEvents and Order Priority"),
 
449
    do_discard(Events, ?not_SetDiscardPolicy(FifoQoS, ?not_RejectNewEvents), 
 
450
               [?EVENT1, ?EVENT2, ?EVENT3, ?EVENT4, ?EVENT5],
 
451
               "Discard RejectNewEvents and Order Fifo"),
 
452
    do_discard(Events, ?not_SetDiscardPolicy(DeadlineQoS, ?not_RejectNewEvents), 
 
453
               [?EVENT5, ?EVENT4, ?EVENT3, ?EVENT2, ?EVENT1],
 
454
               "Discard RejectNewEvents and Order Deadline"),
 
455
    
 
456
    %% Test using Lifo discard policy
 
457
    do_discard(Events, ?not_SetDiscardPolicy(AnyQoS, ?not_LifoOrder), 
 
458
               [?EVENT4, ?EVENT5, ?EVENT1, ?EVENT2, ?EVENT3],
 
459
               "Discard Lifo and Order Any"),
 
460
    do_discard(Events, ?not_SetDiscardPolicy(PriorityQoS, ?not_LifoOrder), 
 
461
               [?EVENT4, ?EVENT5, ?EVENT1, ?EVENT2, ?EVENT3],
 
462
               "Discard Lifo and Order Priority"),
 
463
    do_discard(Events, ?not_SetDiscardPolicy(FifoQoS, ?not_LifoOrder), 
 
464
               [?EVENT1, ?EVENT2, ?EVENT3, ?EVENT4, ?EVENT5],
 
465
               "Discard Lifo and Order Fifo"),
 
466
    do_discard(Events, ?not_SetDiscardPolicy(DeadlineQoS, ?not_LifoOrder), 
 
467
               [?EVENT5, ?EVENT4, ?EVENT3, ?EVENT2, ?EVENT1],
 
468
               "Discard Lifo and Order Deadline"),
 
469
    
 
470
    %% Test using Fifo discard policy
 
471
    do_discard(Events, ?not_SetDiscardPolicy(AnyQoS, ?not_FifoOrder), 
 
472
               [?EVENT5, ?EVENT6, ?EVENT9, ?EVENT7, ?EVENT8],
 
473
               "Discard Fifo and Order Any"),
 
474
    do_discard(Events, ?not_SetDiscardPolicy(PriorityQoS, ?not_FifoOrder), 
 
475
               [?EVENT5, ?EVENT6, ?EVENT9, ?EVENT7, ?EVENT8],
 
476
               "Discard Fifo and Order Priority"),
 
477
    do_discard(Events, ?not_SetDiscardPolicy(FifoQoS, ?not_FifoOrder), 
 
478
               [?EVENT5, ?EVENT6, ?EVENT7, ?EVENT8, ?EVENT9],
 
479
               "Discard Fifo and Order Fifo"),
 
480
    do_discard(Events, ?not_SetDiscardPolicy(DeadlineQoS, ?not_FifoOrder), 
 
481
               [?EVENT9, ?EVENT5, ?EVENT7, ?EVENT6, ?EVENT8],
 
482
               "Discard Fifo and Order Deadline"),
 
483
    
 
484
    %% Test using Priority discard policy
 
485
    do_discard(Events, ?not_SetDiscardPolicy(AnyQoS, ?not_PriorityOrder), 
 
486
               [?EVENT4, ?EVENT5, ?EVENT1, ?EVENT2, ?EVENT3],
 
487
               "Discard Priority and Order Any"),
 
488
    do_discard(Events, ?not_SetDiscardPolicy(PriorityQoS, ?not_PriorityOrder), 
 
489
               [?EVENT4, ?EVENT5, ?EVENT1, ?EVENT2, ?EVENT3],
 
490
               "Discard Priority and Order Priority"),
 
491
    do_discard(Events, ?not_SetDiscardPolicy(FifoQoS, ?not_PriorityOrder), 
 
492
               [?EVENT1, ?EVENT2, ?EVENT3, ?EVENT4, ?EVENT5],
 
493
               "Discard Priority and Order Fifo"),
 
494
    do_discard(Events, ?not_SetDiscardPolicy(DeadlineQoS, ?not_PriorityOrder), 
 
495
               [?EVENT5, ?EVENT4, ?EVENT3, ?EVENT2, ?EVENT1],
 
496
               "Discard Priority and Order Deadline"),
 
497
    
 
498
    %% Test using Deadline discard policy
 
499
    do_discard(Events, ?not_SetDiscardPolicy(AnyQoS, ?not_DeadlineOrder), 
 
500
               [?EVENT1, ?EVENT2, ?EVENT3, ?EVENT6, ?EVENT8],
 
501
               "Discard Deadline and Order Any"),
 
502
    do_discard(Events, ?not_SetDiscardPolicy(PriorityQoS, ?not_DeadlineOrder), 
 
503
               [?EVENT1, ?EVENT2, ?EVENT3, ?EVENT6, ?EVENT8],
 
504
               "Discard Deadline and Order Priority"),
 
505
    do_discard(Events, ?not_SetDiscardPolicy(FifoQoS, ?not_DeadlineOrder), 
 
506
               [?EVENT1, ?EVENT2, ?EVENT3, ?EVENT6, ?EVENT8],
 
507
               "Discard Deadline and Order Fifo"),
 
508
    do_discard(Events, ?not_SetDiscardPolicy(DeadlineQoS, ?not_DeadlineOrder), 
 
509
               [?EVENT6, ?EVENT8, ?EVENT3, ?EVENT2, ?EVENT1],
 
510
               "Discard Deadline and Order Deadline"),
 
511
    
 
512
    ok.
 
513
 
 
514
do_discard(Events, QoS, Reply, Txt) ->
 
515
    io:format("################# ~s #################~n", [Txt]),
 
516
    Ref  = cosNotification_eventDB:create_db(QoS, 60, 50, undefined),
 
517
    create_loop(Events, Ref),
 
518
    ?match({Reply,_}, cosNotification_eventDB:get_events(Ref, ?NO_OF_EVENTS)),
 
519
    cosNotification_eventDB:destroy_db(Ref).
 
520
 
 
521
 
 
522
%%-----------------------------------------------------------------
 
523
%%  cosNotification_eventDB lookup API tests 
 
524
%%-----------------------------------------------------------------
 
525
lookup_api(doc) -> ["The event DB is used to store events which cannot be", 
 
526
                     "delivered at once. This case is supposed to test", 
 
527
                     "that the events are delivered in the correct order.", 
 
528
                     ""];
 
529
lookup_api(suite) -> [];
 
530
lookup_api(_Config) ->
 
531
    InitQoS       = ?not_CreateInitQoS(),
 
532
    InitQoS2      = ?not_SetMaxEventsPerConsumer(InitQoS,100),
 
533
    InitQoS3      = ?not_SetStartTimeSupported(InitQoS2, false),
 
534
    QoS           = ?not_SetDiscardPolicy(InitQoS3, ?not_AnyOrder),
 
535
 
 
536
    AnyQoS        = ?not_SetOrderPolicy(QoS, ?not_AnyOrder),
 
537
    PriorityQoS   = ?not_SetOrderPolicy(QoS, ?not_PriorityOrder),
 
538
    FifoQoS       = ?not_SetOrderPolicy(QoS, ?not_FifoOrder),
 
539
    DeadlineQoS   = ?not_SetOrderPolicy(QoS, ?not_DeadlineOrder),
 
540
 
 
541
    %% "Calculate" data once:
 
542
    Events        = ?EVENTS,
 
543
    PrioOrder     = ?PRIOORDER,
 
544
    FifoOrder     = ?FIFOORDER,
 
545
    DeadlineOrder = ?DEADLINEORDER,
 
546
 
 
547
    do_lookup(PriorityQoS, Events, PrioOrder, "Priority Order"),
 
548
    do_lookup(FifoQoS, Events, FifoOrder, "Fifo Order"),
 
549
    do_lookup(DeadlineQoS, Events, DeadlineOrder, "Deadline Order"),
 
550
    do_lookup(AnyQoS, Events, PrioOrder, "Any Order"),
 
551
    ok.
 
552
 
 
553
do_lookup(QoS, Events, Return, Txt) ->
 
554
    io:format("#################### ~s ###################~n", [Txt]),
 
555
    Ref  = cosNotification_eventDB:create_db(QoS, 60, 50, undefined),
 
556
    create_loop(Events, Ref),
 
557
    ?match({Return,_}, cosNotification_eventDB:get_events(Ref, ?NO_OF_EVENTS)),
 
558
    cosNotification_eventDB:destroy_db(Ref).
 
559
 
 
560
 
 
561
%%-----------------------------------------------------------------
 
562
%%  cosNotification_eventDB max events API tests 
 
563
%%-----------------------------------------------------------------
 
564
max_events_api(doc) -> ["The event DB is used to store events which cannot be", 
 
565
                     "delivered at once. If the MaxEvents QoS is updated we must be", 
 
566
                     "able to reduce the amount of stored events.", 
 
567
                     ""];
 
568
max_events_api(suite) -> [];
 
569
max_events_api(_Config) ->
 
570
 
 
571
    QoS1             = ?not_CreateInitQoS(),
 
572
    QoS2             = ?not_SetOrderPolicy(QoS1, ?not_FifoOrder),
 
573
    QoS3             = ?not_SetDiscardPolicy(QoS2, ?not_RejectNewEvents),
 
574
    QoS4             = ?not_SetStartTimeSupported(QoS3, false),
 
575
    QoS_NO_OF_EVENTS = ?not_SetMaxEventsPerConsumer(QoS4, ?NO_OF_EVENTS),
 
576
    QoS_5_EVENTS     = ?not_SetMaxEventsPerConsumer(QoS4, 5),
 
577
 
 
578
    Events   = ?EVENTS,
 
579
    Events5 = [?EVENT1, ?EVENT2, ?EVENT3, ?EVENT4, ?EVENT5],
 
580
 
 
581
    %% Initiate DB and 'NO_OF_EVENTS' events.
 
582
    Ref1  = cosNotification_eventDB:create_db(QoS_NO_OF_EVENTS, 60, 50, undefined),
 
583
    create_loop(Events, Ref1),
 
584
 
 
585
    %% Reduce the limit to 5 and extract all and see if it's ok.
 
586
    Ref2 = cosNotification_eventDB:update(Ref1, QoS_5_EVENTS),
 
587
    ?match({Events5, true}, cosNotification_eventDB:get_events(Ref2, ?NO_OF_EVENTS)),
 
588
 
 
589
    %% Add 'NO_OF_EVENTS' events. Since the only allow 5 events the DB will only 
 
590
    %% contain 5 events.
 
591
    create_loop(Events, Ref2),
 
592
    Ref3 = cosNotification_eventDB:update(Ref2, QoS_NO_OF_EVENTS),
 
593
 
 
594
    ?match({Events5, true}, cosNotification_eventDB:get_events(Ref3, ?NO_OF_EVENTS)),
 
595
    create_loop(Events, Ref3),
 
596
    ?match({Events, true}, cosNotification_eventDB:get_events(Ref3, ?NO_OF_EVENTS)),
 
597
    cosNotification_eventDB:destroy_db(Ref3),
 
598
    ok.
 
599
 
 
600
 
 
601
%%-----------------------------------------------------------------
 
602
%%  cosNotification_eventDB persisten events API tests 
 
603
%%-----------------------------------------------------------------
 
604
persisten_event_api(doc) -> ["The event DB is used to store events which cannot be", 
 
605
                             "delivered at once.", 
 
606
                             ""];
 
607
persisten_event_api(suite) -> [];
 
608
persisten_event_api(_Config) ->
 
609
 
 
610
    QoS1             = ?not_CreateInitQoS(),
 
611
    QoS2             = ?not_SetOrderPolicy(QoS1, ?not_FifoOrder),
 
612
    QoS3             = ?not_SetDiscardPolicy(QoS2, ?not_RejectNewEvents),
 
613
    QoS4             = ?not_SetStartTimeSupported(QoS3, false),
 
614
    QoS              = ?not_SetMaxEventsPerConsumer(QoS4, ?NO_OF_EVENTS),
 
615
 
 
616
    Event1   = ?EVENT1,
 
617
 
 
618
    Ref  = cosNotification_eventDB:create_db(QoS, 60, 50, undefined),
 
619
    %% Clean DB, should be empty
 
620
    ?match(0, cosNotification_eventDB:status(Ref, eventCounter)),
 
621
    cosNotification_eventDB:add_event(Ref, Event1),
 
622
    ?match(1, cosNotification_eventDB:status(Ref, eventCounter)),
 
623
    %% Get event without removing it. Should still be one event stored
 
624
    ?match({[Event1], _, _}, cosNotification_eventDB:get_events(Ref, 2, false)),
 
625
    ?match(1, cosNotification_eventDB:status(Ref, eventCounter)),
 
626
    {_, _, Keys} = 
 
627
        ?match({Event1, _, _}, cosNotification_eventDB:get_event(Ref, false)),
 
628
    ?match(1, cosNotification_eventDB:status(Ref, eventCounter)),
 
629
    %% Clear the events and check that the DB is empty.
 
630
    cosNotification_eventDB:delete_events(Keys),
 
631
    ?match(0, cosNotification_eventDB:status(Ref, eventCounter)),
 
632
    ?match({[], _, []}, cosNotification_eventDB:get_event(Ref, false)),
 
633
    ?match({[], _, []}, cosNotification_eventDB:get_events(Ref, 2, false)),
 
634
    
 
635
    cosNotification_eventDB:destroy_db(Ref),
 
636
    ok.
 
637
 
 
638
%%-----------------------------------------------------------------
 
639
%%  cosNotification_eventDB gc API tests 
 
640
%%-----------------------------------------------------------------
 
641
gc_api(doc) -> ["The event DB is used to store events which cannot be", 
 
642
                "delivered at once. If Deadline defined the events that", 
 
643
                "are older must be discarded.", 
 
644
                ""];
 
645
gc_api(suite) -> [];
 
646
gc_api(_Config) ->
 
647
 
 
648
    QoS1             = ?not_CreateInitQoS(),
 
649
    QoS2             = ?not_SetOrderPolicy(QoS1, ?not_FifoOrder),
 
650
    QoS3             = ?not_SetDiscardPolicy(QoS2, ?not_RejectNewEvents),
 
651
    QoS4             = ?not_SetStartTimeSupported(QoS3, false),
 
652
    QoS_NO_OF_EVENTS = ?not_SetMaxEventsPerConsumer(QoS4, ?NO_OF_EVENTS),
 
653
 
 
654
    Events   = ?EVENTS,
 
655
    Events6  = [?EVENT1, ?EVENT2, ?EVENT3, ?EVENT4, ?EVENT6, ?EVENT7, ?EVENT8],
 
656
    %% Initiate DB and 'NO_OF_EVENTS' events.
 
657
    Ref  = cosNotification_eventDB:create_db(QoS_NO_OF_EVENTS, 60, 50, undefined),
 
658
    create_loop(Events, Ref),
 
659
 
 
660
    %% Sleep so some events will get 'old'.
 
661
    timer:sleep(23000),
 
662
 
 
663
    %% Reduce the limit to 5 and extract all and see if it's ok.
 
664
    cosNotification_eventDB:gc_events(Ref, high),
 
665
 
 
666
    %% Since gc is done by another process we must wait so it will have a chance
 
667
    %% to complete the job.
 
668
    timer:sleep(2000),
 
669
 
 
670
    ?match({Events6, true}, cosNotification_eventDB:get_events(Ref, ?NO_OF_EVENTS)),
 
671
 
 
672
    create_loop(Events, Ref),
 
673
    timer:sleep(23000),
 
674
    ?match({Events6, true}, cosNotification_eventDB:get_events(Ref, ?NO_OF_EVENTS)),
 
675
    cosNotification_eventDB:destroy_db(Ref),
 
676
    ok.
 
677
 
 
678
 
 
679
%%-----------------------------------------------------------------
 
680
%%  cosNotification_eventDB gc API tests 
 
681
%%-----------------------------------------------------------------
 
682
auto_gc_api(doc) -> ["The event DB is used to store events which cannot be", 
 
683
                "delivered at once. If Deadline defined the events that", 
 
684
                "are older must be discarded.", 
 
685
                ""];
 
686
auto_gc_api(suite) -> [];
 
687
auto_gc_api(_Config) ->
 
688
 
 
689
    QoS1             = ?not_CreateInitQoS(),
 
690
    QoS2             = ?not_SetOrderPolicy(QoS1, ?not_FifoOrder),
 
691
    QoS3             = ?not_SetDiscardPolicy(QoS2, ?not_RejectNewEvents),
 
692
    QoS4             = ?not_SetStopTimeSupported(QoS3, true),
 
693
    QoS5             = ?not_SetStartTimeSupported(QoS4, false),
 
694
    QoS_NO_OF_EVENTS = ?not_SetMaxEventsPerConsumer(QoS5, ?NO_OF_EVENTS),
 
695
 
 
696
    Events6  = [?EVENT1, ?EVENT2, ?EVENT3, ?EVENT7, ?EVENT8, ?EVENT9],
 
697
    %% Initiate DB
 
698
    Ref  = cosNotification_eventDB:create_db(QoS_NO_OF_EVENTS, 50, 50, undefined),
 
699
    create_loop([?EVENT1, ?EVENT2, ?EVENT3, ?EVENT4, ?EVENT6], Ref),
 
700
 
 
701
    %% Sleep so some events will get 'old'.
 
702
    timer:sleep(60000),
 
703
    create_loop([?EVENT7, ?EVENT8, ?EVENT9], Ref),
 
704
 
 
705
    %% Since gc is done by another process we must wait so it will have a chance
 
706
    %% to complete the job.
 
707
    timer:sleep(2000),
 
708
 
 
709
    ?match({Events6, true}, cosNotification_eventDB:get_events(Ref, ?NO_OF_EVENTS)),
 
710
 
 
711
    cosNotification_eventDB:destroy_db(Ref),
 
712
 
 
713
    ok.
 
714
 
 
715
 
 
716
%%-----------------------------------------------------------------
 
717
%%  cosNotification_eventDB start- and stop-time API tests 
 
718
%%-----------------------------------------------------------------
 
719
start_stop_time_api(doc) -> ["The event DB is used to store events which cannot be", 
 
720
                "delivered at once. If Deadline defined the events that", 
 
721
                "are older must be discarded.", 
 
722
                ""];
 
723
start_stop_time_api(suite) -> [];
 
724
start_stop_time_api(_Config) ->
 
725
 
 
726
    QoS1             = ?not_CreateInitQoS(),
 
727
    QoS2             = ?not_SetOrderPolicy(QoS1, ?not_FifoOrder),
 
728
    QoS3             = ?not_SetDiscardPolicy(QoS2, ?not_RejectNewEvents),
 
729
    QoS4             = ?not_SetStopTimeSupported(QoS3, true),
 
730
    QoS5             = ?not_SetStartTimeSupported(QoS4, true),
 
731
    QoS_NO_OF_EVENTS = ?not_SetMaxEventsPerConsumer(QoS5, ?NO_OF_EVENTS),
 
732
 
 
733
    %% Initiate DB
 
734
    TimeService = cosTime:start_time_service(2, 0),
 
735
    Ref  = cosNotification_eventDB:create_db(QoS_NO_OF_EVENTS, 50, 50, TimeService),
 
736
 
 
737
    T1 = 'CosTime_UTO':'_get_utc_time'('CosTime_UTO':
 
738
                                       absolute_time('CosTime_TimeService':
 
739
                                                     new_universal_time(TimeService, 
 
740
                                                                        100000000, 0, 2))),
 
741
    T2 = 'CosTime_UTO':'_get_utc_time'('CosTime_UTO':
 
742
                                       absolute_time('CosTime_TimeService':
 
743
                                                     new_universal_time(TimeService, 
 
744
                                                                        200000000, 0, 2))),
 
745
    T3 = 'CosTime_UTO':'_get_utc_time'('CosTime_UTO':
 
746
                                       absolute_time('CosTime_TimeService':
 
747
                                                     new_universal_time(TimeService, 
 
748
                                                                        300000000, 0, 2))),
 
749
    T4 = 'CosTime_UTO':'_get_utc_time'('CosTime_UTO':
 
750
                                       absolute_time('CosTime_TimeService':
 
751
                                                     new_universal_time(TimeService, 
 
752
                                                                        400000000, 0, 2))),
 
753
    %% Delivered after 10 seconds discarded after 20.
 
754
    EVENT1 =  ?not_CreateSE("","event1","",
 
755
                            [#'CosNotification_Property'
 
756
                             {name="Priority", 
 
757
                              value=any:create(orber_tc:short(), 1)},
 
758
                             #'CosNotification_Property'
 
759
                             {name="StartTime", 
 
760
                              value=any:create('TimeBase_UtcT':tc(), T1)},
 
761
                             #'CosNotification_Property'
 
762
                             {name="StopTime", 
 
763
                              value=any:create('TimeBase_UtcT':tc(), T2)}],
 
764
                            [], any:create(orber_tc:null(), null)),
 
765
    
 
766
    %% Delivered after 30 seconds discarded after 10, i.e., always discarded.
 
767
    EVENT2 =  ?not_CreateSE("","event2","",
 
768
                            [#'CosNotification_Property'
 
769
                             {name="Priority", 
 
770
                              value=any:create(orber_tc:short(), 3)},
 
771
                             #'CosNotification_Property'
 
772
                             {name="StartTime", 
 
773
                                value=any:create('TimeBase_UtcT':tc(), T3)},
 
774
                               #'CosNotification_Property'
 
775
                               {name="StopTime", 
 
776
                                 value=any:create('TimeBase_UtcT':tc(), T1)}],
 
777
                              [], any:create(orber_tc:null(), null)),
 
778
    
 
779
    %% Delivered after 20 seconds discarded after 40
 
780
    EVENT3 = ?not_CreateSE("","event3","",
 
781
                           [#'CosNotification_Property'
 
782
                            {name="Priority", 
 
783
                             value=any:create(orber_tc:short(), 2)},
 
784
                            #'CosNotification_Property'
 
785
                            {name="StartTime", 
 
786
                             value=any:create('TimeBase_UtcT':tc(), T2)},
 
787
                            #'CosNotification_Property'
 
788
                            {name="StopTime", 
 
789
                             value=any:create('TimeBase_UtcT':tc(), T4)}],
 
790
                           [], any:create(orber_tc:null(), null)),
 
791
    
 
792
 
 
793
 
 
794
 
 
795
    create_loop([EVENT1, EVENT2, EVENT3], Ref),
 
796
 
 
797
    ?match({[], false}, cosNotification_eventDB:get_events(Ref, ?NO_OF_EVENTS)),
 
798
 
 
799
    %% Sleep so some events will get 'old'.
 
800
    timer:sleep(12000),
 
801
 
 
802
    ?match({[EVENT1], true}, cosNotification_eventDB:get_events(Ref, ?NO_OF_EVENTS)),
 
803
 
 
804
    ?match({[], false}, cosNotification_eventDB:get_events(Ref, ?NO_OF_EVENTS)),
 
805
 
 
806
    timer:sleep(10000),
 
807
 
 
808
    ?match({[EVENT3], true}, cosNotification_eventDB:get_events(Ref, ?NO_OF_EVENTS)),
 
809
 
 
810
    timer:sleep(20000),
 
811
 
 
812
    %% See if EVENT2 really have been discarded.
 
813
    ?match({[], false}, cosNotification_eventDB:get_events(Ref, ?NO_OF_EVENTS)),
 
814
 
 
815
    cosNotification_eventDB:destroy_db(Ref),
 
816
 
 
817
    cosTime:stop_time_service(TimeService),
 
818
 
 
819
    ok.
 
820
 
 
821
 
 
822
%%-----------------------------------------------------------------
 
823
%%  cosNotification_eventDB order API tests 
 
824
%%-----------------------------------------------------------------
 
825
reorder_api(doc) -> ["The event DB is used to store events which cannot be", 
 
826
                     "delivered at once. If the QoS is updated we must be", 
 
827
                     "able to change the ordering of events as the discard", 
 
828
                     "and order policies tells us.", 
 
829
                     ""];
 
830
reorder_api(suite) -> [];
 
831
reorder_api(_Config) ->
 
832
    %% We need to test switching between:
 
833
    %% * Priority -> Fifo
 
834
    %% * Priority -> Deadline
 
835
    %% * Fifo -> Priority 
 
836
    %% * Fifo -> Deadline
 
837
    %% * Deadline -> Priority 
 
838
    %% * Deadline -> Fifo
 
839
    QoS  = ?not_CreateInitQoS(),
 
840
    QoS2 = ?not_SetMaxEventsPerConsumer(QoS,100),
 
841
    QoS3 = ?not_SetPriority(QoS2, 10),
 
842
    QoS4 = ?not_SetStartTimeSupported(QoS3, false),
 
843
    QoS5 = ?not_SetOrderPolicy(QoS4, ?not_AnyOrder),
 
844
 
 
845
 
 
846
    %% Test all order policies using Any order discard policy.
 
847
    reorder_helper(?not_SetDiscardPolicy(QoS5, ?not_AnyOrder), "Discard Any"),
 
848
    reorder_helper(?not_SetDiscardPolicy(QoS5, ?not_PriorityOrder), "Discard Priority"),
 
849
    reorder_helper(?not_SetDiscardPolicy(QoS5, ?not_DeadlineOrder), "Discard Deadline"),
 
850
    reorder_helper(?not_SetDiscardPolicy(QoS5, ?not_FifoOrder), "Discard Fifo"),
 
851
    reorder_helper(?not_SetDiscardPolicy(QoS5, ?not_LifoOrder), "Discard Lifo"),
 
852
    reorder_helper(?not_SetDiscardPolicy(QoS5, ?not_RejectNewEvents), "Reject New Events"),
 
853
 
 
854
    ok.
 
855
 
 
856
 
 
857
reorder_helper(QoS, Txt) ->
 
858
    io:format("$$$$$$$$$$$$$$$$$$$$ ~s $$$$$$$$$$$$$$$$$$$~n", [Txt]),
 
859
    %% Create a DB with the above settings.
 
860
    Ref  = cosNotification_eventDB:create_db(QoS, 60, 50, undefined),
 
861
 
 
862
    Events        = ?EVENTS,
 
863
    PrioOrder     = ?PRIOORDER,
 
864
    FifoOrder     = ?FIFOORDER,
 
865
    DeadlineOrder = ?DEADLINEORDER,
 
866
 
 
867
    %% Test all order policies using Any order discard policy.
 
868
    Ref2 = do_reorder(Ref, Events, ?not_SetOrderPolicy(QoS, ?not_FifoOrder), 
 
869
                      FifoOrder, "Priority -> Fifo"),
 
870
    Ref3 = do_reorder(Ref2, Events, ?not_SetOrderPolicy(QoS, ?not_PriorityOrder), 
 
871
                      PrioOrder, "Fifo -> Priority"),
 
872
    Ref4 = do_reorder(Ref3, Events, ?not_SetOrderPolicy(QoS, ?not_DeadlineOrder), 
 
873
                      DeadlineOrder, "Priority -> Deadline"),
 
874
 
 
875
    Ref5 = do_reorder(Ref4, Events, ?not_SetOrderPolicy(QoS, ?not_PriorityOrder), 
 
876
                      PrioOrder, "Deadline -> Priority"),
 
877
 
 
878
    Ref6 = do_reorder(Ref5, Events, ?not_SetOrderPolicy(QoS, ?not_FifoOrder), 
 
879
                      FifoOrder, "Priority -> Fifo"),
 
880
 
 
881
    Ref7 = do_reorder(Ref6, Events, ?not_SetOrderPolicy(QoS, ?not_DeadlineOrder), 
 
882
                      DeadlineOrder, "Fifo -> Deadline"),
 
883
 
 
884
    Ref8 = do_reorder(Ref7, Events, ?not_SetOrderPolicy(QoS, ?not_FifoOrder), 
 
885
                      FifoOrder, "Deadline -> Fifo"),
 
886
    cosNotification_eventDB:destroy_db(Ref8),
 
887
    ok.
 
888
 
 
889
    
 
890
 
 
891
do_reorder(Ref, Events, QoS, Reply, Txt) ->
 
892
    create_loop(Events, Ref),
 
893
    io:format("################# ~s #################~n", [Txt]),
 
894
    NewRef = cosNotification_eventDB:update(Ref, QoS),
 
895
    ?match({Reply,_}, cosNotification_eventDB:get_events(NewRef, ?NO_OF_EVENTS)),
 
896
    NewRef.
 
897
 
 
898
%%-----------------------------------------------------------------
 
899
%% Internal functions
 
900
%%-----------------------------------------------------------------
 
901
%% This functions takes as argument a list of structured events.
 
902
create_loop([], _Ref) ->
 
903
    ok;
 
904
create_loop([H|T], Ref) ->
 
905
    catch cosNotification_eventDB:add_event(Ref, H),
 
906
    create_loop(T, Ref).
 
907
 
 
908
create_loop([], _Ref, _Life, _Prio) ->
 
909
    ok;
 
910
create_loop([H|T], Ref, Life, Prio) ->
 
911
    catch cosNotification_eventDB:add_event(Ref, H, Life, Prio),
 
912
    create_loop(T, Ref, Life, Prio).
 
913
 
 
914
%%-------------------- End of Module ------------------------------