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

« back to all changes in this revision

Viewing changes to lib/orber/test/tc_SUITE.erl

  • Committer: Bazaar Package Importer
  • Author(s): Clint Byrum
  • Date: 2011-05-05 15:48:43 UTC
  • mfrom: (3.5.13 sid)
  • Revision ID: james.westby@ubuntu.com-20110505154843-0om6ekzg6m7ugj27
Tags: 1:14.b.2-dfsg-3ubuntu1
* Merge from debian unstable.  Remaining changes:
  - Drop libwxgtk2.8-dev build dependency. Wx isn't in main, and not
    supposed to.
  - Drop erlang-wx binary.
  - Drop erlang-wx dependency from -megaco, -common-test, and -reltool, they
    do not really need wx. Also drop it from -debugger; the GUI needs wx,
    but it apparently has CLI bits as well, and is also needed by -megaco,
    so let's keep the package for now.
  - debian/patches/series: Do what I meant, and enable build-options.patch
    instead.
* Additional changes:
  - Drop erlang-wx from -et
* Dropped Changes:
  - patches/pcre-crash.patch: CVE-2008-2371: outer level option with
    alternatives caused crash. (Applied Upstream)
  - fix for ssl certificate verification in newSSL: 
    ssl_cacertfile_fix.patch (Applied Upstream)
  - debian/patches/series: Enable native.patch again, to get stripped beam
    files and reduce the package size again. (build-options is what
    actually accomplished this)
  - Remove build-options.patch on advice from upstream and because it caused
    odd build failures.

Show diffs side-by-side

added added

removed removed

Lines of Context:
 
1
%%
 
2
%% %CopyrightBegin%
 
3
%% 
 
4
%% Copyright Ericsson AB 2004-2011. All Rights Reserved.
 
5
%% 
 
6
%% The contents of this file are subject to the Erlang Public License,
 
7
%% Version 1.1, (the "License"); you may not use this file except in
 
8
%% compliance with the License. You should have received a copy of the
 
9
%% Erlang Public License along with this software. If not, it can be
 
10
%% retrieved online at http://www.erlang.org/.
 
11
%% 
 
12
%% Software distributed under the License is distributed on an "AS IS"
 
13
%% basis, WITHOUT WARRANTY OF ANY KIND, either express or implied. See
 
14
%% the License for the specific language governing rights and limitations
 
15
%% under the License.
 
16
%% 
 
17
%% %CopyrightEnd%
 
18
%%
 
19
%%
 
20
%%-----------------------------------------------------------------
 
21
%% 
 
22
%% Description:
 
23
%% Test suite for the basic typecode functions
 
24
%%
 
25
%%-----------------------------------------------------------------
 
26
-module(tc_SUITE).
 
27
 
 
28
-include_lib("test_server/include/test_server.hrl").
 
29
-include_lib("orber/src/orber_iiop.hrl").
 
30
 
 
31
-define(default_timeout, ?t:minutes(3)).
 
32
 
 
33
-define(match(Expr),
 
34
        fun() ->
 
35
                case (catch (Expr)) of
 
36
                    AcTuAlReS when is_binary(AcTuAlReS)->
 
37
                        io:format("###### ERROR ERROR ######~nRESULT:  ~p~n",
 
38
                                  [AcTuAlReS]),
 
39
                        exit(AcTuAlReS);
 
40
                    _ ->
 
41
                        ok
 
42
                end
 
43
        end()).
 
44
-define(SUB_ELIST, [{"null", orber_tc:null()},
 
45
                    {"void", orber_tc:void()},
 
46
                    {"short", orber_tc:short()},
 
47
                    {"unsigned_short", orber_tc:unsigned_short()},
 
48
                    {"long", orber_tc:long()},
 
49
                    {"unsigned_long", orber_tc:unsigned_long()},
 
50
                    {"long_long", orber_tc:long_long()},
 
51
                    {"unsigned_long_long", orber_tc:unsigned_long_long()},
 
52
                    {"float", orber_tc:'float'()},
 
53
                    {"double", orber_tc:double()},
 
54
                    {"longdouble", orber_tc:longdouble()},
 
55
                    {"boolean", orber_tc:boolean()},
 
56
                    {"char", orber_tc:char()},
 
57
                    {"wchar", orber_tc:wchar()},
 
58
                    {"octet", orber_tc:octet()},
 
59
                    {"any", orber_tc:any()},
 
60
                    {"typecode", orber_tc:typecode()},
 
61
                    {"principal", orber_tc:principal()},
 
62
                    {"object_reference", orber_tc:object_reference("Id", "Name")}]).
 
