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

« back to all changes in this revision

Viewing changes to lib/cosNotification/test/grammar_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    : grammar_SUITE.erl
 
23
%% Purpose : Testing the CosNotification BNF grammar.
 
24
%%--------------------------------------------------------------------
 
25
 
 
26
-module(grammar_SUITE).
 
27
 
 
28
 
 
29
 
 
30
%%--------------- INCLUDES -----------------------------------
 
31
-include_lib("orber/include/corba.hrl").
 
32
-include_lib("orber/include/ifr_types.hrl").
 
33
%% cosEvent files.
 
34
-include_lib("cosEvent/include/CosEventChannelAdmin.hrl").
 
35
%% Application files
 
36
-include_lib("cosNotification/include/CosNotification.hrl").
 
37
-include_lib("cosNotification/include/CosNotifyChannelAdmin.hrl").
 
38
-include_lib("cosNotification/include/CosNotifyComm.hrl").
 
39
-include_lib("cosNotification/include/CosNotifyFilter.hrl").
 
40
 
 
41
-include_lib("cosNotification/src/CosNotification_Definitions.hrl").
 
42
 
 
43
-include("idl_output/notify_test.hrl").
 
44
 
 
45
-include_lib("test_server/include/test_server.hrl").
 
46
 
 
47
%%--------------- DEFINES ------------------------------------
 
48
-define(default_timeout, ?t:minutes(20)).
 
49
-define(match(ExpectedRes, Expr),
 
50
        fun() ->
 
51
                AcTuAlReS = (catch (Expr)),
 
52
                case AcTuAlReS of
 
53
                    ExpectedRes ->
 
54
                        io:format("------ CORRECT RESULT ------~n~p~n",
 
55
                                  [AcTuAlReS]),
 
56
                        AcTuAlReS;
 
57
                    _ ->
 
58
                        io:format("###### ERROR ERROR ######~n~p~n",
 
59
                                  [AcTuAlReS]),
 
60
                        ?line exit(AcTuAlReS)
 
61
                end
 
62
        end()).
 
63
 
 
64
%%-----------------------------------------------------------------
 
65
%% External exports
 
66
%%-----------------------------------------------------------------
 
67
-export([all/0, suite/0,groups/0,init_per_group/2,end_per_group/2, 
 
68
         cases/0, init_per_suite/1, end_per_suite/1, 
 
69
         union_api/1, enum_api/1, simple_types_api/1,
 
70
         components_api/1, positional_api/1, variable_api/1,
 
71
         init_per_testcase/2, end_per_testcase/2]).
 
72
 
 
73
-import(cosNotification_Filter, [create_filter/1, eval/2]).
 
74
 
 
75
%%-----------------------------------------------------------------
 
76
%% Func: all/1
 
77
%% Args: 
 
78
%% Returns: 
 
79
%%-----------------------------------------------------------------
 
80
suite() -> [{ct_hooks,[ts_install_cth]}].
 
81
 
 
82
all() -> 
 
83
    cases().
 
84
 
 
85
groups() -> 
 
86
    [].
 
87
 
 
88
init_per_group(_GroupName, Config) ->
 
89
    Config.
 
90
 
 
91
end_per_group(_GroupName, Config) ->
 
92
    Config.
 
93
 
 
94
 
 
95
cases() -> 
 
96
    [variable_api, union_api, enum_api, simple_types_api,
 
97
     components_api, positional_api].
 
98
 
 
99
%%-----------------------------------------------------------------
 
100
%% Init and cleanup functions.
 
101
%%-----------------------------------------------------------------
 
102
 
 
103
init_per_testcase(_Case, Config) ->
 
104
    Path = code:which(?MODULE),
 
105
    code:add_pathz(filename:join(filename:dirname(Path), "idl_output")),
 
106
    ?line Dog=test_server:timetrap(?default_timeout),
 
107
    [{watchdog, Dog}|Config].
 
108
 
 
109
 
 
110
end_per_testcase(_Case, Config) ->
 
111
    Path = code:which(?MODULE),
 
112
    code:del_path(filename:join(filename:dirname(Path), "idl_output")),
 
113
    Dog = ?config(watchdog, Config),
 
114
    test_server:timetrap_cancel(Dog),
 
115
    ok.
 
116
 
 
117
init_per_suite(Config) ->
 
118
    Path = code:which(?MODULE),
 
119
    code:add_pathz(filename:join(filename:dirname(Path), "idl_output")),
 
120
    if
 
121
        is_list(Config) ->
 
122
            Config;
 
123
        true ->
 
124
            exit("Config not a list")
 
125
    end.
 
126
 
 
127
end_per_suite(Config) ->
 
128
    Path = code:which(?MODULE),
 
129
    code:del_path(filename:join(filename:dirname(Path), "idl_output")),
 
130
    Config.
 
131
 
 
132
 
 
133
%%-----------------------------------------------------------------
 
134
%%  simple types grammar tests
 
135
%%-----------------------------------------------------------------
 
136
simple_types_api(doc) -> ["CosNotification simple types grammar tests", ""];
 
137
simple_types_api(suite) -> [];
 
138
simple_types_api(_Config) ->
 
139
    %% Will always be true, no matter what kind of event we receive.
 
140
    {ok,T1}  = ?match({ok, _}, create_filter("2==2 and 3<4")),
 
141
    ?match(true, eval(T1, ?not_CreateSE("DomainName","TypeName","EventName",
 
142
                                        [],[], any:create(orber_tc:null(), null)))),
 
143
    
 
144
    %% Will always be true, no matter what kind of event we receive.
 
145
    {ok,T2}  = ?match({ok, _}, create_filter("")),
 
146
    ?match(true, eval(T2, ?not_CreateSE("DomainName","TypeName","EventName",
 
147
                                        [],[], any:create(orber_tc:null(), null)))),
 
148
 
 
149
    %% Check if $variable works
 
150
    {ok,T3}  = ?match({ok, _}, create_filter("$city == \'Berlin\'")),
 
151
    ?match(true, eval(T3, ?not_CreateSE("DomainName","TypeName","EventName",
 
152
                                        [#'CosNotification_Property'{name="city", 
 
153
                                                                     value=any:create(orber_tc:string(0), "Berlin")}],
 
154
                                        [], any:create(orber_tc:null(), null)))),
 
155
    ?match(false, eval(T3, ?not_CreateSE("DomainName","TypeName", "EventName",
 
156
                                         [#'CosNotification_Property'{name="city", 
 
157
                                                                      value=any:create(orber_tc:string(0), "Dallas")}],
 
158
                                         
 
159
                                        [], any:create(orber_tc:null(), null)))),
 
160
    
 
161
    
 
162
    {ok,T4}  = ?match({ok, _}, create_filter("$zip == 44")),
 
163
    ?match(true, eval(T4, ?not_CreateSE("DomainName","TypeName", "EventName",
 
164
                                        [#'CosNotification_Property'{name="zip", 
 
165
                                                                     value=any:create(orber_tc:short(), 44)}],
 
166
                                        
 
167
                                        [], any:create(orber_tc:null(), null)))),
 
168
    ?match(true, eval(T4, ?not_CreateSE("DomainName","TypeName", "EventName",
 
169
                                        [],[], 
 
170
                                        any:create('CosNotification_Property':tc(), 
 
171
                                                   #'CosNotification_Property'
 
172
                                                   {name="zip", 
 
173
                                                    value=any:create(orber_tc:short(), 
 
174
                                                                     44)})))),
 
175
    ?match(false, eval(T4, ?not_CreateSE("DomainName","TypeName", "EventName",
 
176
                                         [#'CosNotification_Property'{name="zip", 
 
177
                                                                      value=any:create(orber_tc:short(), 33)}],
 
178
                                         
 
179
                                        [], any:create(orber_tc:null(), null)))),
 
180
    
 
181
    %% Will always be true, no matter what kind of event we receive.
 
182
    {ok,T5}  = ?match({ok, _}, create_filter("\'oo'\~\'foobar\'")),
 
183
    ?match(true, eval(T5, ?not_CreateSE("DomainName","TypeName","EventName",
 
184
                                        [],[], any:create(orber_tc:null(), null)))),
 
185
    %% Will always be false, no matter what kind of event we receive.
 
186
    {ok,T6} = ?match({ok, _}, create_filter("\'o1'\~\'foobar\'")),
 
187
    ?match(false, eval(T6, ?not_CreateSE("DomainName","TypeName","EventName",
 
188
                                         [],[], any:create(orber_tc:null(), null)))),
 
189
 
 
190
    %% Can we apply the ~ operation as above using a variable
 
191
    {ok,T7} = ?match({ok, _}, create_filter("$str~\'foobar\'")),
 