63
 
 
64
-define(ELIST, [{"null", orber_tc:null()},
 
65
                {"void", orber_tc:void()},
 
66
                {"short", orber_tc:short()},
 
67
                {"unsigned_short", orber_tc:unsigned_short()},
 
68
                {"long", orber_tc:long()},
 
69
                {"unsigned_long", orber_tc:unsigned_long()},
 
70
                {"long_long", orber_tc:long_long()},
 
71
                {"unsigned_long_long", orber_tc:unsigned_long_long()},
 
72
                {"float", orber_tc:'float'()},
 
73
                {"double", orber_tc:double()},
 
74
                {"longdouble", orber_tc:longdouble()},
 
75
                {"boolean", orber_tc:boolean()},
 
76
                {"char", orber_tc:char()},
 
77
                {"wchar", orber_tc:wchar()},
 
78
                {"octet", orber_tc:octet()},
 
79
                {"any", orber_tc:any()},
 
80
                {"typecode", orber_tc:typecode()},
 
81
                {"principal", orber_tc:principal()},
 
82
                {"object_reference", orber_tc:object_reference("Id", "Name")},
 
83
                {"struct", orber_tc:struct("Id", "Name", ?SUB_ELIST)},
 
84
                {"enum", orber_tc:enum("Id", "Name", ["E1", "E2"])},
 
85
                {"string", orber_tc:string(1)},
 
86
                {"wstring", orber_tc:wstring(0)},
 
87
                {"sequence", orber_tc:sequence(orber_tc:enum("Id", "Name", 
 
88
                                                             ["E1", "E2"]), 0)},
 
89
                {"array", orber_tc:array(orber_tc:enum("Id", "Name",
 
90
                                                       ["E1", "E2"]), 2)},
 
91
                {"alias", orber_tc:alias("id", "name", 
 
92
                                         orber_tc:enum("Id", "Name",
 
93
                                                       ["E1", "E2"]))},
 
94
                {"exception", orber_tc:exception("Id", "Name", ?SUB_ELIST)}]).
 
95
 
 
96
-define(VELIST, [{"null", orber_tc:null(), 42},
 
97
                 {"void", orber_tc:void(), 42},
 
98
                 {"short", orber_tc:short(), 42},
 
99
                 {"unsigned_short", orber_tc:unsigned_short(), 42},
 
100
                 {"long", orber_tc:long(), 42},
 
101
                 {"unsigned_long", orber_tc:unsigned_long(), 42},
 
102
                 {"long_long", orber_tc:long_long(), 42},
 
103
                 {"unsigned_long_long", orber_tc:unsigned_long_long(), 42},
 
104
                 {"float", orber_tc:'float'(), 42},
 
105
                 {"double", orber_tc:double(), 42},
 
106
                 {"longdouble", orber_tc:longdouble(), 42},
 
107
                 {"boolean", orber_tc:boolean(), 42},
 
108
                 {"char", orber_tc:char(), 42},
 
109
                 {"wchar", orber_tc:wchar(), 42},
 
110
                 {"octet", orber_tc:octet(), 42},
 
111
                 {"any", orber_tc:any(), 42},
 
112
                 {"typecode", orber_tc:typecode(), 42},
 
113
                 {"principal", orber_tc:principal(), 42},
 
114
                 {"object_reference", orber_tc:object_reference("Id", "Name"), 42},
 
115
                 {"struct", orber_tc:struct("Id", "Name", ?SUB_ELIST), 42},
 
116
                 {"enum", orber_tc:enum("Id", "Name", ["E1", "E2"]), 42},
 
117
                 {"string", orber_tc:string(1), 42},
 
118
                 {"wstring", orber_tc:wstring(0), 42},
 
119
                 {"sequence", orber_tc:sequence(orber_tc:enum("Id", "Name", 
 
120
                                                              ["E1", "E2"]), 0), 42},
 
121
                 {"array", orber_tc:array(orber_tc:enum("Id", "Name",
 
122
                                                        ["E1", "E2"]), 2), 42},
 
123
                 {"alias", orber_tc:alias("id", "name", 
 
124
                                          orber_tc:enum("Id", "Name",
 
125
                                                        ["E1", "E2"])), 42},
 
126
                 {"exception", orber_tc:exception("Id", "Name", ?SUB_ELIST), 42}]).
 
127
 
 
128
%%-----------------------------------------------------------------
 
129
%% External exports
 
130
%%-----------------------------------------------------------------
 
131
-export([all/0, suite/0,groups/0,init_per_suite/1, end_per_suite/1, 
 
132
         init_per_group/2,end_per_group/2]).
 
133
 
 
134
%%-----------------------------------------------------------------
 
135
%% Internal exports
 
136
%%-----------------------------------------------------------------
 
137
-compile(export_all).
 
138
 
 
139
%%-----------------------------------------------------------------
 
140
%% Func: all/1
 
141
%% Args: 
 
142
%% Returns: 
 
143
%%-----------------------------------------------------------------
 
144
suite() -> [{ct_hooks,[ts_install_cth]}].
 
145
 
 
146
all() -> 
 
147
    [null, void, short, ushort, long, ulong, longlong,
 
148
     ulonglong, boolean, char, wchar, octet, float, double,
 
149
     longdouble, any, typecode, principal, object_reference,
 
150
     struct, union, enum, string, wstring, sequence, array,
 
151
     alias, exception, fixed, value, value_box, native,
 
152
     abstract_interface, indirection, get_tc].
 
153
 
 
154
groups() -> 
 
155
    [].
 
156
 
 
157
init_per_suite(Config) ->
 
158
    Config.
 
159
 
 
160
end_per_suite(_Config) ->
 
161
    ok.
 
162
 
 
163
init_per_group(_GroupName, Config) ->
 
164
    Config.
 
165
 
 
166
end_per_group(_GroupName, Config) ->
 
167
    Config.
 
168
 
 
169
 
 
170
%%-----------------------------------------------------------------
 
171
%% Init and cleanup functions.
 
172
%%-----------------------------------------------------------------
 
173
 
 
174
init_per_testcase(_Case, Config) ->
 
175
    ?line Dog=test_server:timetrap(?default_timeout),
 
176
    [{watchdog, Dog}|Config].
 
177
 
 
178
 
 
179
end_per_testcase(_Case, Config) ->
 
180
    Dog = ?config(watchdog, Config),
 
181
    test_server:timetrap_cancel(Dog),
 
182
    ok.
 
183
 
 
184
%%-----------------------------------------------------------------
 
185
%% Test Case: null test
 
186
%% Description: 
 
187
%%-----------------------------------------------------------------
 
188
null(doc) -> [];
 
189
null(suite) -> [];
 
190
null(_) ->
 
191
    ?line true = orber_tc:check_tc(orber_tc:null()),
 
192
    ?line code(orber_tc:null()),
 
193
    ok.
 
194
 
 
195
%%-----------------------------------------------------------------
 
196
%% Test Case: void test
 
197
%% Description: 
 
198
%%-----------------------------------------------------------------
 
199
void(doc) -> [];
 
200
void(suite) -> [];
 
201
void(_) ->
 
202
    ?line true = orber_tc:check_tc(orber_tc:void()),
 
203
    ?line code(orber_tc:void()),
 
204
    ok.
 
205
 
 
206
%%-----------------------------------------------------------------
 
207
%% Test Case: short integer test
 
208
%% Description: 
 
209
%%-----------------------------------------------------------------
 
210
short(doc) -> [];
 
211
short(suite) -> [];
 
212
short(_) ->
 
213
    ?line true = orber_tc:check_tc(orber_tc:short()),
 
214
    ?line code(orber_tc:short()),
 
215
    ok.
 
216
 
 
217
%%-----------------------------------------------------------------
 
218
%% Test Case: unsigned short integer test
 
219
%% Description: 
 
220
%%-----------------------------------------------------------------
 
221
ushort(doc) -> [];
 
222
ushort(suite) -> [];
 
223
ushort(_) ->
 
224
    ?line true = orber_tc:check_tc(orber_tc:unsigned_short()),
 
225
    ?line code(orber_tc:unsigned_short()),
 
226
    ok.
 
227
 
 
228
%%-----------------------------------------------------------------
 
229
%% Test Case: long integer test
 
230
%% Description: 
 
231
%%-----------------------------------------------------------------
 
232
long(doc) -> [];
 
233
long(suite) -> [];
 
234
long(_) ->
 
235
    ?line true = orber_tc:check_tc(orber_tc:long()),
 
236
    ?line code(orber_tc:long()),
 
237
    ok.
 
238
 
 
239
%%-----------------------------------------------------------------
 
240
%% Test Case: unsigned long integer test
 
241
%% Description: 
 
242
%%-----------------------------------------------------------------
 
243
ulong(doc) -> [];
 
244
ulong(suite) -> [];
 
245
ulong(_) -> 
 
246
    ?line true = orber_tc:check_tc(orber_tc:unsigned_long()),
 