192
    ?match(true, eval(T7, ?not_CreateSE("DomainName","TypeName","EventName",
 
193
                                        [#'CosNotification_Property'{name="str", 
 
194
                                                                     value=any:create(orber_tc:string(0), "oo")}],
 
195
                                        [], any:create(orber_tc:null(), null)))),
 
196
    ?match(false, eval(T7, ?not_CreateSE("DomainName","TypeName","EventName",
 
197
                                         [#'CosNotification_Property'{name="str", 
 
198
                                                                      value=any:create(orber_tc:string(0), "ok")}],
 
199
                                         [], any:create(orber_tc:null(), null)))),
 
200
    
 
201
    
 
202
 
 
203
    {ok,_T8} = ?match({ok, _}, create_filter("$\\zip == 44444")),
 
204
 
 
205
    ok.
 
206
 
 
207
%%-----------------------------------------------------------------
 
208
%%  enum grammar tests
 
209
%%-----------------------------------------------------------------
 
210
enum_api(doc) -> ["CosNotification enum grammar tests", ""];
 
211
enum_api(suite) -> [];
 
212
enum_api(_Config) ->
 
213
    %% Accept events whose 'in' enum is set to the value 'HOUSE' or 'CAR'. 
 
214
    {ok,T1} = ?match({ok, _}, create_filter("$.\\in == HOUSE or $.\\in == CAR")),
 
215
 
 
216
    ?match(true, eval(T1, any:create(orber_tc:alias("IFRId","in",tk_any),
 
217
                                     any:create({tk_enum, "IFRId", "in", ["HOUSE", "CAR"]},
 
218
                                                'HOUSE')))),
 
219
    ?match(false, eval(T1, any:create(orber_tc:alias("IFRId","in",tk_any),
 
220
                                      any:create({tk_enum, "IFRId", "in", ["HOUSE", "CAR"]},
 
221
                                                 'GARAGE')))),
 
222
    ok.
 
223
    
 
224
 
 
225
%%-----------------------------------------------------------------
 
226
%%  Union grammar tests
 
227
%%-----------------------------------------------------------------
 
228
union_api(doc) -> ["CosNotification union grammar tests", ""];
 
229
union_api(suite) -> [];
 
230
union_api(_Config) ->
 
231
    {ok,T1} = ?match({ok, _}, create_filter("exist $.uni1._d and $.uni1._d == 1 and $.uni1.(1) == 10")),
 
232
    {ok,T2} = ?match({ok, _}, create_filter("default $.uni1._d and $.uni1.() == 10")),
 
233
    {ok,T3} = ?match({ok, _}, create_filter("default $.uni1._d and $.uni1.(999) == 10")),
 
234
    ?match(true, eval(T1, ?not_CreateSE("DomainName","CommunicationsAlarm",
 
235
                                        "EventName",[],[],
 
236
                                        any:create(orber_tc:alias("IDL:notify_test/namedAny:1.0",
 
237
                                                                  "uni1",
 
238
                                                                  tk_any),
 
239
                                                    any:create(notify_test_uni1:tc(),
 
240
                                                               #notify_test_uni1{label= 1, 
 
241
                                                                                 value=10}))))),
 
242
    ?match(true, eval(T2, ?not_CreateSE("DomainName","CommunicationsAlarm",
 
243
                                        "EventName",[],[],
 
244
                                        any:create(orber_tc:alias("IDL:notify_test/namedAny:1.0",
 
245
                                                                   "uni1",
 
246
                                                                  tk_any),
 
247
                                                    any:create(notify_test_uni1:tc(),
 
248
                                                               #notify_test_uni1{label= 100, 
 
249
                                                                                 value=10}))))),
 
250
    ?match(true, eval(T3, ?not_CreateSE("DomainName","CommunicationsAlarm",
 
251
                                        "EventName",[],[],
 
252
                                        any:create(orber_tc:alias("IDL:notify_test/namedAny:1.0",
 
253
                                                                  "uni1",
 
254
                                                                  tk_any),
 
255
                                                    any:create(notify_test_uni1:tc(),
 
256
                                                               #notify_test_uni1{label= 100, 
 
257
                                                                                 value=10}))))),
 
258
    ?match(true, eval(T1, any:create(orber_tc:alias("IDL:notify_test/namedAny:1.0",
 
259
                                                    "uni1",
 
260
                                                    tk_any),
 
261
                                     any:create(notify_test_uni1:tc(),
 
262
                                                #notify_test_uni1{label= 1, 
 
263
                                                                   value=10})))),
 
264
    ?match(false, eval(T2, any:create(orber_tc:alias("IDL:notify_test/namedAny:1.0",
 
265
                                                     "uni1",
 
266
                                                     tk_any),
 
267
                                      any:create(notify_test_uni1:tc(),
 
268
                                                 #notify_test_uni1{label= 1, 
 
269
                                                                   value=10})))),
 
270
    ?match(false, eval(T3, any:create(orber_tc:alias("IDL:notify_test/namedAny:1.0",
 
271
                                                     "uni1",
 
272
                                                     tk_any),
 
273
                                      any:create(notify_test_uni1:tc(),
 
274
                                                 #notify_test_uni1{label= 1, 
 
275
                                                                   value=10})))),
 
276
    ?match(true, eval(T1, ?not_CreateSE("DomainName","CommunicationsAlarm",
 
277
                                        "EventName",[],[],
 
278
                                        any:create(notify_test_studies:tc(), #notify_test_studies
 
279
                                                    {uni1 = #notify_test_uni1{label= 1, value=10},
 
280
                                                     gpa = 90,
 
281
                                                     tests = [#'CosNotification_Property'
 
282
                                                              {name="midterm", value=any:create(orber_tc:short(), 70)},
 
283
                                                              #'CosNotification_Property'
 
284
                                                              {name="final", value=any:create(orber_tc:short(), 60)}],
 
285
                                                     monthly_attendance = {0,1,2,10}})))),
 
286
    ?match(false, eval(T2, ?not_CreateSE("DomainName","CommunicationsAlarm",
 
287
                                         "EventName",[],[],
 
288
                                         any:create(notify_test_studies:tc(), #notify_test_studies
 
289
                                                    {uni1 = #notify_test_uni1{label= 1, value=10},
 
290
                                                     gpa = 90,
 
291
                                                     tests = [#'CosNotification_Property'
 
292
                                                              {name="midterm", value=any:create(orber_tc:short(), 70)},
 
293
                                                              #'CosNotification_Property'
 
294
                                                              {name="final", value=any:create(orber_tc:short(), 60)}],
 
295
                                                     monthly_attendance = {0,1,2,10}})))),
 
296
    ?match(false, eval(T3, ?not_CreateSE("DomainName","CommunicationsAlarm",
 
297
                                         "EventName",[],[],
 
298
                                         any:create(notify_test_studies:tc(), #notify_test_studies
 
299
                                                    {uni1 = #notify_test_uni1{label= 1, value=10},
 
300
                                                     gpa = 90,
 
301
                                                     tests = [#'CosNotification_Property'
 
302
                                                              {name="midterm", value=any:create(orber_tc:short(), 70)},
 
303
                                                              #'CosNotification_Property'
 
304
                                                              {name="final", value=any:create(orber_tc:short(), 60)}],
 
305
                                                     monthly_attendance = {0,1,2,10}})))),
 
306
    ?match(true, eval(T1, any:create(notify_test_studies:tc(), #notify_test_studies
 
307
                                     {uni1 = #notify_test_uni1{label= 1, value=10},
 
308
                                      gpa = 90,
 
309
                                      tests = [#'CosNotification_Property'
 
310
                                               {name="midterm", value=any:create(orber_tc:short(), 70)},
 
311
                                               #'CosNotification_Property'
 
312
                                               {name="final", value=any:create(orber_tc:short(), 60)}],
 
313
                                      monthly_attendance = {0,1,2,10}}))),
 
314
    ?match(false, eval(T2, any:create(notify_test_studies:tc(), #notify_test_studies
 
315
                                      {uni1 = #notify_test_uni1{label= 1, value=10},
 
316
                                       gpa = 90,
 
317
                                       tests = [#'CosNotification_Property'
 
318
                                                {name="midterm", value=any:create(orber_tc:short(), 70)},
 
319
                                                #'CosNotification_Property'
 
320
                                                {name="final", value=any:create(orber_tc:short(), 60)}],
 
321
                                       monthly_attendance = {0,1,2,10}}))),
 