247
    ?line code(orber_tc:unsigned_long()),
 
248
    ok.
 
249
    
 
250
 
 
251
%%-----------------------------------------------------------------
 
252
%% Test Case: long integer test
 
253
%% Description: 
 
254
%%-----------------------------------------------------------------
 
255
longlong(doc) -> [];
 
256
longlong(suite) -> [];
 
257
longlong(_) ->
 
258
    ?line true = orber_tc:check_tc(orber_tc:long_long()),
 
259
    ?line code(orber_tc:long_long()),
 
260
    ok.
 
261
 
 
262
%%-----------------------------------------------------------------
 
263
%% Test Case: unsigned long integer test
 
264
%% Description: 
 
265
%%-----------------------------------------------------------------
 
266
ulonglong(doc) -> [];
 
267
ulonglong(suite) -> [];
 
268
ulonglong(_) -> 
 
269
    ?line true = orber_tc:check_tc(orber_tc:unsigned_long_long()),
 
270
    ?line code(orber_tc:unsigned_long_long()),
 
271
    ok.
 
272
 
 
273
 
 
274
%%-----------------------------------------------------------------
 
275
%% Test Case: float test
 
276
%% Description: 
 
277
%%-----------------------------------------------------------------
 
278
float(doc) -> [];
 
279
float(suite) -> [];
 
280
float(_) ->
 
281
    ?line true = orber_tc:check_tc(orber_tc:'float'()),
 
282
    ?line code(orber_tc:'float'()),
 
283
    ok.
 
284
 
 
285
%%-----------------------------------------------------------------
 
286
%% Test Case: double test
 
287
%% Description: 
 
288
%%-----------------------------------------------------------------
 
289
double(doc) -> [];
 
290
double(suite) -> [];
 
291
double(_) ->
 
292
    ?line true = orber_tc:check_tc(orber_tc:double()),
 
293
    ?line code(orber_tc:double()),
 
294
    ok.
 
295
 
 
296
%%-----------------------------------------------------------------
 
297
%% Test Case: longdouble test
 
298
%% Description: 
 
299
%%-----------------------------------------------------------------
 
300
longdouble(doc) -> [];
 
301
longdouble(suite) -> [];
 
302
longdouble(_) ->
 
303
    ?line true = orber_tc:check_tc(orber_tc:longdouble()),
 
304
    ?line code(orber_tc:longdouble()),
 
305
    ok.
 
306
 
 
307
%%-----------------------------------------------------------------
 
308
%% Test Case: boolean test
 
309
%% Description: 
 
310
%%-----------------------------------------------------------------
 
311
boolean(doc) -> [];
 
312
boolean(suite) -> [];
 
313
boolean(_) ->
 
314
    ?line true = orber_tc:check_tc(orber_tc:boolean()),
 
315
    ?line code(orber_tc:boolean()),
 
316
    ok.
 
317
 
 
318
%%-----------------------------------------------------------------
 
319
%% Test Case: character test
 
320
%% Description: 
 
321
%%-----------------------------------------------------------------
 
322
char(doc) -> [];
 
323
char(suite) -> [];
 
324
char(_) ->
 
325
    ?line true = orber_tc:check_tc(orber_tc:char()),
 
326
    ?line code(orber_tc:char()),
 
327
    ok.
 
328
 
 
329
%%-----------------------------------------------------------------
 
330
%% Test Case: character test
 
331
%% Description: 
 
332
%%-----------------------------------------------------------------
 
333
wchar(doc) -> [];
 
334
wchar(suite) -> [];
 
335
wchar(_) ->
 
336
    ?line true = orber_tc:check_tc(orber_tc:wchar()),
 
337
    ?line code(orber_tc:wchar()),
 
338
    ok.
 
339
 
 
340
%%-----------------------------------------------------------------
 
341
%% Test Case: octet test
 
342
%% Description: 
 
343
%%-----------------------------------------------------------------
 
344
octet(doc) -> [];
 
345
octet(suite) -> [];
 
346
octet(_) ->
 
347
    ?line true = orber_tc:check_tc(orber_tc:octet()),
 
348
    ?line code(orber_tc:octet()),
 
349
    ok.
 
350
 
 
351
%%-----------------------------------------------------------------
 
352
%% Test Case: any test
 
353
%% Description: 
 
354
%%-----------------------------------------------------------------
 
355
any(doc) -> [];
 
356
any(suite) -> [];
 
357
any(_) ->
 
358
    ?line true = orber_tc:check_tc(orber_tc:any()),
 
359
    ?line code(orber_tc:any()),
 
360
    ok.
 
361
 
 
362
%%-----------------------------------------------------------------
 
363
%% Test Case: typecode test
 
364
%% Description: 
 
365
%%-----------------------------------------------------------------
 
366
typecode(doc) -> [];
 
367
typecode(suite) -> [];
 
368
typecode(_) ->
 
369
    ?line true = orber_tc:check_tc(orber_tc:typecode()),
 
370
    ?line code(orber_tc:typecode()),
 
371
    ok.
 
372
 
 
373
%%-----------------------------------------------------------------
 
374
%% Test Case: principal test
 
375
%% Description: 
 
376
%%-----------------------------------------------------------------
 
377
principal(doc) -> [];
 
378
principal(suite) -> [];
 
379
principal(_) ->
 
380
    ?line true = orber_tc:check_tc(orber_tc:principal()),
 
381
    ?line code(orber_tc:principal()),
 
382
    ok.
 
383
 
 
384
 
 
385
%%-----------------------------------------------------------------
 
386
%% Test Case: object_reference test
 
387
%% Description: 
 
388
%%-----------------------------------------------------------------
 
389
object_reference(doc) -> [];
 
390
object_reference(suite) -> [];
 
391
object_reference(_) ->
 
392
    ?line true = orber_tc:check_tc(orber_tc:object_reference("Id", "Name")),
 
393
    ?line false = orber_tc:check_tc(orber_tc:object_reference(42, "Name")),
 
394
    ?line false = orber_tc:check_tc(orber_tc:object_reference("Id", 42)),
 
395
    ?line code(orber_tc:object_reference("Id", "Name")),
 
396
    ?line ?match(code(orber_tc:object_reference(42, "Name"))),
 
397
    ?line ?match(code(orber_tc:object_reference("Id", 42))),
 
398
    ok.
 
399
 
 
400
%%-----------------------------------------------------------------
 
401
%% Test Case: struct
 
402
%% Description: 
 
403
%%-----------------------------------------------------------------
 
404
struct(doc) -> [];
 
405
struct(suite) -> [];
 
406
struct(_) ->
 
407
    ?line true = orber_tc:check_tc(orber_tc:struct("Id", "Name", ?ELIST)),
 
408
    ?line false = orber_tc:check_tc(orber_tc:struct(42, "Name", ?ELIST)),
 
409
    ?line false = orber_tc:check_tc(orber_tc:struct("Id", false, ?ELIST)),
 
410
    ?line false = orber_tc:check_tc(orber_tc:struct("Id", "Name", ?VELIST)),
 
411
    ?line false = orber_tc:check_tc(orber_tc:struct("Id", "Name", "wrong")),
 
412
    ?line code(orber_tc:struct("Id", "Name", ?ELIST)),
 
413
    ?line ?match(code(orber_tc:struct(42, "Name", ?ELIST))),
 
414
    ?line ?match(code(orber_tc:struct("Id", false, ?ELIST))),
 
415
    ?line ?match(code(orber_tc:struct("Id", "Name", ?VELIST))),
 
416
    ?line ?match(code(orber_tc:struct("Id", "Name", "wrong"))),
 
417
    ok.
 
418
 
 
419
%%-----------------------------------------------------------------
 
420
%% Test Case: union
 
421
%% Description: 
 
422
%%-----------------------------------------------------------------
 
423
union(doc) -> [];
 
424
union(suite) -> [];
 
425
union(_) ->
 
426
    ?line true = orber_tc:check_tc(orber_tc:union("Id", "Name", orber_tc:long(), 
 
427
                                                  -1, [{1, "long", orber_tc:long()},
 
428
                                                       {2, "longlong", orber_tc:long()}])),
 
429
    ?line false = orber_tc:check_tc(orber_tc:union("Id", "Name", orber_tc:long(), 
 
430
                                                   -1, ?ELIST)),
 
431
    ?line false = orber_tc:check_tc(orber_tc:union(42, "Name", orber_tc:long(), 
 
432
                                                   -1, [{1, "long", orber_tc:long()},
 
433
                                                        {2, "longlong", orber_tc:long()}])),
 
434
    ?line false = orber_tc:check_tc(orber_tc:union("Id", false, orber_tc:long(), 
 
435
                                                   -1, [{1, "long", orber_tc:long()},
 
436
                                                        {2, "longlong", orber_tc:long()}])),
 
437
    ?line false = orber_tc:check_tc(orber_tc:union("Id", "Name", bad_tc, 
 
438
                                                   -1, [{1, "long", orber_tc:long()},
 
439
                                                        {2, "longlong", orber_tc:long()}])),
 