322
    ?match(false, eval(T3, any:create(notify_test_studies:tc(), #notify_test_studies
 
323
                                      {uni1 = #notify_test_uni1{label= 1, value=10},
 
324
                                       gpa = 90,
 
325
                                       tests = [#'CosNotification_Property'
 
326
                                                {name="midterm", value=any:create(orber_tc:short(), 70)},
 
327
                                                #'CosNotification_Property'
 
328
                                                {name="final", value=any:create(orber_tc:short(), 60)}],
 
329
                                       monthly_attendance = {0,1,2,10}}))),
 
330
    
 
331
    {ok,T4} = ?match({ok, _}, create_filter("exist $.alias.uni1._d and $.alias.uni1._d == 1 and $.alias.uni1.(1) == 10")),
 
332
    ?match(true, eval(T4, ?not_CreateSE("DomainName","CommunicationsAlarm",
 
333
                                        "EventName",[],[],
 
334
                                        any:create(orber_tc:alias(notify_test_studies:id(),
 
335
                                                                  "alias",
 
336
                                                                  notify_test_studies:tc()), 
 
337
                                                   #notify_test_studies
 
338
                                                   {uni1 = #notify_test_uni1{label= 1, value=10},
 
339
                                                    gpa = 90, tests = [],
 
340
                                                    monthly_attendance = {0,1,2,10}})))),
 
341
    ?match(true, eval(T4, any:create(orber_tc:alias(notify_test_studies:id(),
 
342
                                                    "alias",
 
343
                                                    notify_test_studies:tc()), 
 
344
                                     #notify_test_studies
 
345
                                     {uni1 = #notify_test_uni1{label= 1, value=10},
 
346
                                      gpa = 90, tests = [],
 
347
                                      monthly_attendance = {0,1,2,10}}))),
 
348
    %% Accept events with a default union discriminator set to the value 2. 
 
349
    {ok,T5} = ?match({ok, _}, create_filter("default $._d and $.defvalue == 2")),
 