440
    ?line false = orber_tc:check_tc(orber_tc:union("Id", "Name", orber_tc:long(), 
 
441
                                                   "wrong", [{1, "long", orber_tc:long()},
 
442
                                                             {2, "longlong", orber_tc:long()}])),
 
443
 
 
444
    ?line code(orber_tc:union("Id", "Name", orber_tc:long(), 
 
445
                              -1, [{1, "long", orber_tc:long()},
 
446
                                   {2, "longlong", orber_tc:long()}])),
 
447
    ok.
 
448
 
 
449
 
 
450
%%-----------------------------------------------------------------
 
451
%% Test Case: enum test
 
452
%% Description: 
 
453
%%-----------------------------------------------------------------
 
454
enum(doc) -> [];
 
455
enum(suite) -> [];
 
456
enum(_) ->
 
457
    ?line true = orber_tc:check_tc(orber_tc:enum("Id", "Name", 
 
458
                                                 ["E1", "E2", "E3"])),
 
459
    ?line false = orber_tc:check_tc(orber_tc:enum(42, "Name", 
 
460
                                                  ["E1", "E2", "E3"])),
 
461
    ?line false = orber_tc:check_tc(orber_tc:enum("Id", false, 
 
462
                                                  ["E1", "E2", "E3"])),
 
463
    ?line false = orber_tc:check_tc(orber_tc:enum("Id", "Name", 
 
464
                                                  ["E1", false, "E3"])),
 
465
    ?line code(orber_tc:enum("Id", "Name", ["E1", "E2", "E3"])),
 
466
    ?line ?match(code(orber_tc:enum(false, "Name", ["E1", "E2", "E3"]))),
 
467
    ?line ?match(code(orber_tc:enum("Id", 42, ["E1", "E2", "E3"]))),
 
468
    ?line ?match(code(orber_tc:enum("Id", "Name", ["E1", false, "E3"]))),
 
469
    ok.
 
470
 
 
471
%%-----------------------------------------------------------------
 
472
%% Test Case: string
 
473
%% Description: 
 
474
%%-----------------------------------------------------------------
 
475
string(doc) -> [];
 
476
string(suite) -> [];
 
477
string(_) ->
 
478
    ?line true = orber_tc:check_tc(orber_tc:string(0)),
 
479
    ?line true = orber_tc:check_tc(orber_tc:string(1)),
 
480
    ?line false = orber_tc:check_tc(orber_tc:string("wrong")),
 
481
    ?line code(orber_tc:string(0)),
 
482
    ?line code(orber_tc:string(1)),
 
483
    ?line ?match(code(orber_tc:string(-1))),
 
484
    ?line ?match(code(orber_tc:string(?ULONGMAX+1))),
 
485
    ?line ?match(code(orber_tc:string("wrong"))),
 
486
    ok.
 
487
 
 
488
%%-----------------------------------------------------------------
 
489
%% Test Case: wstring
 
490
%% Description: 
 
491
%%-----------------------------------------------------------------
 
492
wstring(doc) -> [];
 
493
wstring(suite) -> [];
 
494
wstring(_) ->
 
495
    ?line true = orber_tc:check_tc(orber_tc:wstring(0)),
 
496
    ?line true = orber_tc:check_tc(orber_tc:wstring(1)),
 
497
    ?line false = orber_tc:check_tc(orber_tc:wstring("wrong")),
 
498
    ?line code(orber_tc:wstring(0)),
 
499
    ?line code(orber_tc:wstring(1)),
 
500
    ?line ?match(code(orber_tc:wstring(-1))),
 
501
    ?line ?match(code(orber_tc:wstring(?ULONGMAX+1))),
 
502
    ?line ?match(code(orber_tc:wstring(false))),
 
503
    ok.
 
504
 
 
505
%%-----------------------------------------------------------------
 
506
%% Test Case: sequence
 
507
%% Description: 
 
508
%%-----------------------------------------------------------------
 
509
sequence(doc) -> [];
 
510
sequence(suite) -> [];
 
511
sequence(_) ->
 
512
    ?line true = orber_tc:check_tc(orber_tc:sequence(orber_tc:struct("Id", "Name", ?ELIST), 0)),
 
513
    ?line code(orber_tc:sequence(orber_tc:struct("Id", "Name", ?ELIST), 0)),
 
514
    ok.
 
515
 
 
516
%%-----------------------------------------------------------------
 
517
%% Test Case: array
 
518
%% Description: 
 