350
    ?match(true, eval(T5, any:create(notify_test_uni1:tc(), 
 
351
                                     #notify_test_uni1{label= 100, value=2}))),
 
352
    %% label not default.
 
353
    ?match(false, eval(T5, any:create(notify_test_uni1:tc(), 
 
354
                                      #notify_test_uni1{label= 2, value=2}))),
 
355
    %% Default does not exist (nor the component defvalue)
 
356
    ?match(false, eval(T5, any:create(notify_test_uni2:tc(), 
 
357
                                      #notify_test_uni2{label= 100, value=2}))),
 
358
    %% Both wrong
 
359
    ?match(false, eval(T5, any:create(notify_test_uni2:tc(), 
 
360
                                      #notify_test_uni2{label= 2, value=2}))),
 
361
   
 
362
    {ok,T6} = ?match({ok, _}, create_filter("default $._d and $.(-8) == 2")),
 
363
    ?match(true, eval(T6, any:create(notify_test_uni1:tc(), 
 
364
                                     #notify_test_uni1{label= 100, value=2}))),
 
365
    %% label not default.
 
366
    ?match(false, eval(T6, any:create(notify_test_uni1:tc(), 
 
367
                                      #notify_test_uni1{label= 2, value=2}))),
 
368
    %% Default does not exist (nor the component defvalue)
 
369
    ?match(false, eval(T6, any:create(notify_test_uni2:tc(), 
 
370
                                      #notify_test_uni2{label= 100, value=2}))),
 
371
    %% Both wrong
 
372
    ?match(false, eval(T6, any:create(notify_test_uni2:tc(), 
 
373
                                      #notify_test_uni2{label= 2, value=2}))),
 
374
    %% the same as the above, but we try to access a label that is not default
 
375
    {ok,T7} = ?match({ok, _}, create_filter("default $._d and $.(2) == 2")),
 
376
    ?match({error, _}, eval(T7, any:create(notify_test_uni1:tc(), 
 
377
                                           #notify_test_uni1{label= 100, value=2}))),
 
378
 
 
379
    %% Must be a default-union with its 'defvalue' set to 2.
 
380
    {ok,T8} = ?match({ok, _}, create_filter("default $._d and $.('defvalue') == 2")),
 
381
    ?match(true, eval(T8, any:create(notify_test_uni1:tc(), 
 
382
                                     #notify_test_uni1{label= 100, value=2}))),
 
383
    %% label not default.
 
384
    ?match(false, eval(T8, any:create(notify_test_uni1:tc(), 
 
385
                                      #notify_test_uni1{label= 2, value=2}))),
 
386
    %% Default does not exist (nor the component defvalue)
 
387
    ?match(false, eval(T8, any:create(notify_test_uni2:tc(), 
 
388
                                      #notify_test_uni2{label= 100, value=2}))),
 
389
    %% Both wrong
 
390
    ?match(false, eval(T8, any:create(notify_test_uni2:tc(), 
 
391
                                      #notify_test_uni2{label= 2, value=2}))),
 
392
 
 
393
    %% Must be a default-union with its value set to 2.
 
394
    {ok,T9} = ?match({ok, _}, create_filter("default $._d and $.(+100) == 2")),
 
395
    ?match(true, eval(T9, any:create(notify_test_uni1:tc(), 
 
396
                                     #notify_test_uni1{label= 100, value=2}))),
 
397
    %% label not default.
 
398
    ?match(false, eval(T9, any:create(notify_test_uni1:tc(), 
 
399
                                      #notify_test_uni1{label= 2, value=2}))),
 
400
    %% Default does not exist (nor the component defvalue)
 
401
    ?match(false, eval(T9, any:create(notify_test_uni2:tc(), 
 
402
                                      #notify_test_uni2{label= 100, value=2}))),
 
403
    %% Both wrong
 
404
    ?match(false, eval(T9, any:create(notify_test_uni2:tc(), 
 
405
                                      #notify_test_uni2{label= 2, value=2}))),
 
406
 
 
407
    %% So far, we have only tested to access the union itself. No will use more
 
408
    %% complex union members.
 
409
    %% T10 and T11 is "equal"
 
410
    {ok,T10} = ?match({ok, _}, create_filter("$.M < 54")),
 
411
    {ok,T11} = ?match({ok, _}, create_filter("$.(5) < 54")),
 
412
    ?match(false, eval(T10, any:create(notify_test_K:tc(), 
 
413
                                       #notify_test_K{label= 5, value=54}))),
 
414
    ?match(false, eval(T11, any:create(notify_test_K:tc(), 
 
415
                                       #notify_test_K{label= 5, value=54}))),
 
416
    ?match(true, eval(T10, any:create(notify_test_K:tc(), 
 
417
                                      #notify_test_K{label= 5, value=50}))),
 
418
    ?match(true, eval(T11, any:create(notify_test_K:tc(), 
 
419
                                      #notify_test_K{label= 5, value=50}))),
 
420
    ?match({error,_}, eval(T10, any:create(notify_test_K:tc(), 
 
421
                                           #notify_test_K{label= -1, value=50}))),
 
422
    ?match({error,_}, eval(T11, any:create(notify_test_K:tc(), 
 
423
                                           #notify_test_K{label= -1, value=50}))),
 
424
    
 
425
    %% T12 and T13 is "equal"
 
426
    {ok,T12} = ?match({ok, _}, create_filter("$.L.C < 128")),
 
427
    {ok,T13} = ?match({ok, _}, create_filter("$.(3).2 < 128")),
 
428
    ?match(true, eval(T12, any:create(notify_test_K:tc(), 
 
429
                                      #notify_test_K{label= 3, value=
 
430
                                                     #notify_test_X{'A' = 1,
 
431
                                                                    'B' = "string",
 
432
                                                                    'C' = 120}}))),
 
433
    ?match(true, eval(T13, any:create(notify_test_K:tc(), 
 
434
                                      #notify_test_K{label= 3, value=
 
435
                                                     #notify_test_X{'A' = 1,
 
436
                                                                    'B' = "string",
 
437
                                                                    'C' = 120}}))),
 
438
    ?match(false, eval(T12, any:create(notify_test_K:tc(), 
 
439
                                      #notify_test_K{label= 3, value=
 
440
                                                     #notify_test_X{'A' = 1,
 
441
                                                                    'B' = "string",
 
442
                                                                    'C' = 200}}))),
 
443
    ?match(false, eval(T13, any:create(notify_test_K:tc(), 
 
444
                                      #notify_test_K{label= 3, value=
 
445
                                                     #notify_test_X{'A' = 1,
 
446
                                                                    'B' = "string",
 
447
                                                                    'C' = 200}}))),
 
448
 
 
449
    %% Test if 'putty' is a substring of K
 
450
    {ok,T15} = ?match({ok, _}, create_filter("'putty' ~ $.(2)")),
 
451
    {ok,T16} = ?match({ok, _}, create_filter("'putty' ~ $.K")),
 
452
    ?match(true, eval(T15, any:create(notify_test_K:tc(), 
 
453
                                      #notify_test_K{label= 2, value= "isputtyok"}))),
 
454
    ?match(true, eval(T16, any:create(notify_test_K:tc(), 
 
455
                                      #notify_test_K{label= 2, value= "isputtyok"}))),
 
456
    ?match(false, eval(T15, any:create(notify_test_K:tc(), 
 
457
                                       #notify_test_K{label= 2, value= "notputtok"}))),
 
458
    ?match(false, eval(T16, any:create(notify_test_K:tc(), 
 
459
                                       #notify_test_K{label= 2, value= "notputtok"}))),
 
460
    
 
461
    {ok,_T17} = ?match({ok, _}, create_filter("'putty' ~ $.(3).1")),
 
462
    {ok,_T18} = ?match({ok, _}, create_filter("'putty' ~ $.L.B")),
 
463
    ?match(true, eval(T12, any:create(notify_test_K:tc(), 
 
464
                                      #notify_test_K{label= 3, value=
 
465
                                                     #notify_test_X{'A' = 1,
 
466
                                                                    'B' = "isputtyok",
 
467
                                                                    'C' = 120}}))),
 
468
    ?match(true, eval(T13, any:create(notify_test_K:tc(), 
 
469
                                      #notify_test_K{label= 3, value=
 
470
                                                     #notify_test_X{'A' = 1,
 
471
                                                                    'B' = "isputtyok",
 
472
                                                                    'C' = 120}}))),
 
473
    ?match(false, eval(T12, any:create(notify_test_K:tc(), 
 
474
                                      #notify_test_K{label= 3, value=
 
475
                                                     #notify_test_X{'A' = 1,
 
476
                                                                    'B' = "notputtok",
 
477
                                                                    'C' = 200}}))),
 
478
    ?match(false, eval(T13, any:create(notify_test_K:tc(), 
 
479
                                      #notify_test_K{label= 3, value=
 
480
                                                     #notify_test_X{'A' = 1,
 
481
                                                                    'B' = "notputtok",
 
482
                                                                    'C' = 200}}))),
 
483
 
 
484
    %% Please observe that the switch 0 and 2 is defined to be equivalent.
 
485
    {ok,T19} = ?match({ok, _}, create_filter("$._d == 2 and $.(0) != 'hoob'")),
 
486
    {ok,T20} = ?match({ok, _}, create_filter("$._d == 2 and $.(2) != 'hoob'")),
 
487
    ?match(true, eval(T19, any:create(notify_test_K:tc(), 
 
488
                                      #notify_test_K{label= 2, value= "nothoob"}))),
 
489
    ?match(true, eval(T20, any:create(notify_test_K:tc(), 
 
490
                                      #notify_test_K{label= 2, value= "nothoob"}))),
 
491
    ?match(false, eval(T19, any:create(notify_test_K:tc(), 
 
492
                                       #notify_test_K{label= 2, value= "hoob"}))),
 
493
    ?match(false, eval(T20, any:create(notify_test_K:tc(), 
 
494
                                       #notify_test_K{label= 2, value= "hoob"}))),
 
495
 
 
496
    ?match(false, eval(T19, any:create(notify_test_K:tc(), 
 
497
                                       #notify_test_K{label= 5, value= 55}))),
 
498
    ?match(false, eval(T20, any:create(notify_test_K:tc(), 
 
499
                                       #notify_test_K{label= 5, value= 55}))),
 
500
 
 
501
    ?match(false, eval(T19, any:create(notify_test_K:tc(), 
 
502
                                       #notify_test_K{label= 100, value= "nothoob"}))),
 
503
    ?match(false, eval(T20, any:create(notify_test_K:tc(), 
 
504
                                       #notify_test_K{label= 100, value= "nothoob"}))),
 
505
 
 
506
    {ok,T21} = ?match({ok, _}, create_filter("exist $.K")),
 
507
    {ok,T22} = ?match({ok, _}, create_filter("exist $.(0) or exist $.(2)")),
 
508
    ?match(true, eval(T21, any:create(notify_test_K:tc(), 
 
509
                                      #notify_test_K{label= 0, value= "hoob"}))),
 
510
    ?match(true, eval(T22, any:create(notify_test_K:tc(), 
 
511
                                      #notify_test_K{label= 0, value= "hoob"}))),
 
512
    ?match(true, eval(T21, any:create(notify_test_K:tc(), 
 
513
                                      #notify_test_K{label= 2, value= "hoob"}))),
 
514
    ?match(true, eval(T22, any:create(notify_test_K:tc(), 
 
515
                                      #notify_test_K{label= 2, value= "hoob"}))),
 
516
    ?match(false, eval(T21, any:create(notify_test_K:tc(), 
 
517
                                       #notify_test_K{label= 5, value= 55}))),
 
518
    ?match(false, eval(T22, any:create(notify_test_K:tc(), 
 
519
                                       #notify_test_K{label= 5, value= 55}))),
 
520
 
 
521
 
 
522
    %% Please observe that the switch 0 and 2 is defined to be equivalent.
 
523
    {ok,T23} = ?match({ok, _}, create_filter("exist $.(2)")),
 
524
    {ok,T24} = ?match({ok, _}, create_filter("exist $.(0)")),
 
525
    ?match(true, eval(T23, any:create(notify_test_K:tc(), 
 
526
                                      #notify_test_K{label= 2, value= "hoob"}))),
 
527
    ?match(false, eval(T24, any:create(notify_test_K:tc(), 
 
528
                                       #notify_test_K{label= 2, value= "hoob"}))),
 
529
    ?match(false, eval(T23, any:create(notify_test_K:tc(), 
 
530
                                       #notify_test_K{label= 0, value= "hoob"}))),
 
531
    ?match(true, eval(T24, any:create(notify_test_K:tc(), 
 
532
                                      #notify_test_K{label= 0, value= "hoob"}))),
 
533
    ?match(false, eval(T23, any:create(notify_test_K:tc(), 
 
534
                                       #notify_test_K{label= 5, value= 55}))),
 
535
    ?match(false, eval(T24, any:create(notify_test_K:tc(), 
 
536
                                       #notify_test_K{label= 5, value= 55}))),
 
537
 
 
538
    ok.
 
539
 
 
540
%%-----------------------------------------------------------------
 
541
%%  Variables grammar tests
 
542
%%-----------------------------------------------------------------
 
543
variable_api(doc) -> ["CosNotification variables grammar tests", ""];
 
544
variable_api(suite) -> [];
 
545
variable_api(_Config) ->
 
546
    %% Accept all "CommunicationsAlarm" events 
 
547
    {ok,T0} = ?match({ok, _}, create_filter("$type_name == 'CommunicationsAlarm'")),
 
548
 
 
549
    ?match(true, eval(T0, ?not_CreateSE("DomainName","CommunicationsAlarm",
 
550
                                        "EventName",[],[],
 
551
                                        any:create(orber_tc:null(), null)))),
 
552
    ?match(false, eval(T0, ?not_CreateSE("DomainName","CommunicationsOK",
 
553
                                         "EventName", [],[],
 
554
                                         any:create(orber_tc:null(), null)))),
 
555
    ?match(true, eval(T0, ?not_CreateSE("DomainName","CommunicationsAlarm",
 
556
                                        "EventName", [],[],
 
557
                                        any:create(orber_tc:alias("IFRId", "type_name",
 
558
                                                    orber_tc:string(0)),
 
559
                                                    "CommunicationsOK")))),
 
560
 
 
561
    ?match(true, eval(T0, any:create(orber_tc:alias("IFRId", "type_name",
 
562
                                                    orber_tc:string(0)),
 
563
                                                    "CommunicationsAlarm"))), 
 
564
    ?match(false, eval(T0, any:create(orber_tc:alias("IFRId", "type_name",
 
565
                                                    orber_tc:string(0)),
 
566
                                                    "CommunicationsOK"))), 
 
567
 
 
568
 
 
569
    %% Accept all "CommunicationsAlarm" events but no "lost_packet" messages. 
 
570
    {ok,T1} = ?match({ok, _}, create_filter("$type_name == 'CommunicationsAlarm' and not ($event_name == 'lost_packet')")),
 
571
 
 
572
    ?match(true, eval(T1, ?not_CreateSE("DomainName","CommunicationsAlarm",
 
573
                                        "EventName",[],[],
 
574
                                        any:create(orber_tc:null(), null)))),
 
575
    ?match(false, eval(T1, ?not_CreateSE("DomainName","CommunicationsAlarm",
 
576
                                         "lost_packet", [],[],
 
577
                                         any:create(orber_tc:null(), null)))),
 
578
    ?match(true, 
 
579
           eval(T1, any:create(orber_tc:sequence('CosNotification_Property':tc(),0),
 
580
                               [#'CosNotification_Property'{name="type_name",
 
581
                                            value=any:create(orber_tc:string(0), "CommunicationsAlarm")},
 
582
                                #'CosNotification_Property'{name="event_name",
 
583
                                            value=any:create(orber_tc:string(0), "EventName")}]))),
 
584
    ?match(false, 
 
585
           eval(T1, any:create(orber_tc:sequence('CosNotification_Property':tc(),0),
 
586
                               [#'CosNotification_Property'{name="type_name",
 
587
                                            value=any:create(orber_tc:string(0), "CommunicationsAlarm")},
 
588
                                #'CosNotification_Property'{name="event_name",
 
589
                                            value=any:create(orber_tc:string(0), "lost_packet")}]))),
 
590
 
 
591
 
 
592
    %% Accept "CommunicationsAlarm" events with priorities ranging from 1 to 5. 
 
593
    {ok,T2} = ?match({ok, _}, create_filter("$type_name == 'CommunicationsAlarm' and $priority >= 1 and $priority <= 5")),
 
594
    ?match(true, eval(T2, ?not_CreateSE("DomainName","CommunicationsAlarm",
 
595
                                        "EventName", 
 
596
                                        [#'CosNotification_Property'{name="priority", 
 
597
                                                                     value=any:create(orber_tc:short(), 2)}],
 
598
                                        [], any:create(orber_tc:null(), null)))),
 
599
    ?match(false, eval(T2, ?not_CreateSE("DomainName","CommunicationsAlarm",
 
600
                                         "EventName", 
 
601
                                         [#'CosNotification_Property'{name="priority", 
 
602
                                                                      value=any:create(orber_tc:short(), 20)}],
 
603
                                         [], any:create(orber_tc:null(), null)))),
 
604
    
 
605
    %% Select "MOVIE" events featuring at least 3 of the Marx Brothers. 
 
606
    {ok,T3} = ?match({ok, _}, create_filter("$type_name == 'MOVIE' and (('groucho' in $starlist) + ('chico' in $starlist) + ('harpo' in $starlist) + ('zeppo' in $starlist) + ('gummo' in $starlist)) > 2")),
 
607
    ?match(true, eval(T3, ?not_CreateSE("DomainName","MOVIE",
 
608
                                        "EventName", 
 
609
                                        [#'CosNotification_Property'{name="starlist", 
 
610
                                                                     value=any:create(orber_tc:sequence(orber_tc:string(0),0),
 
611
                                                                                      ["groucho", "harpo", "sam", "gummo"])}],
 
612
                                        [], any:create(orber_tc:null(), null)))),
 
613
    ?match(false, eval(T3, ?not_CreateSE("DomainName","MOVIE",
 
614
                                         "EventName", 
 
615
                                         [#'CosNotification_Property'{name="starlist", 
 
616
                                                                      value=any:create(orber_tc:sequence(orber_tc:string(0),0),
 
617
                                                                                       ["frodo", "bilbo", "sam", "gummo"])}],
 
618
                                         [], any:create(orber_tc:null(), null)))),
 
619
    %% Accept students that took all 3 tests and had an average score of at least 80%. 
 
620
    {ok,T4} = ?match({ok, _}, create_filter("$test._length == 3 and ($test[0].score + $test[1].score + $test[2].score)/3 >=80")),
 
621
    ?match(true, eval(T4, ?not_CreateSE("DomainName","TypeName",
 
622
                                        "EventName", [],
 
623
                                        [#'CosNotification_Property'{name="test", 
 
624
                                                                     value=any:create(orber_tc:array(notify_test_data:tc(),0),
 
625
                                                                                      {#notify_test_data{score=75},
 
626
                                                                                       #notify_test_data{score=80},
 
627
                                                                                       #notify_test_data{score=85}})}],
 
628
                                        any:create(orber_tc:null(), null)))),
 
629
    ?match(false, eval(T4, ?not_CreateSE("DomainName","TypeName",
 
630
                                         "EventName", [],
 
631
                                         [#'CosNotification_Property'{name="test", 
 
632
                                                                      value=any:create(orber_tc:array(notify_test_data:tc(),0),
 
633
                                                                                       {#notify_test_data{score=75},
 
634
                                                                                        #notify_test_data{score=80},
 
635
                                                                                        #notify_test_data{score=80}})}],
 
636
                                         any:create(orber_tc:null(), null)))),
 
637
    ?match(false, eval(T4, ?not_CreateSE("DomainName","TypeName",
 
638
                                         "EventName", [],
 
639
                                         [#'CosNotification_Property'{name="test", 
 
640
                                                                      value=any:create(orber_tc:array(notify_test_data:tc(),0),
 
641
                                                                                       {#notify_test_data{score=75},
 
642
                                                                                        #notify_test_data{score=85}})}],
 
643
                                         any:create(orber_tc:null(), null)))),
 
644
    %% Select processes that exceed a certain usage threshold. 
 
645
    {ok,T5} = ?match({ok, _}, create_filter("$memsize / 5.5 + $cputime * 1275.0 + $filesize * 1.25 > 500000.0")),
 
646
    ?match(true, eval(T5, ?not_CreateSE("DomainName","TypeName",
 
647
                                        "EventName", [],
 
648
                                        [#'CosNotification_Property'{name="memsize", 
 
649
                                                                     value=any:create(orber_tc:float(), 5.5)},
 
650
                                         #'CosNotification_Property'{name="cputime", 
 
651
                                                                     value=any:create(orber_tc:float(), 0.00078431137)},
 
652
                                         #'CosNotification_Property'{name="filesize", 
 
653
                                                                     value=any:create(orber_tc:float(), 500000)}],
 
654
                                        any:create(orber_tc:null(), null)))),
 
655
    ?match(false, eval(T5, ?not_CreateSE("DomainName","TypeName",
 
656
                                         "EventName", [],
 
657
                                         [#'CosNotification_Property'{name="memsize", 
 
658
                                                                      value=any:create(orber_tc:float(), 5.5)},
 
659
                                          #'CosNotification_Property'{name="cputime", 
 
660
                                                                      value=any:create(orber_tc:float(), 0.00078431137)},
 
661
                                          #'CosNotification_Property'{name="filesize", 
 
662
                                                                      value=any:create(orber_tc:float(), 500)}],
 
663
                                         any:create(orber_tc:null(), null)))),
 
664
    ?match({error, _}, eval(T5, ?not_CreateSE("DomainName","TypeName",
 
665
                                              "EventName", [],
 
666
                                              [#'CosNotification_Property'{name="memsize", 
 
667
                                                                           value=any:create(orber_tc:float(), 5.5)},
 
668
                                               #'CosNotification_Property'{name="filesize", 
 
669
                                                                           value=any:create(orber_tc:float(), 500)}],
 
670
                                              any:create(orber_tc:null(), null)))),
 
671
 
 
672
    ?match(true, eval(T5, ?not_CreateSE("DomainName","TypeName",
 
673
                                        "EventName", [], [],
 
674
                                        any:create(orber_tc:sequence('CosNotification_Property':tc(),0),
 
675
                                        [#'CosNotification_Property'{name="memsize", 
 
676
                                                                     value=any:create(orber_tc:float(), 5.5)},
 
677
                                         #'CosNotification_Property'{name="cputime", 
 
678
                                                                     value=any:create(orber_tc:float(), 0.00078431137)},
 
679
                                         #'CosNotification_Property'{name="filesize", 
 
680
                                                                     value=any:create(orber_tc:float(), 500000)}])))),
 
681
    ?match(false, eval(T5, ?not_CreateSE("DomainName","TypeName",
 
682
                                        "EventName", [], [],
 
683
                                        any:create(orber_tc:sequence('CosNotification_Property':tc(),0),
 
684
                                        [#'CosNotification_Property'{name="memsize", 
 
685
                                                                     value=any:create(orber_tc:float(), 5.5)},
 
686
                                         #'CosNotification_Property'{name="cputime", 
 
687
                                                                     value=any:create(orber_tc:float(), 0.00078431137)},
 
688
                                         #'CosNotification_Property'{name="filesize", 
 
689
                                                                     value=any:create(orber_tc:float(), 500)}])))),
 
690
    ?match({error, _}, eval(T5, ?not_CreateSE("DomainName","TypeName",
 
691
                                        "EventName", [], [],
 
692
                                        any:create(orber_tc:sequence('CosNotification_Property':tc(),0),
 
693
                                        [#'CosNotification_Property'{name="memsize", 
 
694
                                                                     value=any:create(orber_tc:float(), 5.5)},
 
695
                                         #'CosNotification_Property'{name="filesize", 
 
696
                                                                     value=any:create(orber_tc:float(), 500)}])))),
 
697
 
 
698
    ?match(true, eval(T5, any:create(orber_tc:sequence('CosNotification_Property':tc(),0),
 
699
                                     [#'CosNotification_Property'{name="memsize", 
 
700
                                                                  value=any:create(orber_tc:float(), 5.5)},
 
701
                                      #'CosNotification_Property'{name="cputime", 
 
702
                                                                  value=any:create(orber_tc:float(), 0.00078431137)},
 
703
                                      #'CosNotification_Property'{name="filesize", 
 
704
                                                                  value=any:create(orber_tc:float(), 500000)}]))),
 
705
    ?match(false, eval(T5, any:create(orber_tc:sequence('CosNotification_Property':tc(),0),
 
706
                                        [#'CosNotification_Property'{name="memsize", 
 
707
                                                                     value=any:create(orber_tc:float(), 5.5)},
 
708
                                         #'CosNotification_Property'{name="cputime", 
 
709
                                                                     value=any:create(orber_tc:float(), 0.00078431137)},
 
710
                                         #'CosNotification_Property'{name="filesize", 
 
711
                                                                     value=any:create(orber_tc:float(), 500)}]))),
 
712
    ?match({error, _}, eval(T5, any:create(orber_tc:sequence('CosNotification_Property':tc(),0),
 
713
                                           [#'CosNotification_Property'{name="memsize", 
 
714
                                                                        value=any:create(orber_tc:float(), 5.5)},
 
715
                                            #'CosNotification_Property'{name="filesize", 
 
716
                                                                        value=any:create(orber_tc:float(), 500)}]))),
 
717
 
 
718
    %% Accept events where a threshold has the unscoped type name 'data'. 
 
719
    {ok,T6} = ?match({ok, _}, create_filter("exist $threshold._type_id and $threshold._type_id == 'data'")),
 
720
    ?match(true, eval(T6, any:create(orber_tc:alias(notify_test_data:id(),
 
721
                                                    "threshold",
 
722
                                                    notify_test_data:tc()), 
 
723
                                     #notify_test_data{score = 10, name = "Erlang"}))),
 
724
    
 
725
 
 
726
 
 
727
    ?match(true, eval(T6, ?not_CreateSE("DomainName","TypeName",
 
728
                                        "EventName", [],
 
729
                                        [#'CosNotification_Property'
 
730
                                         {name="threshold", 
 
731
                                          value=any:create(notify_test_data:tc(),
 
732
                                                           #notify_test_data
 
733
                                                           {score = 10, 
 
734
                                                            name  = "Erlang"})}],
 
735
                                        any:create(orber_tc:null(), null)))),
 
736
 
 
737
 
 
738
    ?match(true, eval(T6, ?not_CreateSE("DomainName","TypeName",
 
739
                                        "EventName", [],
 
740
                                        [#'CosNotification_Property'
 
741
                                         {name="NotThreshold", 
 
742
                                          value=any:create(notify_test_data:tc(),
 
743
                                                           #notify_test_data
 
744
                                                           {score = 10, 
 
745
                                                            name  = "Erlang"})}],
 
746
                                        any:create(orber_tc:alias(notify_test_data:id(),
 
747
                                                                  "threshold",
 
748
                                                                  notify_test_data:tc()), 
 
749
                                                   #notify_test_data{score = 10, name = "Erlang"})))),
 
750
 
 
751
 
 
752
 
 
753
    %% Accept events with a serviceUser property of the correct standard type. 
 
754
    {ok,T7} = ?match({ok, _}, create_filter("$violation(TestData)._repos_id == 'IDL:notify_test/data:1.0'")),
 
755
    ?match(true, eval(T7, ?not_CreateSE("DomainName","TypeName",
 
756
                                        "EventName", [],
 
757
                                        [#'CosNotification_Property'
 
758
                                         {name="violation", 
 
759
                                          value=any:create(orber_tc:array('CosNotification_Property':tc(),0),
 
760
                                                           [#'CosNotification_Property'
 
761
                                                            {name="TestData",
 
762
                                                             value=any:create(notify_test_data:tc(),
 
763
                                                                              #notify_test_data
 
764
                                                                              {score=100,
 
765
                                                                               name="perfect score"})}])}],
 
766
                                        any:create(orber_tc:null(), null)))),
 
767
    
 
768
    {ok,T8} = ?match({ok, _}, create_filter("$type_name == 'CommunicationsAlarm' and $event_name == 'lost_packet' and $priority < 2")),
 
769
    %% All correct
 
770
    Event1 = ?not_CreateSE("DomainName","CommunicationsAlarm",
 
771
                           "lost_packet",
 
772
                           [#'CosNotification_Property'{name="priority", 
 
773
                                                        value=any:create(orber_tc:short(), 1)}],
 
774
                           [], any:create(orber_tc:null(), null)),
 
775
    %% Priority to high
 
776
    Event2 = ?not_CreateSE("DomainName","CommunicationsAlarm",
 
777
                          "lost_packet",
 
778
                           [#'CosNotification_Property'{name="priority", 
 
779
                                                        value=any:create(orber_tc:short(), 2)}],
 
780
                           [], any:create(orber_tc:null(), null)),
 
781
    %% Misspell event_name, i.e., lost_packets instead of lost_packet
 
782
    Event3 = ?not_CreateSE("DomainName","CommunicationsAlarm",
 
783
                          "lost_packets",
 
784
                           [#'CosNotification_Property'{name="priority", 
 
785
                                                        value=any:create(orber_tc:short(), 1)}],
 
786
                          [], any:create(orber_tc:null(), null)),
 
787
    %% Another type_name
 
788
    Event4 = ?not_CreateSE("DomainName","TemperatureAlarm",
 
789
                           "lost_packets",
 
790
                          [#'CosNotification_Property'{name="priority", 
 
791
                                                       value=any:create(orber_tc:short(), 1)}],
 
792
                           [], any:create(orber_tc:null(), null)),
 
793
    
 
794
    ?match(true,  eval(T8, Event1)),
 
795
    ?match(false, eval(T8, Event2)),
 
796
    ?match(false, eval(T8, Event3)),
 
797
    ?match(false, eval(T8, Event4)),
 
798
    
 
799
    {ok,T9} = ?match({ok, _}, create_filter("$gpa < 80 or $tests(midterm) > $tests(final) or $monthly_attendance[3] < 10")),
 
800
 
 
801
    %% midterm > final yields true, the others false
 
802
    Event5 = ?not_CreateSE("DomainName","TypeName",
 
803
                           "EventName", [],
 
804
                           [#'CosNotification_Property'
 
805
                            {name="tests",
 
806
                             value=any:create(orber_tc:array('CosNotification_Property':tc(),0),
 
807
                                                 [#'CosNotification_Property'{name="midterm",
 
808
                                                        value=any:create(orber_tc:short(), 70)},
 
809
                                                  #'CosNotification_Property'{name="final",
 
810
                                                                              value=any:create(orber_tc:short(), 60)}])},
 
811
                            #'CosNotification_Property'{name="monthly_attendance", 
 
812
                                                        value=any:create(orber_tc:array(orber_tc:short(), 0),
 
813
                                                                         {0,1,2,10})},
 
814
                            #'CosNotification_Property'{name="gpa", 
 
815
                                                        value=any:create(orber_tc:short(), 90)}],
 
816
                           any:create(orber_tc:null(), null)),
 
817
    
 
818
    %% monthly_attendance[3] < 10 yields true, the others false
 
819
    Event6 = ?not_CreateSE("DomainName","TypeName",
 
820
                           "EventName", [],
 
821
                           [#'CosNotification_Property'{name="tests",
 
822
                                        value=any:create(orber_tc:array('CosNotification_Property':tc(),0),
 
823
                                                 [#'CosNotification_Property'{name="midterm",
 
824
                                                        value=any:create(orber_tc:short(), 70)},
 
825
                                                  #'CosNotification_Property'{name="final",
 
826
                                                                              value=any:create(orber_tc:short(), 80)}])},
 
827
                            #'CosNotification_Property'{name="monthly_attendance", 
 
828
                                                        value=any:create(orber_tc:array(orber_tc:short(), 0),
 
829
                                                                         {0,1,2,9})},
 
830
                            #'CosNotification_Property'{name="gpa", 
 
831
                                                        value=any:create(orber_tc:short(), 90)}],
 
832
                           any:create(orber_tc:null(), null)),
 
833
 
 
834
    %% gpa < 80 true, rest false.
 
835
    Event7 = ?not_CreateSE("DomainName","TypeName",
 
836
                           "EventName", [],
 
837
                           [#'CosNotification_Property'{name="tests",
 
838
                                        value=any:create(orber_tc:array('CosNotification_Property':tc(),0),
 
839
                                                 [#'CosNotification_Property'{name="midterm",
 
840
                                                        value=any:create(orber_tc:short(), 70)},
 
841
                                                  #'CosNotification_Property'{name="final",
 
842
                                                                              value=any:create(orber_tc:short(), 80)}])},
 
843
                            #'CosNotification_Property'{name="monthly_attendance", 
 
844
                                                        value=any:create(orber_tc:array(orber_tc:short(), 0),
 
845
                                                                         {0,1,2,10})},
 
846
                            #'CosNotification_Property'{name="gpa", 
 
847
                                                        value=any:create(orber_tc:short(), 70)}],
 
848
                           any:create(orber_tc:null(), null)),
 
849
 
 
850
    %% All false
 
851
    Event8 = ?not_CreateSE("DomainName","TypeName",
 
852
                           "EventName", [],
 
853
                           [#'CosNotification_Property'{name="tests",
 
854
                                        value=any:create(orber_tc:array('CosNotification_Property':tc(),0),
 
855
                                                 [#'CosNotification_Property'{name="midterm",
 
856
                                                        value=any:create(orber_tc:short(), 70)},
 
857
                                                  #'CosNotification_Property'{name="final",
 
858
                                                                              value=any:create(orber_tc:short(), 80)}])},
 
859
                            #'CosNotification_Property'{name="monthly_attendance", 
 
860
                                                        value=any:create(orber_tc:array(orber_tc:short(), 0),
 
861
                                                                         {0,1,2,10})},
 
862
                            #'CosNotification_Property'{name="gpa", 
 
863
                                                        value=any:create(orber_tc:short(), 80)}],
 
864
                           any:create(orber_tc:null(), null)),
 
865
 
 
866
    ?match(true,  eval(T9, Event5)),
 
867
    ?match(true,  eval(T9, Event6)),
 
868
    ?match(true,  eval(T9, Event7)),
 
869
    ?match(false, eval(T9, Event8)),
 
870
    ok.
 
871
 
 
872
%%-----------------------------------------------------------------
 
873
%%  Misc grammar tests
 
874
%%-----------------------------------------------------------------
 
875
positional_api(doc) -> ["CosNotification positional notation grammar tests", ""];
 
876
positional_api(suite) -> [];
 
877
positional_api(_Config) ->
 
878
    {ok,T1} = ?match({ok, _}, create_filter("$.3 < 80 or $.1(midterm) > $.1(final) or $.2[3] < 10")),
 
879
 
 
880
    %% midterm > final yields true, the others false
 
881
    Event1 = any:create(notify_test_studies:tc(), #notify_test_studies
 
882
                        {gpa = 90,
 
883
                         tests = [#'CosNotification_Property'
 
884
                                  {name="midterm", value=any:create(orber_tc:short(), 70)},
 
885
                                  #'CosNotification_Property'
 
886
                                  {name="final", value=any:create(orber_tc:short(), 60)}],
 
887
                         monthly_attendance = {0,1,2,10}}),
 
888
    %% monthly_attendance[3] < 10 yields true, the others false
 
889
    Event2 = any:create(notify_test_studies:tc(), #notify_test_studies
 
890
                        {gpa = 90,
 
891
                         tests = [#'CosNotification_Property'
 
892
                                  {name="midterm", value=any:create(orber_tc:short(), 70)},
 
893
                                  #'CosNotification_Property'
 
894
                                  {name="final", value=any:create(orber_tc:short(), 80)}],
 
895
                         monthly_attendance = {0,1,2,9}}),
 
896
    %% gpa < 80 true, rest false.
 
897
    Event3 = any:create(notify_test_studies:tc(), #notify_test_studies
 
898
                        {gpa = 70,
 
899
                         tests = [#'CosNotification_Property'
 
900
                                  {name="midterm", value=any:create(orber_tc:short(), 70)},
 
901
                                  #'CosNotification_Property'
 
902
                                  {name="final", value=any:create(orber_tc:short(), 80)}],
 
903
                         monthly_attendance = {0,1,2,10}}),
 
904
    %% All false
 
905
    Event4 = any:create(notify_test_studies:tc(), #notify_test_studies
 
906
                        {gpa = 80,
 
907
                         tests = [#'CosNotification_Property'
 
908
                                  {name="midterm", value=any:create(orber_tc:short(), 70)},
 
909
                                  #'CosNotification_Property'
 
910
                                  {name="final", value=any:create(orber_tc:short(), 80)}],
 
911
                         monthly_attendance = {0,1,2,10}}),
 
912
 
 
913
    ?match(true,  eval(T1, Event1)),
 
914
    ?match(true,  eval(T1, Event2)),
 
915
    ?match(true,  eval(T1, Event3)),
 
916
    ?match(false, eval(T1, Event4)),
 
917
 
 
918
    {ok,T2} = ?match({ok, _}, create_filter("$.0.0.0.1 == 'CommunicationsAlarm'")),
 
919
 
 
920
    Event5 = ?not_CreateSE("DomainName","CommunicationsAlarm",
 
921
                           "lost_packet", [], [], 
 
922
                           any:create(orber_tc:null(), null)),
 
923
 
 
924
    ?match(true,  eval(T2, Event5)),
 
925
    
 
926
    ok.
 
927
 
 
928
%%-----------------------------------------------------------------
 
929
%%  Components grammar tests
 
930
%%-----------------------------------------------------------------
 
931
components_api(doc) -> ["CosNotification components grammar tests", ""];
 
932
components_api(suite) -> [];
 
933
components_api(_Config) ->
 
934
    {ok,T1}  = ?match({ok, _}, create_filter("$ == 2")),
 
935
    ?match(true, eval(T1, ?not_CreateSE("DomainName","TypeName","EventName",
 
936
                                        [],[], any:create(orber_tc:short(), 2)))),
 
937
    ?match(true, eval(T1, any:create(orber_tc:short(), 2))),
 
938
    ?match(false, eval(T1, ?not_CreateSE("DomainName","TypeName","EventName",
 
939
                                         [],[], any:create(orber_tc:short(), 3)))),
 
940
    ?match(false, eval(T1, any:create(orber_tc:short(), 3))),
 
941
 
 
942
    %% Select "MOVIE" events featuring at least 3 of the Marx Brothers. 
 
943
    {ok,T2} = ?match({ok, _}, create_filter("$type_name == 'MOVIE' and (('groucho' in $.starlist) + ('chico' in $.starlist) + ('harpo' in $.starlist) + ('zeppo' in $.starlist) + ('gummo' in $.starlist)) > 2")),
 
944
    ?match(true, eval(T2, ?not_CreateSE("DomainName","MOVIE", "EventName", [], [],
 
945
                                        any:create(orber_tc:alias("IFRId","starlist",tk_any),
 
946
                                                   any:create(orber_tc:sequence(orber_tc:string(0),0),
 
947
                                                              ["groucho", "harpo", "sam", "gummo"]))))),
 
948
    ?match(false, eval(T2, ?not_CreateSE("DomainName","MOVIE", "EventName", [], [], 
 
949
                                        any:create(orber_tc:alias("IFRId","starlist",tk_any),
 
950
                                                   any:create(orber_tc:sequence(orber_tc:string(0),0),
 
951
                                                              ["frodo", "bilbo", "sam", "gummo"]))))),
 
952
 
 
953
    %% Accept only recent events (e.g., generated within the last 15 minutes or so). 
 
954
    {ok,_T3} = ?match({ok, _}, create_filter("$origination_timestamp.high + 2 < $curtime.high")),
 
955
 
 
956
 
 
957
    %% Accept students that took all 3 tests and had an average score of at least 80%. 
 
958
    {ok,T4} = ?match({ok, _}, create_filter("$.test._length == 3 and ($.test[0].score + $.test[1].score + $.test[2].score)/3 >=80")),
 
959
    ?match(true, eval(T4, ?not_CreateSE("DomainName","TypeName", "EventName", [], [],
 
960
                                        any:create(orber_tc:alias("IFRId","test",tk_any),
 
961
                                                   any:create(orber_tc:array(notify_test_data:tc(),0),
 
962
                                                              {#notify_test_data{score=75},
 
963
                                                               #notify_test_data{score=80},
 
964
                                                               #notify_test_data{score=85}}))))),
 
965
    ?match(false, eval(T4, ?not_CreateSE("DomainName","TypeName", "EventName", [], [],
 
966
                                         any:create(orber_tc:alias("IFRId","test",tk_any),
 
967
                                                    any:create(orber_tc:array(notify_test_data:tc(),0),
 
968
                                                               {#notify_test_data{score=75},
 
969
                                                                #notify_test_data{score=80},
 
970
                                                                #notify_test_data{score=80}}))))),
 
971
    ?match(false, eval(T4, ?not_CreateSE("DomainName","TypeName", "EventName", [], [],
 
972
                                         any:create(orber_tc:alias("IFRId","test",tk_any),
 
973
                                                    any:create(orber_tc:array(notify_test_data:tc(),0),
 
974
                                                               {#notify_test_data{score=75},
 
975
                                                                #notify_test_data{score=80}}))))),
 
976
 
 
977
    %% Select processes that exceed a certain usage threshold. 
 
978
    {ok,T5} = ?match({ok, _}, create_filter("$.memsize / 5.5 + $.cputime * 1275.0 + $.filesize * 1.25 > 500000.0")),
 
979
    ?match(true, eval(T5, ?not_CreateSE("DomainName","TypeName", "EventName", [], [],
 
980
                                        any:create(notify_test_computer:tc(),
 
981
                                                   #notify_test_computer
 
982
                                                   {memsize=5.5,
 
983
                                                    cputime = 0.00078431137, 
 
984
                                                    filesize = 500000})))),
 
985
    ?match(false, eval(T5, ?not_CreateSE("DomainName","TypeName", "EventName", [], [],
 
986
                                         any:create(notify_test_computer:tc(),
 
987
                                                    #notify_test_computer
 
988
                                                    {memsize=5.5,
 
989
                                                     cputime = 0.00078431137, 
 
990
                                                     filesize = 500})))),
 
991
    ?match({error,_}, eval(T5, ?not_CreateSE("DomainName","TypeName", "EventName", [], [],
 
992
                                             any:create(notify_test_computer:tc(),
 
993
                                                        #notify_test_computer
 
994
                                                        {memsize=5.5,
 
995
                                                         cputime = 0.00078431137})))),
 
996
 
 
997
    %% Accept only Notification Service structured events. 
 
998
    {ok,T6} = ?match({ok, _}, create_filter("$._repos_id == 'IDL:omg.org/CosNotification/StructuredEvent:1.0'")),
 
999
    ?match(true, eval(T6, ?not_CreateSE("DomainName","CommunicationsAlarm",
 
1000
                                        "EventName",
 
1001
                                        [], [], any:create(orber_tc:null(), null)))),
 
1002
 
 
1003
   
 
1004
 
 
1005
    %% Accept only those events that have a specified security "rights list". 
 
1006
    {ok,T7} = ?match({ok, _}, create_filter("exist $.header.variable_header(required_rights)")),
 
1007
    ?match(false, eval(T7, ?not_CreateSE("DomainName","CommunicationsAlarm",
 
1008
                                         "lost_packet",
 
1009
                                         [#'CosNotification_Property'{name="priority", 
 
1010
                                                                      value=any:create(orber_tc:short(), 1)}],
 
1011
                                         [], any:create(orber_tc:null(), null)))),
 
1012
    ?match(true, eval(T7, ?not_CreateSE("DomainName","CommunicationsAlarm",
 
1013
                                        "lost_packet",
 
1014
                                        [#'CosNotification_Property'{name="required_rights", 
 
1015
                                                                     value=any:create(orber_tc:short(), 1)}],
 
1016
                                        [], any:create(orber_tc:null(), null)))),
 
1017
 
 
1018
 
 
1019
    {ok,T8} = ?match({ok, _}, create_filter("$.header.fixed_header.event_type.type_name == 'CommunicationsAlarm' and $.header.fixed_header.event_name == 'lost_packet' and $.header.variable_header(priority) < 2")),
 
1020
    %% All correct
 
1021
    Event1 = ?not_CreateSE("DomainName","CommunicationsAlarm",
 
1022
                          "lost_packet",
 
1023
                          [#'CosNotification_Property'{name="priority", 
 
1024
                                                       value=any:create(orber_tc:short(), 1)}],
 
1025
                          [], any:create(orber_tc:null(), null)),
 
1026
    %% Priority to high
 
1027
    Event2 = ?not_CreateSE("DomainName","CommunicationsAlarm",
 
1028
                          "lost_packet",
 
1029
                          [#'CosNotification_Property'{name="priority", 
 
1030
                                                       value=any:create(orber_tc:short(), 2)}],
 
1031
                          [], any:create(orber_tc:null(), null)),
 
1032
    %% Misspell event_name, i.e., lost_packets instead of lost_packet
 
1033
    Event3 = ?not_CreateSE("DomainName","CommunicationsAlarm",
 
1034
                          "lost_packets",
 
1035
                          [#'CosNotification_Property'{name="priority", 
 
1036
                                                       value=any:create(orber_tc:short(), 1)}],
 
1037
                          [], any:create(orber_tc:null(), null)),
 
1038
    %% Another type_name
 
1039
    Event4 = ?not_CreateSE("DomainName","TemperatureAlarm",
 
1040
                          "lost_packets",
 
1041
                          [#'CosNotification_Property'{name="priority", 
 
1042
                                                       value=any:create(orber_tc:short(), 1)}],
 
1043
                          [], any:create(orber_tc:null(), null)),
 
1044
 
 
1045
    ?match(true,  eval(T8, Event1)),
 
1046
    ?match(false, eval(T8, Event2)),
 
1047
    ?match(false, eval(T8, Event3)),
 
1048
    ?match(false, eval(T8, Event4)),
 
1049
   
 
1050
 
 
1051
    {ok,T9} = ?match({ok, _}, create_filter("$.gpa < 80 or $.tests(midterm) > $.tests(final) or $.monthly_attendance[3] < 10")),
 
1052
 
 
1053
    %% midterm > final yields true, the others false
 
1054
    Event5 = ?not_CreateSE("DomainName","TypeName",
 
1055
                           "EventName", [], [],
 
1056
                            any:create(notify_test_studies:tc(), #notify_test_studies
 
1057
                                       {gpa = 90,
 
1058
                                        tests = [#'CosNotification_Property'
 
1059
                                                 {name="midterm", value=any:create(orber_tc:short(), 70)},
 
1060
                                                 #'CosNotification_Property'
 
1061
                                                 {name="final", value=any:create(orber_tc:short(), 60)}],
 
1062
                                        monthly_attendance = {0,1,2,10}})),
 
1063
    %% monthly_attendance[3] < 10 yields true, the others false
 
1064
    Event6 = ?not_CreateSE("DomainName","TypeName",
 
1065
                           "EventName", [], [],
 
1066
                            any:create(notify_test_studies:tc(), #notify_test_studies
 
1067
                                       {gpa = 90,
 
1068
                                        tests = [#'CosNotification_Property'
 
1069
                                                 {name="midterm", value=any:create(orber_tc:short(), 70)},
 
1070
                                                 #'CosNotification_Property'
 
1071
                                                 {name="final", value=any:create(orber_tc:short(), 80)}],
 
1072
                                        monthly_attendance = {0,1,2,9}})),
 
1073
    %% gpa < 80 true, rest false.
 
1074
    Event7 = ?not_CreateSE("DomainName","TypeName",
 
1075
                           "EventName", [], [],
 
1076
                            any:create(notify_test_studies:tc(), #notify_test_studies
 
1077
                                       {gpa = 70,
 
1078
                                        tests = [#'CosNotification_Property'
 
1079
                                                 {name="midterm", value=any:create(orber_tc:short(), 70)},
 
1080
                                                 #'CosNotification_Property'
 
1081
                                                 {name="final", value=any:create(orber_tc:short(), 80)}],
 
1082
                                        monthly_attendance = {0,1,2,10}})),
 
1083
    %% All false
 
1084
    Event8 = ?not_CreateSE("DomainName","TypeName",
 
1085
                           "EventName", [], [],
 
1086
                            any:create(notify_test_studies:tc(), #notify_test_studies
 
1087
                                       {gpa = 80,
 
1088
                                        tests = [#'CosNotification_Property'
 
1089
                                                 {name="midterm", value=any:create(orber_tc:short(), 70)},
 
1090
                                                 #'CosNotification_Property'
 
1091
                                                 {name="final", value=any:create(orber_tc:short(), 80)}],
 
1092
                                        monthly_attendance = {0,1,2,10}})),
 
1093
 
 
1094
    ?match(true,  eval(T9, Event5)),
 
1095
    ?match(true,  eval(T9, Event6)),
 
1096
    ?match(true,  eval(T9, Event7)),
 
1097
    ?match(false, eval(T9, Event8)),
 
1098
    ok.
 
1099
 
 
1100
 
 
1101
%%-----------------------------------------------------------------
 
1102
%% Internal functions
 
1103
%%-----------------------------------------------------------------
 
1104
 
 
1105
%%-------------------- End of Module ------------------------------