519
%%-----------------------------------------------------------------
 
520
array(doc) -> [];
 
521
array(suite) -> [];
 
522
array(_) ->
 
523
    ?line true = orber_tc:check_tc(orber_tc:array(orber_tc:struct("Id", "Name", ?ELIST), 1)),
 
524
    ?line code(orber_tc:array(orber_tc:struct("Id", "Name", ?ELIST), 1)),
 
525
    ok.
 
526
 
 
527
%%-----------------------------------------------------------------
 
528
%% Test Case: alias
 
529
%% Description: 
 
530
%%-----------------------------------------------------------------
 
531
alias(doc) -> [];
 
532
alias(suite) -> [];
 
533
alias(_) ->
 
534
    ?line true = orber_tc:check_tc(orber_tc:alias("Id", "Name", orber_tc:struct("Id", "Name", ?ELIST))),
 
535
    ?line false = orber_tc:check_tc(orber_tc:alias(false, "Name", orber_tc:struct("Id", "Name", ?ELIST))),
 
536
    ?line false = orber_tc:check_tc(orber_tc:alias("Id", 42, orber_tc:struct("Id", "Name", ?ELIST))),
 
537
    ?line false = orber_tc:check_tc(orber_tc:alias("Id", "Name", "wrong")),
 
538
    ?line code(orber_tc:alias("Id", "Name", orber_tc:struct("Id", "Name", ?ELIST))),
 
539
    ?line ?match(code(orber_tc:alias("Id", "Name", orber_tc:struct("Id", "Name", ?VELIST)))),
 
540
    ok.
 
541
 
 
542
%%-----------------------------------------------------------------
 
543
%% Test Case: exception
 
544
%% Description: 
 
545
%%-----------------------------------------------------------------
 
546
exception(doc) -> [];
 
547
exception(suite) -> [];
 
548
exception(_) ->
 
549
    ?line true = orber_tc:check_tc(orber_tc:exception("Id", "Name", ?ELIST)),
 
550
    ?line false = orber_tc:check_tc(orber_tc:exception(42, "Name", ?ELIST)),
 
551
    ?line false = orber_tc:check_tc(orber_tc:exception("Id", false, ?ELIST)),
 
552
    ?line false = orber_tc:check_tc(orber_tc:exception("Id", "Name", "wrong")),
 
553
    ?line code(orber_tc:exception("Id", "Name", ?ELIST)),
 
554
    ?line ?match(code(orber_tc:exception(42, "Name", ?ELIST))),
 
555
    ?line ?match(code(orber_tc:exception("Id", false, ?ELIST))),
 
556
    ?line ?match(code(orber_tc:exception("Id", "Name", "wrong"))),
 
557
 
 
558
    ok.
 
559
 
 
560
%%-----------------------------------------------------------------
 
561
%% Test Case: fixed
 
562
%% Description: 
 
563
%%-----------------------------------------------------------------
 
564
fixed(doc) -> [];
 
565
fixed(suite) -> [];
 
566
fixed(_) ->
 
567
    ?line true = orber_tc:check_tc(orber_tc:fixed(25, 2)),
 
568
    ?line code(orber_tc:fixed(25, 2)),
 
569
    ok.
 
570
 
 
571
%%-----------------------------------------------------------------
 
572
%% Test Case: value
 
573
%% Description: 
 
574
%%-----------------------------------------------------------------
 
575
value(doc) -> [];
 
576
value(suite) -> [];
 
577
value(_) ->
 
578
    ?line true = orber_tc:check_tc(orber_tc:value("Id", "Name", 42,
 
579
                                                  orber_tc:fixed(25, 2), ?VELIST)),
 
580
    ?line false = orber_tc:check_tc(orber_tc:value(42, "Name", 42,
 
581
                                                   orber_tc:fixed(25, 2), ?VELIST)),
 
582
    ?line false = orber_tc:check_tc(orber_tc:value("Id", 42, 42,
 
583
                                                   orber_tc:fixed(25, 2), ?VELIST)),
 
584
    ?line false = orber_tc:check_tc(orber_tc:value("Id", "Name", "wrong",
 
585
                                                   orber_tc:fixed(25, 2), ?VELIST)),
 
586
    ?line false = orber_tc:check_tc(orber_tc:value("Id", "Name", "42",
 
587
                                                   orber_tc:fixed(25, 2), ?VELIST)),
 
588
    ?line false = orber_tc:check_tc(orber_tc:value("Id", "Name", "42",
 
589
                                                   ?VELIST, ?VELIST)),
 
590
    ?line false = orber_tc:check_tc(orber_tc:value("Id", "Name", "42",
 
591
                                                   orber_tc:fixed(25, 2), false)),
 
592
 
 
593
    ?line code(orber_tc:value("Id", "Name", 42, orber_tc:long(), ?VELIST)),
 
594
    ok.
 
595
 
 
596
%%-----------------------------------------------------------------
 
597
%% Test Case: value_box
 
598
%% Description: 
 
599
%%-----------------------------------------------------------------
 
600
value_box(doc) -> [];
 
601
value_box(suite) -> [];
 
602
value_box(_) ->
 
603
    ?line true = orber_tc:check_tc(orber_tc:value_box("Id", "Name", 
 
604
                                                      orber_tc:fixed(25, 2))),
 
605
    ?line false = orber_tc:check_tc(orber_tc:value_box(42, "Name", 
 
606
                                                       orber_tc:fixed(25, 2))),
 
607
    ?line false = orber_tc:check_tc(orber_tc:value_box("Id", 42, 
 
608
                                                       orber_tc:fixed(25, 2))),
 
609
    ?line false = orber_tc:check_tc(orber_tc:value_box("Id", "Name", "wrong")),
 
610
    ?line code(orber_tc:value_box("Id", "Name", orber_tc:long())),
 
611
    ?line ?match(code(orber_tc:value_box(42, "Name", orber_tc:short()))),
 
612
    ?line ?match(code(orber_tc:value_box("Id", 42, orber_tc:char()))),
 
613
    ?line ?match(code(orber_tc:value_box("Id", "Name", false))),
 
614
    ok.
 
615
 
 
616
%%-----------------------------------------------------------------
 
617
%% Test Case: native
 
618
%% Description: 
 
619
%%-----------------------------------------------------------------
 
620
native(doc) -> [];
 
621
native(suite) -> [];
 
622
native(_) ->
 
623
    ?line true = orber_tc:check_tc(orber_tc:native("Id", "Name")),
 
624
    ?line false = orber_tc:check_tc(orber_tc:native(42, "Name")),
 
625
    ?line false = orber_tc:check_tc(orber_tc:native("Id", 42)),
 
626
    ?line code(orber_tc:native("Id", "Name")),
 
627
    ?line ?match(code(orber_tc:native(42, "Name"))),
 
628
    ?line ?match(code(orber_tc:native("Id", 42))),
 
629
    ok.
 
630
 
 
631
%%-----------------------------------------------------------------
 
632
%% Test Case: abstract_interface
 
633
%% Description: 
 
634
%%-----------------------------------------------------------------
 
635
abstract_interface(doc) -> [];
 
636
abstract_interface(suite) -> [];
 
637
abstract_interface(_) ->
 
638
    ?line true = orber_tc:check_tc(orber_tc:abstract_interface("RepId", "Name")),
 
639
    ?line false = orber_tc:check_tc(orber_tc:abstract_interface(false, "Name")),
 
640
    ?line false = orber_tc:check_tc(orber_tc:abstract_interface("RepId", 42)),
 
641
    ?line code(orber_tc:abstract_interface("RepId", "Name")),
 
642
    ?line ?match(code(orber_tc:abstract_interface(42, "Name"))),
 
643
    ?line ?match(code(orber_tc:abstract_interface("Id", 42))),
 
644
    ok.
 
645
 
 
646
 
 
647
 
 
648
%%-----------------------------------------------------------------
 
649
%% Test Case: indirection
 
650
%% Description: 
 
651
%%-----------------------------------------------------------------
 
652
indirection(doc) -> [];
 
653
indirection(suite) -> [];
 
654
indirection(_) ->
 
655
    ?line true = orber_tc:check_tc({'none', 42}),
 
656
    ok.
 
657
 
 
658
%%-----------------------------------------------------------------
 
659
%% Test Case: get_tc
 
660
%% Description: 
 
661
%%-----------------------------------------------------------------
 
662
get_tc(doc) -> [];
 
663
get_tc(suite) -> [];
 
664
get_tc(_) ->
 
665
    TC = 'CosNaming_Binding':tc(),
 
666
    ?line TC = orber_tc:get_tc({'CosNaming_Binding', 42}),
 
667
    ?line ?match(orber_tc:get_tc({'none', 42})),
 
668
    ok.
 
669
 
 
670
%%-----------------------------------------------------------------
 
671
%% MISC Operations
 
672
%%-----------------------------------------------------------------
 
673
code(Value) ->
 
674
    cdr_encode:enc_type({1,2}, tk_TypeCode, Value).