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

« back to all changes in this revision

Viewing changes to lib/asn1/test/asn1_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 2001-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
%%% Purpose : Test suite for the ASN.1 application
 
21
 
 
22
-module(asn1_SUITE).
 
23
-define(PER,'per').
 
24
-define(BER,'ber').
 
25
-define(ber_driver(Erule,Func),
 
26
        case Erule of
 
27
           ber_bin_v2 ->
 
28
                Func;
 
29
            _ -> ok
 
30
        end).
 
31
-define(per_optimize(Erule),
 
32
        case Erule of
 
33
           ber_bin_v2 ->[optimize];
 
34
           _ -> []
 
35
        end).
 
36
-define(per_bit_opt(FuncCall),
 
37
        case ?BER of
 
38
           ber_bin_v2 -> FuncCall;
 
39
%          _ -> {skip,"only for bit optimized per_bin"}
 
40
           _ -> ok
 
41
        end).
 
42
-define(uper_bin(FuncCall),
 
43
        case ?PER of
 
44
           per -> FuncCall;
 
45
           _ -> ok
 
46
        end).
 
47
 
 
48
-compile(export_all).
 
49
%%-export([Function/Arity, ...]).
 
50
 
 
51
-include_lib("test_server/include/test_server.hrl").
 
52
 
 
53
%% records used by test-case default
 
54
-record('Def1',{ bool0, 
 
55
                 bool1 = asn1_DEFAULT, 
 
56
                 bool2 = asn1_DEFAULT, 
 
57
                 bool3 = asn1_DEFAULT}).
 
58
 
 
59
%-record('Def2',{
 
60
%bool10, bool11 = asn1_DEFAULT, bool12 = asn1_DEFAULT, bool13}).
 
61
 
 
62
%-record('Def3',{
 
63
%bool30 = asn1_DEFAULT, bool31 = asn1_DEFAULT, bool32 = asn1_DEFAULT, bool33 = asn1_DEFAULT}).
 
64
 
 
65
suite() -> [{ct_hooks,[ts_install_cth]}].
 
66
 
 
67
all() -> 
 
68
    [{group, compile}, parse, default_per, default_ber,
 
69
     default_per_opt, per, {group, ber}, testPrim,
 
70
     testPrimStrings, testPrimExternal, testChoPrim,
 
71
     testChoExtension, testChoExternal, testChoOptional,
 
72
     testChoOptionalImplicitTag, testChoRecursive,
 
73
     testChoTypeRefCho, testChoTypeRefPrim,
 
74
     testChoTypeRefSeq, testChoTypeRefSet, testDef, testOpt,
 
75
     testSeqDefault, testSeqExtension, testSeqExternal,
 
76
     testSeqOptional, testSeqPrim, testSeqTag,
 
77
     testSeqTypeRefCho, testSeqTypeRefPrim,
 
78
     testSeqTypeRefSeq, testSeqTypeRefSet, testSeqOf,
 
79
     testSeqOfIndefinite, testSeqOfCho, testSeqOfExternal,
 
80
     testSetDefault, testSetExtension,
 
81
     testExtensionAdditionGroup, testSetExternal,
 
82
     testSeqOfTag, testSetOptional, testSetPrim, testSetTag,
 
83
     testSetTypeRefCho, testSetTypeRefPrim,
 
84
     testSetTypeRefSeq, testSetTypeRefSet, testSetOf,
 
85
     testSetOfCho, testSetOfExternal, testSetOfTag,
 
86
     testEnumExt, value_test, testSeq2738, constructed,
 
87
     ber_decode_error, h323test, testSeqIndefinite,
 
88
     testSetIndefinite, testChoiceIndefinite,
 
89
     per_GeneralString, per_open_type, testInfObjectClass,
 
90
     testParameterizedInfObj, testMergeCompile, testobj,
 
91
     testDeepTConstr, testConstraints, testInvokeMod,
 
92
     testExport, testImport, testCompactBitString,
 
93
     testMegaco, testParamBasic, testMvrasn6,
 
94
     testContextSwitchingTypes, testTypeValueNotation,
 
95
     testOpenTypeImplicitTag, duplicate_tags, rtUI, testROSE,
 
96
     testINSTANCE_OF, testTCAP, testDER, specialized_decodes,
 
97
     special_decode_performance, test_driver_load,
 
98
     test_ParamTypeInfObj, test_WS_ParamClass,
 
99
     test_Defed_ObjectIdentifier, testSelectionType,
 
100
     testSSLspecs, testNortel, test_undecoded_rest,
 
101
     test_inline, testTcapsystem, testNBAPsystem,
 
102
     test_compile_options, testDoubleEllipses,
 
103
     test_modified_x420, testX420, test_x691, ticket_6143,
 
104
     testExtensionAdditionGroup] ++ common() ++ particular().
 
105
 
 
106
groups() -> 
 
107
    [{option_tests, [],
 
108
      [test_compile_options, ticket_6143]},
 
109
     {infobj, [],
 
110
      [testInfObjectClass, testParameterizedInfObj,
 
111
       testMergeCompile, testobj, testDeepTConstr]},
 
112
     {performance, [],
 
113
      [testTimer_ber, testTimer_ber_opt_driver, testTimer_per,
 
114
       testTimer_per_opt, testTimer_uper_bin]},
 
115
     {bugs, [],
 
116
      [test_ParamTypeInfObj, test_WS_ParamClass,
 
117
       test_Defed_ObjectIdentifier]},
 
118
     {compile, [],
 
119
      [c_syntax, c_string_per, c_string_ber,
 
120
       c_implicit_before_choice]},
 
121
     {ber, [],
 
122
      [ber_choiceinseq, ber_optional, ber_optional_keyed_list,
 
123
       ber_other]},
 
124
     {app_test, [], [{asn1_app_test, all}]},
 
125
     {appup_test, [], [{asn1_appup_test, all}]}].
 
126
 
 
127
init_per_suite(Config) ->
 
128
    Config.
 
129
 
 
130
end_per_suite(_Config) ->
 
131
    ok.
 
132
 
 
133
init_per_group(_GroupName, Config) ->
 
134
        Config.
 
135
 
 
136
end_per_group(_GroupName, Config) ->
 
137
        Config.
 
138
 
 
139
 
 
140
%all(suite) -> [test_inline,testNBAPsystem,test_compile_options,ticket_6143].
 
141
 
 
142
 
 
143
init_per_testcase(Func,Config) ->
 
144
    %%?line test_server:format("Func: ~p~n",[Func]),
 
145
    ?line {ok, _} = file:read_file_info(filename:join([?config(priv_dir,Config)])),
 
146
    ?line code:add_patha(?config(priv_dir,Config)),
 
147
    Dog=
 
148
    case Func of
 
149
       testX420 ->
 
150
           test_server:timetrap({minutes,60}); % 60 minutes
 
151
       _ ->
 
152
           test_server:timetrap({minutes,30}) % 60 minutes
 
153
    end,
 
154
%%    Dog=test_server:timetrap(1800000), % 30 minutes
 
155
    [{watchdog, Dog}|Config].
 
156
 
 
157
end_per_testcase(_Func,Config) ->
 
158
          Dog=?config(watchdog, Config),
 
159
          test_server:timetrap_cancel(Dog).
 
160
 
 
161
 
 
162
testPrim(suite) -> [];
 
163
testPrim(Config) ->
 
164
    ?line testPrim:compile(Config,?BER,[]),
 
165
    ?line testPrim_cases(?BER),
 
166
    ?line ?ber_driver(?BER,testPrim:compile(Config,?BER,[driver])),
 
167
    ?line ?ber_driver(?BER,testPrim_cases(?BER)),
 
168
    ?line testPrim:compile(Config,?PER,[]),
 
169
    ?line testPrim_cases(?PER),
 
170
    ?line ?per_bit_opt(testPrim:compile(Config,?PER,[optimize])),
 
171
    ?line ?per_bit_opt(testPrim_cases(?PER)),
 
172
    ?line ?uper_bin(testPrim:compile(Config,uper_bin,[])),
 
173
    ?line ?uper_bin(testPrim_cases(uper_bin)),
 
174
    ?line testPrim:compile(Config,?PER,[optimize]),
 
175
    ?line testPrim_cases(?PER).
 
176
 
 
177
testPrim_cases(Rules) ->
 
178
    ?line testPrim:bool(Rules),
 
179
    ?line testPrim:int(Rules),
 
180
    ?line testPrim:enum(Rules),
 
181
    ?line testPrim:obj_id(Rules),
 
182
    ?line testPrim:rel_oid(Rules),
 
183
    ?line testPrim:null(Rules),
 
184
    ?line testPrim:real(Rules).
 
185
 
 
186
 
 
187
testCompactBitString(suite) -> [];
 
188
testCompactBitString(Config) -> 
 
189
 
 
190
    ?line testCompactBitString:compile(Config,?BER,[compact_bit_string]),
 
191
    ?line testCompactBitString:compact_bit_string(?BER),
 
192
 
 
193
    ?line ?ber_driver(?BER,testCompactBitString:compile(Config,?BER,[compact_bit_string,driver])),
 
194
    ?line ?ber_driver(?BER,testCompactBitString:compact_bit_string(?BER)),
 
195
 
 
196
    ?line testCompactBitString:compile(Config,?PER,[compact_bit_string]),
 
197
    ?line testCompactBitString:compact_bit_string(?PER),
 
198
    ?line testCompactBitString:bit_string_unnamed(?PER),
 
199
 
 
200
    ?line ?per_bit_opt(testCompactBitString:compile(Config,?PER,
 
201
                                        [compact_bit_string,optimize])),
 
202
    ?line ?per_bit_opt(testCompactBitString:compact_bit_string(?PER)),
 
203
    ?line ?per_bit_opt(testCompactBitString:bit_string_unnamed(?PER)),
 
204
    ?line ?per_bit_opt(testCompactBitString:ticket_7734(?PER)),
 
205
 
 
206
    ?line ?uper_bin(testCompactBitString:compile(Config,uper_bin,
 
207
                                        [compact_bit_string])),
 
208
    ?line ?uper_bin(testCompactBitString:compact_bit_string(uper_bin)),
 
209
    ?line ?uper_bin(testCompactBitString:bit_string_unnamed(uper_bin)),
 
210
 
 
211
    ?line testCompactBitString:compile(Config,?PER,[optimize,compact_bit_string]),
 
212
    ?line testCompactBitString:compact_bit_string(?PER),
 
213
    ?line testCompactBitString:bit_string_unnamed(?PER),
 
214
 
 
215
    ?line testCompactBitString:otp_4869(?PER).
 
216
 
 
217
 
 
218
testPrimStrings(suite) -> [];
 
219
testPrimStrings(Config) ->
 
220
 
 
221
    ?line testPrimStrings:compile(Config,?BER,[]),
 
222
    ?line testPrimStrings_cases(?BER),
 
223
    ?line testPrimStrings:more_strings(?BER), %% these are not implemented in per yet
 
224
    ?line ?ber_driver(?BER,testPrimStrings:compile(Config,?BER,[driver])),
 
225
    ?line ?ber_driver(?BER,testPrimStrings_cases(?BER)),
 
226
    ?line ?ber_driver(?BER,testPrimStrings:more_strings(?BER)),
 
227
 
 
228
    ?line testPrimStrings:compile(Config,?PER,[]),
 
229
    ?line testPrimStrings_cases(?PER),
 
230
 
 
231
    ?line ?per_bit_opt(testPrimStrings:compile(Config,?PER,[optimize])),
 
232
    ?line ?per_bit_opt(testPrimStrings_cases(?PER)),
 
233
 
 
234
    ?line ?uper_bin(testPrimStrings:compile(Config,uper_bin,[])),
 
235
    ?line ?uper_bin(testPrimStrings_cases(uper_bin)),
 
236
 
 
237
    ?line testPrimStrings:compile(Config,?PER,[optimize]),
 
238
    ?line testPrimStrings_cases(?PER).
 
239
 
 
240
testPrimStrings_cases(Rules) ->
 
241
    ?line testPrimStrings:bit_string(Rules),
 
242
    ?line testPrimStrings:bit_string_unnamed(Rules),
 
243
    ?line testPrimStrings:octet_string(Rules),
 
244
    ?line testPrimStrings:numeric_string(Rules),
 
245
    ?line testPrimStrings:other_strings(Rules),
 
246
    ?line testPrimStrings:universal_string(Rules),
 
247
    ?line testPrimStrings:bmp_string(Rules),
 
248
    ?line testPrimStrings:times(Rules),
 
249
    ?line testPrimStrings:utf8_string(Rules).
 
250
    
 
251
 
 
252
 
 
253
testPrimExternal(suite) -> [];
 
254
testPrimExternal(Config) ->
 
255
 
 
256
    ?line testExternal:compile(Config,?BER,[]),
 
257
    ?line testPrimExternal:compile(Config,?BER,[]),
 
258
    ?line testPrimExternal_cases(?BER),
 
259
 
 
260
    ?line ?ber_driver(?BER,testExternal:compile(Config,?BER,[driver])),
 
261
    ?line ?ber_driver(?BER,testPrimExternal:compile(Config,?BER,[driver])),
 
262
    ?line ?ber_driver(?BER,testPrimExternal_cases(?BER)),
 
263
    
 
264
    ?line testExternal:compile(Config,?PER,[]),     
 
265
    ?line testPrimExternal:compile(Config,?PER,[]), 
 
266
    ?line testPrimExternal_cases(?PER),
 
267
 
 
268
    ?line ?per_bit_opt(testExternal:compile(Config,?PER,[optimize])),     
 
269
    ?line ?per_bit_opt(testPrimExternal:compile(Config,?PER,[optimize])), 
 
270
    ?line ?per_bit_opt(testPrimExternal_cases(?PER)),
 
271
 
 
272
    ?line ?uper_bin(testExternal:compile(Config,uper_bin,[])),     
 
273
    ?line ?uper_bin(testPrimExternal:compile(Config,uper_bin,[])), 
 
274
    ?line ?uper_bin(testPrimExternal_cases(uper_bin)),
 
275
 
 
276
    ?line testExternal:compile(Config,?PER,[optimize]),     
 
277
    ?line testPrimExternal:compile(Config,?PER,[optimize]), 
 
278
    ?line testPrimExternal_cases(?PER).
 
279
 
 
280
testPrimExternal_cases(Rules) ->
 
281
    ?line testPrimExternal:external(Rules).
 
282
 
 
283
 
 
284
 
 
285
 
 
286
testChoPrim(suite) -> [];
 
287
testChoPrim(Config) ->
 
288
 
 
289
    ?line testChoPrim:compile(Config,?BER,[]),
 
290
    ?line testChoPrim_cases(?BER),
 
291
 
 
292
    ?line ?ber_driver(?BER,testChoPrim:compile(Config,?BER,[driver])),
 
293
    ?line ?ber_driver(?BER,testChoPrim_cases(?BER)),
 
294
 
 
295
    ?line testChoPrim:compile(Config,?PER,[]), 
 
296
    ?line testChoPrim_cases(?PER),
 
297
 
 
298
    ?line ?per_bit_opt(testChoPrim:compile(Config,?PER,[optimize])), 
 
299
    ?line ?per_bit_opt(testChoPrim_cases(?PER)),
 
300
 
 
301
    ?line ?uper_bin(testChoPrim:compile(Config,uper_bin,[])), 
 
302
    ?line ?uper_bin(testChoPrim_cases(uper_bin)),
 
303
 
 
304
    ?line testChoPrim:compile(Config,?PER,[optimize]), 
 
305
    ?line testChoPrim_cases(?PER).
 
306
 
 
307
testChoPrim_cases(Rules) ->
 
308
    ?line testChoPrim:bool(Rules),
 
309
    ?line testChoPrim:int(Rules).
 
310
 
 
311
 
 
312
 
 
313
testChoExtension(suite) -> [];
 
314
testChoExtension(Config) ->
 
315
 
 
316
    ?line testChoExtension:compile(Config,?BER,[]),
 
317
    ?line testChoExtension_cases(?BER),          
 
318
 
 
319
    ?line ?ber_driver(?BER,testChoExtension:compile(Config,?BER,[driver])),
 
320
    ?line ?ber_driver(?BER,testChoExtension_cases(?BER)),
 
321
 
 
322
    ?line testChoExtension:compile(Config,?PER,[]),
 
323
    ?line testChoExtension_cases(?PER),          
 
324
 
 
325
    ?line ?per_bit_opt(testChoExtension:compile(Config,?PER,[optimize])),
 
326
    ?line ?per_bit_opt(testChoExtension_cases(?PER)),
 
327
 
 
328
    ?line ?uper_bin(testChoExtension:compile(Config,uper_bin,[])),
 
329
    ?line ?uper_bin(testChoExtension_cases(uper_bin)),
 
330
 
 
331
    ?line testChoExtension:compile(Config,?PER,[optimize]),
 
332
    ?line testChoExtension_cases(?PER).          
 
333
 
 
334
testChoExtension_cases(Rules) ->
 
335
    ?line testChoExtension:extension(Rules).
 
336
 
 
337
 
 
338
 
 
339
testChoExternal(suite) -> [];
 
340
testChoExternal(Config) ->
 
341
 
 
342
    ?line testExternal:compile(Config,?BER,[]),
 
343
    ?line testChoExternal:compile(Config,?BER,[]),
 
344
    ?line testChoExternal_cases(?BER),
 
345
 
 
346
    ?line ?ber_driver(?BER,testExternal:compile(Config,?BER,[driver])),
 
347
    ?line ?ber_driver(?BER,testChoExternal:compile(Config,?BER,[driver])),
 
348
    ?line ?ber_driver(?BER,testChoExternal_cases(?BER)),
 
349
 
 
350
    ?line testExternal:compile(Config,?PER,[]),
 
351
    ?line testChoExternal:compile(Config,?PER,[]), 
 
352
    ?line testChoExternal_cases(?PER),
 
353
 
 
354
    ?line ?per_bit_opt(testExternal:compile(Config,?PER,[optimize])),
 
355
    ?line ?per_bit_opt(testChoExternal:compile(Config,?PER,[optimize])), 
 
356
    ?line ?per_bit_opt(testChoExternal_cases(?PER)),
 
357
 
 
358
    ?line ?uper_bin(testExternal:compile(Config,uper_bin,[])),
 
359
    ?line ?uper_bin(testChoExternal:compile(Config,uper_bin,[])), 
 
360
    ?line ?uper_bin(testChoExternal_cases(uper_bin)),
 
361
 
 
362
    ?line testExternal:compile(Config,?PER,[optimize]),
 
363
    ?line testChoExternal:compile(Config,?PER,[optimize]), 
 
364
    ?line testChoExternal_cases(?PER).
 
365
 
 
366
 
 
367
testChoExternal_cases(Rules) ->
 
368
    ?line testChoExternal:external(Rules).
 
369
 
 
370
 
 
371
 
 
372
testChoOptional(suite) -> [];
 
373
testChoOptional(Config) ->
 
374
 
 
375
    ?line testChoOptional:compile(Config,?BER,[]),
 
376
    ?line testChoOptional_cases(?BER),
 
377
 
 
378
    ?line ?ber_driver(?BER,testChoOptional:compile(Config,?BER,[driver])),
 
379
    ?line ?ber_driver(?BER,testChoOptional_cases(?BER)),
 
380
 
 
381
    ?line testChoOptional:compile(Config,?PER,[]), 
 
382
    ?line testChoOptional_cases(?PER),
 
383
 
 
384
    ?line ?per_bit_opt(testChoOptional:compile(Config,?PER,[optimize])), 
 
385
    ?line ?per_bit_opt(testChoOptional_cases(?PER)),
 
386
 
 
387
    ?line ?uper_bin(testChoOptional:compile(Config,uper_bin,[])), 
 
388
    ?line ?uper_bin(testChoOptional_cases(uper_bin)),
 
389
 
 
390
    ?line testChoOptional:compile(Config,?PER,[optimize]), 
 
391
    ?line testChoOptional_cases(?PER).
 
392
 
 
393
testChoOptional_cases(Rules) ->
 
394
    ?line testChoOptional:optional(Rules).
 
395
 
 
396
testChoOptionalImplicitTag(suite) -> [];
 
397
testChoOptionalImplicitTag(Config) ->
 
398
    %% Only meaningful for ?BER
 
399
    ?line testChoOptionalImplicitTag:compile(Config,?BER),
 
400
    ?line testChoOptionalImplicitTag:optional(?BER).
 
401
 
 
402
 
 
403
testChoRecursive(suite) -> [];
 
404
testChoRecursive(Config) ->
 
405
 
 
406
    ?line testChoRecursive:compile(Config,?BER,[]),
 
407
    ?line testChoRecursive_cases(?BER),
 
408
 
 
409
    ?line ?ber_driver(?BER,testChoRecursive:compile(Config,?BER,[driver])),
 
410
    ?line ?ber_driver(?BER,testChoRecursive_cases(?BER)),
 
411
 
 
412
    ?line testChoRecursive:compile(Config,?PER,[]), 
 
413
    ?line testChoRecursive_cases(?PER),
 
414
 
 
415
    ?line ?per_bit_opt(testChoRecursive:compile(Config,?PER,[optimize])), 
 
416
    ?line ?per_bit_opt(testChoRecursive_cases(?PER)),
 
417
 
 
418
    ?line ?uper_bin(testChoRecursive:compile(Config,uper_bin,[])), 
 
419
    ?line ?uper_bin(testChoRecursive_cases(uper_bin)),
 
420
 
 
421
    ?line testChoRecursive:compile(Config,?PER,[optimize]), 
 
422
    ?line testChoRecursive_cases(?PER).
 
423
 
 
424
testChoRecursive_cases(Rules) ->
 
425
    ?line testChoRecursive:recursive(Rules).
 
426
 
 
427
 
 
428
 
 
429
testChoTypeRefCho(suite) -> [];
 
430
testChoTypeRefCho(Config) ->
 
431
 
 
432
    ?line testChoTypeRefCho:compile(Config,?BER,[]),
 
433
    ?line testChoTypeRefCho_cases(?BER),
 
434
 
 
435
    ?line ?ber_driver(?BER,testChoTypeRefCho:compile(Config,?BER,[driver])),
 
436
    ?line ?ber_driver(?BER,testChoTypeRefCho_cases(?BER)),
 
437
 
 
438
    ?line testChoTypeRefCho:compile(Config,?PER,[]), 
 
439
    ?line testChoTypeRefCho_cases(?PER),
 
440
 
 
441
    ?line ?per_bit_opt(testChoTypeRefCho:compile(Config,?PER,[optimize])), 
 
442
    ?line ?per_bit_opt(testChoTypeRefCho_cases(?PER)),
 
443
 
 
444
    ?line ?uper_bin(testChoTypeRefCho:compile(Config,uper_bin,[])), 
 
445
    ?line ?uper_bin(testChoTypeRefCho_cases(uper_bin)),
 
446
 
 
447
    ?line testChoTypeRefCho:compile(Config,?PER,[optimize]), 
 
448
    ?line testChoTypeRefCho_cases(?PER).
 
449
 
 
450
testChoTypeRefCho_cases(Rules) ->
 
451
    ?line testChoTypeRefCho:choice(Rules).
 
452
 
 
453
 
 
454
 
 
455
testChoTypeRefPrim(suite) -> [];
 
456
testChoTypeRefPrim(Config) ->
 
457
 
 
458
    ?line testChoTypeRefPrim:compile(Config,?BER,[]),
 
459
    ?line testChoTypeRefPrim_cases(?BER),
 
460
 
 
461
    ?line ?ber_driver(?BER,testChoTypeRefPrim:compile(Config,?BER,[driver])),
 
462
    ?line ?ber_driver(?BER,testChoTypeRefPrim_cases(?BER)),
 
463
 
 
464
    ?line testChoTypeRefPrim:compile(Config,?PER,[]), 
 
465
    ?line testChoTypeRefPrim_cases(?PER),
 
466
 
 
467
    ?line ?per_bit_opt(testChoTypeRefPrim:compile(Config,?PER,[optimize])), 
 
468
    ?line ?per_bit_opt(testChoTypeRefPrim_cases(?PER)),
 
469
 
 
470
    ?line ?uper_bin(testChoTypeRefPrim:compile(Config,uper_bin,[])), 
 
471
    ?line ?uper_bin(testChoTypeRefPrim_cases(uper_bin)),
 
472
 
 
473
    ?line testChoTypeRefPrim:compile(Config,?PER,[optimize]), 
 
474
    ?line testChoTypeRefPrim_cases(?PER).
 
475
 
 
476
testChoTypeRefPrim_cases(Rules) ->
 
477
    ?line testChoTypeRefPrim:prim(Rules).
 
478
 
 
479
 
 
480
 
 
481
testChoTypeRefSeq(suite) -> [];
 
482
testChoTypeRefSeq(Config) ->
 
483
 
 
484
    ?line testChoTypeRefSeq:compile(Config,?BER,[]),
 
485
    ?line testChoTypeRefSeq_cases(?BER),
 
486
 
 
487
    ?line ?ber_driver(?BER,testChoTypeRefSeq:compile(Config,?BER,[driver])),
 
488
    ?line ?ber_driver(?BER,testChoTypeRefSeq_cases(?BER)),
 
489
 
 
490
    ?line testChoTypeRefSeq:compile(Config,?PER,[]), 
 
491
    ?line testChoTypeRefSeq_cases(?PER),
 
492
 
 
493
    ?line ?per_bit_opt(testChoTypeRefSeq:compile(Config,?PER,[optimize])), 
 
494
    ?line ?per_bit_opt(testChoTypeRefSeq_cases(?PER)),
 
495
 
 
496
    ?line ?uper_bin(testChoTypeRefSeq:compile(Config,uper_bin,[])), 
 
497
    ?line ?uper_bin(testChoTypeRefSeq_cases(uper_bin)),
 
498
 
 
499
    ?line testChoTypeRefSeq:compile(Config,?PER,[optimize]), 
 
500
    ?line testChoTypeRefSeq_cases(?PER).
 
501
 
 
502
testChoTypeRefSeq_cases(Rules) ->
 
503
    ?line testChoTypeRefSeq:seq(Rules).
 
504
 
 
505
 
 
506
 
 
507
testChoTypeRefSet(suite) -> [];
 
508
testChoTypeRefSet(Config) ->
 
509
 
 
510
    ?line testChoTypeRefSet:compile(Config,?BER,[]),
 
511
    ?line testChoTypeRefSet_cases(?BER),
 
512
 
 
513
    ?line ?ber_driver(?BER,testChoTypeRefSet:compile(Config,?BER,[driver])),
 
514
    ?line ?ber_driver(?BER,testChoTypeRefSet_cases(?BER)),
 
515
 
 
516
    ?line testChoTypeRefSet:compile(Config,?PER,[]), 
 
517
    ?line testChoTypeRefSet_cases(?PER),
 
518
 
 
519
    ?line ?per_bit_opt(testChoTypeRefSet:compile(Config,?PER,[optimize])), 
 
520
    ?line ?per_bit_opt(testChoTypeRefSet_cases(?PER)),
 
521
 
 
522
    ?line ?uper_bin(testChoTypeRefSet:compile(Config,uper_bin,[])), 
 
523
    ?line ?uper_bin(testChoTypeRefSet_cases(uper_bin)),
 
524
 
 
525
    ?line testChoTypeRefSet:compile(Config,?PER,[optimize]), 
 
526
    ?line testChoTypeRefSet_cases(?PER).
 
527
 
 
528
testChoTypeRefSet_cases(Rules) ->
 
529
    ?line testChoTypeRefSet:set(Rules).
 
530
 
 
531
 
 
532
 
 
533
testDef(suite) -> [];
 
534
testDef(Config) ->
 
535
 
 
536
    ?line testDef:compile(Config,?BER,[]),
 
537
    ?line testDef_cases(?BER),
 
538
 
 
539
    ?line ?ber_driver(?BER,testDef:compile(Config,?BER,[driver])),
 
540
    ?line ?ber_driver(?BER,testDef_cases(?BER)),
 
541
 
 
542
    ?line testDef:compile(Config,?PER,[]), 
 
543
    ?line testDef_cases(?PER),
 
544
 
 
545
    ?line ?per_bit_opt(testDef:compile(Config,?PER,[optimize])), 
 
546
    ?line ?per_bit_opt(testDef_cases(?PER)),
 
547
 
 
548
    ?line ?uper_bin(testDef:compile(Config,uper_bin,[])), 
 
549
    ?line ?uper_bin(testDef_cases(uper_bin)),
 
550
 
 
551
    ?line testDef:compile(Config,?PER,[optimize]), 
 
552
    ?line testDef_cases(?PER).
 
553
 
 
554
testDef_cases(Rules) ->
 
555
    ?line testDef:main(Rules).
 
556
 
 
557
 
 
558
 
 
559
testOpt(suite) -> [];
 
560
testOpt(Config) ->
 
561
 
 
562
    ?line testOpt:compile(Config,?BER),
 
563
    ?line testOpt_cases(?BER),
 
564
 
 
565
    ?line testOpt:compile(Config,?PER), 
 
566
    ?line testOpt_cases(?PER).          
 
567
 
 
568
testOpt_cases(Rules) ->
 
569
    ?line testOpt:main(Rules).
 
570
 
 
571
 
 
572
testEnumExt(suite) -> [];
 
573
testEnumExt(Config) ->
 
574
 
 
575
    ?line testEnumExt:compile(Config,?BER,[]),
 
576
    ?line testEnumExt:main(?BER),
 
577
 
 
578
    ?line ?ber_driver(?BER,testEnumExt:compile(Config,?BER,[driver])),
 
579
    ?line ?ber_driver(?BER,testEnumExt:main(?BER)),
 
580
 
 
581
    ?line testEnumExt:compile(Config,?PER,[]),
 
582
    ?line testEnumExt:main(?PER),
 
583
 
 
584
    ?line ?per_bit_opt(testEnumExt:compile(Config,?PER,[optimize])),
 
585
    ?line ?per_bit_opt(testEnumExt:main(?PER)),
 
586
 
 
587
    ?line ?uper_bin(testEnumExt:compile(Config,uper_bin,[])),
 
588
    ?line ?uper_bin(testEnumExt:main(uper_bin)),
 
589
 
 
590
    ?line testEnumExt:compile(Config,?PER,[optimize]),
 
591
    ?line testEnumExt:main(?PER).
 
592
 
 
593
testSeqDefault(doc) -> ["Test of OTP-2523 ENUMERATED with extensionmark."];
 
594
testSeqDefault(suite) -> [];
 
595
testSeqDefault(Config) ->
 
596
 
 
597
    ?line testSeqDefault:compile(Config,?BER,[]),
 
598
    ?line testSeqDefault_cases(?BER),
 
599
 
 
600
    ?line ?ber_driver(?BER,testSeqDefault:compile(Config,?BER,[driver])),
 
601
    ?line ?ber_driver(?BER,testSeqDefault_cases(?BER)),
 
602
 
 
603
    ?line testSeqDefault:compile(Config,?PER,[]), 
 
604
    ?line testSeqDefault_cases(?PER),
 
605
 
 
606
    ?line ?per_bit_opt(testSeqDefault:compile(Config,?PER,[optimize])), 
 
607
    ?line ?per_bit_opt(testSeqDefault_cases(?PER)),
 
608
 
 
609
    ?line ?uper_bin(testSeqDefault:compile(Config,uper_bin,[])), 
 
610
    ?line ?uper_bin(testSeqDefault_cases(uper_bin)),
 
611
 
 
612
    ?line testSeqDefault:compile(Config,?PER,[optimize]), 
 
613
    ?line testSeqDefault_cases(?PER).
 
614
 
 
615
testSeqDefault_cases(Rules) ->
 
616
    ?line testSeqDefault:main(Rules).
 
617
 
 
618
 
 
619
 
 
620
testSeqExtension(suite) -> [];
 
621
testSeqExtension(Config) ->
 
622
 
 
623
    ?line testExternal:compile(Config,?BER,[]),
 
624
    ?line testSeqExtension:compile(Config,?BER,[]),
 
625
    ?line testSeqExtension_cases(?BER),
 
626
 
 
627
    ?line ?ber_driver(?BER,testExternal:compile(Config,?BER,[driver])),
 
628
    ?line ?ber_driver(?BER,testSeqExtension:compile(Config,?BER,[driver])),
 
629
    ?line ?ber_driver(?BER,testSeqExtension_cases(?BER)).
 
630
 
 
631
testSeqExtension_cases(Rules) ->
 
632
    ?line testSeqExtension:main(Rules).
 
633
 
 
634
 
 
635
 
 
636
testSeqExternal(suite) -> [];
 
637
testSeqExternal(Config) ->
 
638
 
 
639
    ?line testExternal:compile(Config,?BER,[]),
 
640
    ?line testSeqExternal:compile(Config,?BER,[]),
 
641
    ?line testSeqExternal_cases(?BER),
 
642
 
 
643
    ?line ?ber_driver(?BER,testExternal:compile(Config,?BER,[driver])),
 
644
    ?line ?ber_driver(?BER,testSeqExternal:compile(Config,?BER,[driver])),
 
645
    ?line ?ber_driver(?BER,testSeqExternal_cases(?BER)).
 
646
 
 
647
testSeqExternal_cases(Rules) ->
 
648
    ?line testSeqExternal:main(Rules).
 
649
 
 
650
 
 
651
testSeqOptional(suite) -> [];
 
652
testSeqOptional(Config) ->
 
653
 
 
654
    ?line testSeqOptional:compile(Config,?BER,[]),
 
655
    ?line testSeqOptional_cases(?BER),
 
656
 
 
657
    ?line ?ber_driver(?BER,testSeqOptional:compile(Config,?BER,[driver])),
 
658
    ?line ?ber_driver(?BER,testSeqOptional_cases(?BER)),
 
659
 
 
660
    ?line testSeqOptional:compile(Config,?PER,[]), 
 
661
    ?line testSeqOptional_cases(?PER),
 
662
 
 
663
    ?line ?per_bit_opt(testSeqOptional:compile(Config,?PER,[optimize])), 
 
664
    ?line ?per_bit_opt(testSeqOptional_cases(?PER)),
 
665
 
 
666
    ?line ?uper_bin(testSeqOptional:compile(Config,uper_bin,[])), 
 
667
    ?line ?uper_bin(testSeqOptional_cases(uper_bin)),
 
668
 
 
669
    ?line testSeqOptional:compile(Config,?PER,[optimize]), 
 
670
    ?line testSeqOptional_cases(?PER).
 
671
 
 
672
testSeqOptional_cases(Rules) ->
 
673
    ?line testSeqOptional:main(Rules).
 
674
 
 
675
 
 
676
 
 
677
testSeqPrim(suite) -> [];
 
678
testSeqPrim(Config) ->
 
679
 
 
680
    ?line testSeqPrim:compile(Config,?BER,[]),
 
681
    ?line testSeqPrim_cases(?BER),
 
682
 
 
683
    ?line ?ber_driver(?BER,testSeqPrim:compile(Config,?BER,[driver])),
 
684
    ?line ?ber_driver(?BER,testSeqPrim_cases(?BER)),
 
685
 
 
686
    ?line testSeqPrim:compile(Config,?PER,[]), 
 
687
    ?line testSeqPrim_cases(?PER),
 
688
 
 
689
    ?line ?per_bit_opt(testSeqPrim:compile(Config,?PER,[optimize])), 
 
690
    ?line ?per_bit_opt(testSeqPrim_cases(?PER)),
 
691
 
 
692
    ?line ?uper_bin(testSeqPrim:compile(Config,uper_bin,[])), 
 
693
    ?line ?uper_bin(testSeqPrim_cases(uper_bin)),
 
694
 
 
695
    ?line testSeqPrim:compile(Config,?PER,[optimize]), 
 
696
    ?line testSeqPrim_cases(?PER).
 
697
 
 
698
testSeqPrim_cases(Rules) ->
 
699
    ?line testSeqPrim:main(Rules).
 
700
 
 
701
 
 
702
testSeq2738(doc) -> ["Test of OTP-2738 Detect corrupt optional component."];
 
703
testSeq2738(suite) -> [];
 
704
testSeq2738(Config) ->
 
705
 
 
706
    ?line testSeq2738:compile(Config,?BER,[]),
 
707
    ?line testSeq2738_cases(?BER),
 
708
 
 
709
    ?line ?ber_driver(?BER,testSeq2738:compile(Config,?BER,[driver])),
 
710
    ?line ?ber_driver(?BER,testSeq2738_cases(?BER)),
 
711
 
 
712
    ?line testSeq2738:compile(Config,?PER,[]), 
 
713
    ?line testSeq2738_cases(?PER),
 
714
 
 
715
    ?line ?per_bit_opt(testSeq2738:compile(Config,?PER,[optimize])), 
 
716
    ?line ?per_bit_opt(testSeq2738_cases(?PER)),
 
717
 
 
718
    ?line ?uper_bin(testSeq2738:compile(Config,uper_bin,[])), 
 
719
    ?line ?uper_bin(testSeq2738_cases(uper_bin)),
 
720
 
 
721
    ?line testSeq2738:compile(Config,?PER,[optimize]), 
 
722
    ?line testSeq2738_cases(?PER).
 
723
 
 
724
testSeq2738_cases(Rules) ->
 
725
    ?line testSeq2738:main(Rules).
 
726
 
 
727
 
 
728
testSeqTag(suite) -> [];
 
729
testSeqTag(Config) ->
 
730
 
 
731
    ?line testExternal:compile(Config,?BER,[]),
 
732
    ?line testSeqTag:compile(Config,?BER,[]),
 
733
    ?line testSeqTag_cases(?BER),
 
734
 
 
735
    ?line ?ber_driver(?BER,testExternal:compile(Config,?BER,[driver])),
 
736
    ?line ?ber_driver(?BER,testSeqTag:compile(Config,?BER,[driver])),
 
737
    ?line ?ber_driver(?BER,testSeqTag_cases(?BER)),
 
738
 
 
739
    ?line testExternal:compile(Config,?PER,[]),
 
740
    ?line testSeqTag:compile(Config,?PER,[]), 
 
741
    ?line testSeqTag_cases(?PER),
 
742
 
 
743
    ?line ?per_bit_opt(testExternal:compile(Config,?PER,[optimize])),
 
744
    ?line ?per_bit_opt(testSeqTag:compile(Config,?PER,[optimize])), 
 
745
    ?line ?per_bit_opt(testSeqTag_cases(?PER)),
 
746
 
 
747
    ?line ?uper_bin(testExternal:compile(Config,uper_bin,[])),
 
748
    ?line ?uper_bin(testSeqTag:compile(Config,uper_bin,[])), 
 
749
    ?line ?uper_bin(testSeqTag_cases(uper_bin)),
 
750
 
 
751
    ?line testExternal:compile(Config,?PER,[optimize]),
 
752
    ?line testSeqTag:compile(Config,?PER,[optimize]), 
 
753
    ?line testSeqTag_cases(?PER).
 
754
 
 
755
testSeqTag_cases(Rules) ->
 
756
    ?line testSeqTag:main(Rules).
 
757
 
 
758
 
 
759
 
 
760
 
 
761
testSeqTypeRefCho(suite) -> [];
 
762
testSeqTypeRefCho(Config) ->
 
763
 
 
764
    ?line testSeqTypeRefCho:compile(Config,?BER,[]),
 
765
    ?line testSeqTypeRefCho_cases(?BER),
 
766
 
 
767
    ?line ?ber_driver(?BER,testSeqTypeRefCho:compile(Config,?BER,[driver])),
 
768
    ?line ?ber_driver(?BER,testSeqTypeRefCho_cases(?BER)),
 
769
 
 
770
    ?line testSeqTypeRefCho:compile(Config,?PER,[]), 
 
771
    ?line testSeqTypeRefCho_cases(?PER),
 
772
 
 
773
    ?line ?per_bit_opt(testSeqTypeRefCho:compile(Config,?PER,[optimize])), 
 
774
    ?line ?per_bit_opt(testSeqTypeRefCho_cases(?PER)),
 
775
 
 
776
    ?line ?uper_bin(testSeqTypeRefCho:compile(Config,uper_bin,[])), 
 
777
    ?line ?uper_bin(testSeqTypeRefCho_cases(uper_bin)),
 
778
 
 
779
    ?line testSeqTypeRefCho:compile(Config,?PER,[optimize]), 
 
780
    ?line testSeqTypeRefCho_cases(?PER).
 
781
 
 
782
testSeqTypeRefCho_cases(Rules) ->
 
783
    ?line testSeqTypeRefCho:main(Rules).
 
784
 
 
785
 
 
786
 
 
787
testSeqTypeRefPrim(suite) -> [];
 
788
testSeqTypeRefPrim(Config) ->
 
789
 
 
790
    ?line testSeqTypeRefPrim:compile(Config,?BER,[]),
 
791
    ?line testSeqTypeRefPrim_cases(?BER),
 
792
 
 
793
    ?line ?ber_driver(?BER,testSeqTypeRefPrim:compile(Config,?BER,[driver])),
 
794
    ?line ?ber_driver(?BER,testSeqTypeRefPrim_cases(?BER)),
 
795
 
 
796
    ?line testSeqTypeRefPrim:compile(Config,?PER,[]), 
 
797
    ?line testSeqTypeRefPrim_cases(?PER),
 
798
 
 
799
    ?line ?per_bit_opt(testSeqTypeRefPrim:compile(Config,?PER,[optimize])), 
 
800
    ?line ?per_bit_opt(testSeqTypeRefPrim_cases(?PER)),
 
801
 
 
802
    ?line ?uper_bin(testSeqTypeRefPrim:compile(Config,uper_bin,[])), 
 
803
    ?line ?uper_bin(testSeqTypeRefPrim_cases(uper_bin)),
 
804
 
 
805
    ?line testSeqTypeRefPrim:compile(Config,?PER,[optimize]), 
 
806
    ?line testSeqTypeRefPrim_cases(?PER).
 
807
 
 
808
testSeqTypeRefPrim_cases(Rules) ->
 
809
    ?line testSeqTypeRefPrim:main(Rules).
 
810
 
 
811
 
 
812
 
 
813
testSeqTypeRefSeq(suite) -> [];
 
814
testSeqTypeRefSeq(Config) ->
 
815
 
 
816
    ?line testSeqTypeRefSeq:compile(Config,?BER,[]),
 
817
    ?line testSeqTypeRefSeq_cases(?BER),
 
818
 
 
819
    ?line ?ber_driver(?BER,testSeqTypeRefSeq:compile(Config,?BER,[driver])),
 
820
    ?line ?ber_driver(?BER,testSeqTypeRefSeq_cases(?BER)),
 
821
 
 
822
    ?line testSeqTypeRefSeq:compile(Config,?PER,[]), 
 
823
    ?line testSeqTypeRefSeq_cases(?PER),
 
824
 
 
825
    ?line ?per_bit_opt(testSeqTypeRefSeq:compile(Config,?PER,[optimize])), 
 
826
    ?line ?per_bit_opt(testSeqTypeRefSeq_cases(?PER)),
 
827
 
 
828
    ?line ?uper_bin(testSeqTypeRefSeq:compile(Config,uper_bin,[])), 
 
829
    ?line ?uper_bin(testSeqTypeRefSeq_cases(uper_bin)),
 
830
 
 
831
    ?line testSeqTypeRefSeq:compile(Config,?PER,[optimize]), 
 
832
    ?line testSeqTypeRefSeq_cases(?PER).
 
833
 
 
834
testSeqTypeRefSeq_cases(Rules) ->
 
835
    ?line testSeqTypeRefSeq:main(Rules).
 
836
 
 
837
 
 
838
 
 
839
testSeqTypeRefSet(suite) -> [];
 
840
testSeqTypeRefSet(Config) ->
 
841
 
 
842
    ?line testSeqTypeRefSet:compile(Config,?BER,[]),
 
843
    ?line testSeqTypeRefSet_cases(?BER),
 
844
 
 
845
    ?line ?ber_driver(?BER,testSeqTypeRefSet:compile(Config,?BER,[driver])),
 
846
    ?line ?ber_driver(?BER,testSeqTypeRefSet_cases(?BER)),
 
847
 
 
848
    ?line testSeqTypeRefSet:compile(Config,?PER,[]), 
 
849
    ?line testSeqTypeRefSet_cases(?PER),
 
850
 
 
851
    ?line ?per_bit_opt(testSeqTypeRefSet:compile(Config,?PER,[optimize])), 
 
852
    ?line ?per_bit_opt(testSeqTypeRefSet_cases(?PER)),
 
853
 
 
854
    ?line ?uper_bin(testSeqTypeRefSet:compile(Config,uper_bin,[])), 
 
855
    ?line ?uper_bin(testSeqTypeRefSet_cases(uper_bin)),
 
856
 
 
857
    ?line testSeqTypeRefSet:compile(Config,?PER,[optimize]), 
 
858
    ?line testSeqTypeRefSet_cases(?PER).
 
859
 
 
860
testSeqTypeRefSet_cases(Rules) ->
 
861
    ?line testSeqTypeRefSet:main(Rules).
 
862
 
 
863
 
 
864
 
 
865
 
 
866
testSeqOf(suite) -> [];
 
867
testSeqOf(Config) ->
 
868
    ?line true = code:add_patha(?config(priv_dir,Config)),
 
869
 
 
870
    ?line testSeqOf:compile(Config,?BER,[]),
 
871
    ?line testSeqOf_cases(?BER),
 
872
 
 
873
    ?line ?ber_driver(?BER,testSeqOf:compile(Config,?BER,[driver])),
 
874
    ?line ?ber_driver(?BER,testSeqOf_cases(?BER)),
 
875
 
 
876
    ?line testSeqOf:compile(Config,?PER,[]), 
 
877
    ?line testSeqOf_cases(?PER),
 
878
 
 
879
    ?line ?per_bit_opt(testSeqOf:compile(Config,?PER,[optimize])), 
 
880
    ?line ?per_bit_opt(testSeqOf_cases(?PER)),
 
881
 
 
882
    ?line ?uper_bin(testSeqOf:compile(Config,uper_bin,[])), 
 
883
    ?line ?uper_bin(testSeqOf_cases(uper_bin)),
 
884
 
 
885
    ?line testSeqOf:compile(Config,?PER,[optimize]), 
 
886
    ?line testSeqOf_cases(?PER).
 
887
 
 
888
testSeqOf_cases(Rules) ->
 
889
    ?line testSeqOf:main(Rules).
 
890
 
 
891
 
 
892
 
 
893
 
 
894
testSeqOfCho(suite) -> [];
 
895
testSeqOfCho(Config) ->
 
896
    ?line true = code:add_patha(?config(priv_dir,Config)),
 
897
 
 
898
    ?line testSeqOfCho:compile(Config,?BER,[]),
 
899
    ?line testSeqOfCho_cases(?BER),
 
900
 
 
901
    ?line ?ber_driver(?BER,testSeqOfCho:compile(Config,?BER,[driver])),
 
902
    ?line ?ber_driver(?BER,testSeqOfCho_cases(?BER)),
 
903
 
 
904
    ?line testSeqOfCho:compile(Config,?PER,[]), 
 
905
    ?line testSeqOfCho_cases(?PER),
 
906
 
 
907
    ?line ?per_bit_opt(testSeqOfCho:compile(Config,?PER,[optimize])), 
 
908
    ?line ?per_bit_opt(testSeqOfCho_cases(?PER)),
 
909
 
 
910
    ?line ?uper_bin(testSeqOfCho:compile(Config,uper_bin,[])), 
 
911
    ?line ?uper_bin(testSeqOfCho_cases(uper_bin)),
 
912
 
 
913
    ?line testSeqOfCho:compile(Config,?PER,[optimize]), 
 
914
    ?line testSeqOfCho_cases(?PER).
 
915
 
 
916
testSeqOfIndefinite(suite) -> [];
 
917
testSeqOfIndefinite(Config) ->
 
918
    ?line true = code:add_patha(?config(priv_dir,Config)),
 
919
 
 
920
    ?line testSeqOfIndefinite:compile(Config,?BER,[]),
 
921
    ?line testSeqOfIndefinite:main(),
 
922
 
 
923
    ?line ?ber_driver(?BER,testSeqOfIndefinite:compile(Config,?BER,[driver])),
 
924
    ?line ?ber_driver(?BER,testSeqOfIndefinite:main()).
 
925
 
 
926
testSeqOfCho_cases(Rules) ->
 
927
    ?line testSeqOfCho:main(Rules).
 
928
 
 
929
 
 
930
testSeqOfExternal(suite) -> [];
 
931
testSeqOfExternal(Config) ->
 
932
    ?line true = code:add_patha(?config(priv_dir,Config)),
 
933
 
 
934
    ?line testExternal:compile(Config,?BER,[]),
 
935
    ?line testSeqOfExternal:compile(Config,?BER,[]),
 
936
    ?line testSeqOfExternal_cases(?BER),
 
937
 
 
938
    ?line ?ber_driver(?BER,testExternal:compile(Config,?BER,[driver])),
 
939
    ?line ?ber_driver(?BER,testSeqOfExternal:compile(Config,?BER,[driver])),
 
940
    ?line ?ber_driver(?BER,testSeqOfExternal_cases(?BER)),
 
941
 
 
942
    ?line testExternal:compile(Config,?PER,[]),
 
943
    ?line testSeqOfExternal:compile(Config,?PER,[]), 
 
944
    ?line testSeqOfExternal_cases(?PER),
 
945
 
 
946
    ?line ?per_bit_opt(testExternal:compile(Config,?PER,[optimize])),
 
947
    ?line ?per_bit_opt(testSeqOfExternal:compile(Config,?PER,[optimize])), 
 
948
    ?line ?per_bit_opt(testSeqOfExternal_cases(?PER)),
 
949
 
 
950
    ?line ?uper_bin(testExternal:compile(Config,uper_bin,[])),
 
951
    ?line ?uper_bin(testSeqOfExternal:compile(Config,uper_bin,[])), 
 
952
    ?line ?uper_bin(testSeqOfExternal_cases(uper_bin)),
 
953
 
 
954
    ?line testExternal:compile(Config,?PER,[optimize]),
 
955
    ?line testSeqOfExternal:compile(Config,?PER,[optimize]), 
 
956
    ?line testSeqOfExternal_cases(?PER).
 
957
 
 
958
testSeqOfExternal_cases(Rules) ->
 
959
    ?line testSeqOfExternal:main(Rules).
 
960
 
 
961
 
 
962
 
 
963
testSeqOfTag(suite) -> [];
 
964
testSeqOfTag(Config) ->
 
965
    ?line true = code:add_patha(?config(priv_dir,Config)),
 
966
 
 
967
    ?line testExternal:compile(Config,?BER,[]),
 
968
    ?line testSeqOfTag:compile(Config,?BER,[]),
 
969
    ?line testSeqOfTag_cases(?BER),
 
970
 
 
971
    ?line ?ber_driver(?BER,testExternal:compile(Config,?BER,[driver])),
 
972
    ?line ?ber_driver(?BER,testSeqOfTag:compile(Config,?BER,[driver])),
 
973
    ?line ?ber_driver(?BER,testSeqOfTag_cases(?BER)),
 
974
 
 
975
    ?line testExternal:compile(Config,?PER,[]),
 
976
    ?line testSeqOfTag:compile(Config,?PER,[]), 
 
977
    ?line testSeqOfTag_cases(?PER),
 
978
 
 
979
    ?line ?per_bit_opt(testExternal:compile(Config,?PER,[optimize])),
 
980
    ?line ?per_bit_opt(testSeqOfTag:compile(Config,?PER,[optimize])), 
 
981
    ?line ?per_bit_opt(testSeqOfTag_cases(?PER)),
 
982
 
 
983
    ?line ?uper_bin(testExternal:compile(Config,uper_bin,[])),
 
984
    ?line ?uper_bin(testSeqOfTag:compile(Config,uper_bin,[])), 
 
985
    ?line ?uper_bin(testSeqOfTag_cases(uper_bin)),
 
986
 
 
987
    ?line testExternal:compile(Config,?PER,[optimize]),
 
988
    ?line testSeqOfTag:compile(Config,?PER,[optimize]), 
 
989
    ?line testSeqOfTag_cases(?PER).
 
990
 
 
991
testSeqOfTag_cases(Rules) ->
 
992
    ?line testSeqOfTag:main(Rules).
 
993
 
 
994
 
 
995
 
 
996
 
 
997
testSetDefault(suite) -> [];
 
998
testSetDefault(Config) ->
 
999
    ?line true = code:add_patha(?config(priv_dir,Config)),
 
1000
 
 
1001
    ?line testSetDefault:compile(Config,?BER,[]),
 
1002
    ?line testSetDefault_cases(?BER),
 
1003
 
 
1004
    ?line ?ber_driver(?BER,testSetDefault:compile(Config,?BER,[driver])),
 
1005
    ?line ?ber_driver(?BER,testSetDefault_cases(?BER)),
 
1006
 
 
1007
    ?line testSetDefault:compile(Config,?PER,[]), 
 
1008
    ?line testSetDefault_cases(?PER),
 
1009
 
 
1010
    ?line ?per_bit_opt(testSetDefault:compile(Config,?PER,[optimize])), 
 
1011
    ?line ?per_bit_opt(testSetDefault_cases(?PER)),
 
1012
 
 
1013
    ?line ?uper_bin(testSetDefault:compile(Config,uper_bin,[])), 
 
1014
    ?line ?uper_bin(testSetDefault_cases(uper_bin)),
 
1015
 
 
1016
    ?line testSetDefault:compile(Config,?PER,[optimize]), 
 
1017
    ?line testSetDefault_cases(?PER).
 
1018
 
 
1019
testSetDefault_cases(Rules) ->
 
1020
    ?line testSetDefault:main(Rules).
 
1021
 
 
1022
 
 
1023
testParamBasic(suite) -> [];
 
1024
testParamBasic(Config) ->
 
1025
    ?line true = code:add_patha(?config(priv_dir,Config)),
 
1026
 
 
1027
    ?line testParamBasic:compile(Config,?BER,[]),
 
1028
    ?line testParamBasic_cases(?BER),
 
1029
 
 
1030
    ?line ?ber_driver(?BER,testParamBasic:compile(Config,?BER,[driver])),
 
1031
    ?line ?ber_driver(?BER,testParamBasic_cases(?BER)),
 
1032
 
 
1033
    ?line testParamBasic:compile(Config,?PER,[]),
 
1034
    ?line testParamBasic_cases(?PER),
 
1035
 
 
1036
    ?line ?per_bit_opt(testParamBasic:compile(Config,?PER,[optimize])),
 
1037
    ?line ?per_bit_opt(testParamBasic_cases(?PER)),
 
1038
 
 
1039
    ?line ?uper_bin(testParamBasic:compile(Config,uper_bin,[])),
 
1040
    ?line ?uper_bin(testParamBasic_cases(uper_bin)),
 
1041
 
 
1042
    ?line testParamBasic:compile(Config,?PER,[optimize]),
 
1043
    ?line testParamBasic_cases(?PER).
 
1044
 
 
1045
 
 
1046
testParamBasic_cases(Rules) ->
 
1047
    ?line testParamBasic:main(Rules).
 
1048
 
 
1049
testSetExtension(suite) -> [];
 
1050
testSetExtension(Config) ->
 
1051
    ?line true = code:add_patha(?config(priv_dir,Config)),
 
1052
 
 
1053
    ?line testExternal:compile(Config,?BER,[]),
 
1054
    ?line testSetExtension:compile(Config,?BER,[]),
 
1055
    ?line testSetExtension_cases(?BER),
 
1056
 
 
1057
    ?line ?ber_driver(?BER,testExternal:compile(Config,?BER,[driver])),
 
1058
    ?line ?ber_driver(?BER,testSetExtension:compile(Config,?BER,[driver])),
 
1059
    ?line ?ber_driver(?BER,testSetExtension_cases(?BER)).
 
1060
 
 
1061
testSetExtension_cases(Rules) ->
 
1062
    ?line testSetExtension:main(Rules).
 
1063
 
 
1064
 
 
1065
testSetExternal(suite) -> [];
 
1066
testSetExternal(Config) ->
 
1067
    ?line true = code:add_patha(?config(priv_dir,Config)),
 
1068
 
 
1069
    ?line testExternal:compile(Config,?BER,[]),
 
1070
    ?line testSetExternal:compile(Config,?BER,[]),
 
1071
    ?line testSetExternal_cases(?BER),
 
1072
 
 
1073
    ?line ?ber_driver(?BER,testExternal:compile(Config,?BER,[driver])),
 
1074
    ?line ?ber_driver(?BER,testSetExternal:compile(Config,?BER,[driver])),
 
1075
    ?line ?ber_driver(?BER,testSetExternal_cases(?BER)).
 
1076
 
 
1077
testSetExternal_cases(Rules) ->
 
1078
    ?line testSetExternal:main(Rules).
 
1079
 
 
1080
 
 
1081
testSetOptional(suite) -> [];
 
1082
testSetOptional(Config) ->
 
1083
    ?line true = code:add_patha(?config(priv_dir,Config)),
 
1084
 
 
1085
    ?line testSetOptional:compile(Config,?BER,[]),
 
1086
    ?line testSetOptional_cases(?BER),
 
1087
 
 
1088
    ?line ?ber_driver(?BER,testSetOptional:compile(Config,?BER,[driver])),
 
1089
    ?line ?ber_driver(?BER,testSetOptional_cases(?BER)),
 
1090
 
 
1091
    ?line testSetOptional:compile(Config,?PER,[]), 
 
1092
    ?line testSetOptional_cases(?PER),
 
1093
 
 
1094
    ?line ?per_bit_opt(testSetOptional:compile(Config,?PER,[optimize])), 
 
1095
    ?line ?per_bit_opt(testSetOptional_cases(?PER)),
 
1096
 
 
1097
    ?line ?uper_bin(testSetOptional:compile(Config,uper_bin,[])), 
 
1098
    ?line ?uper_bin(testSetOptional_cases(uper_bin)),
 
1099
 
 
1100
    ?line testSetOptional:compile(Config,?PER,[optimize]), 
 
1101
    ?line testSetOptional_cases(?PER).
 
1102
 
 
1103
testSetOptional_cases(Rules) ->
 
1104
    ?line ok = testSetOptional:ticket_7533(Rules),
 
1105
    ?line ok = testSetOptional:main(Rules).
 
1106
 
 
1107
 
 
1108
 
 
1109
 
 
1110
testSetPrim(suite) -> [];
 
1111
testSetPrim(Config) ->
 
1112
    ?line true = code:add_patha(?config(priv_dir,Config)),
 
1113
 
 
1114
    ?line testSetPrim:compile(Config,?BER,[]),
 
1115
    ?line testSetPrim_cases(?BER),
 
1116
 
 
1117
    ?line ?ber_driver(?BER,testSetPrim:compile(Config,?BER,[driver])),
 
1118
    ?line ?ber_driver(?BER,testSetPrim_cases(?BER)),
 
1119
 
 
1120
    ?line testSetPrim:compile(Config,?PER,[]), 
 
1121
    ?line testSetPrim_cases(?PER),
 
1122
 
 
1123
    ?line ?per_bit_opt(testSetPrim:compile(Config,?PER,[optimize])), 
 
1124
    ?line ?per_bit_opt(testSetPrim_cases(?PER)),
 
1125
 
 
1126
    ?line ?uper_bin(testSetPrim:compile(Config,uper_bin,[])), 
 
1127
    ?line ?uper_bin(testSetPrim_cases(uper_bin)),
 
1128
 
 
1129
    ?line testSetPrim:compile(Config,?PER,[optimize]), 
 
1130
    ?line testSetPrim_cases(?PER).
 
1131
 
 
1132
testSetPrim_cases(Rules) ->
 
1133
    ?line testSetPrim:main(Rules).
 
1134
 
 
1135
 
 
1136
 
 
1137
testSetTag(suite) -> [];
 
1138
testSetTag(Config) ->
 
1139
    ?line true = code:add_patha(?config(priv_dir,Config)),
 
1140
 
 
1141
    ?line testExternal:compile(Config,?BER,[]),
 
1142
    ?line testSetTag:compile(Config,?BER,[]),
 
1143
    ?line testSetTag_cases(?BER),
 
1144
 
 
1145
    ?line ?ber_driver(?BER,testExternal:compile(Config,?BER,[driver])),
 
1146
    ?line ?ber_driver(?BER,testSetTag:compile(Config,?BER,[driver])),
 
1147
    ?line ?ber_driver(?BER,testSetTag_cases(?BER)),
 
1148
 
 
1149
    ?line testExternal:compile(Config,?PER,[]),
 
1150
    ?line testSetTag:compile(Config,?PER,[]), 
 
1151
    ?line testSetTag_cases(?PER),
 
1152
 
 
1153
    ?line ?per_bit_opt(testExternal:compile(Config,?PER,[optimize])),
 
1154
    ?line ?per_bit_opt(testSetTag:compile(Config,?PER,[optimize])), 
 
1155
    ?line ?per_bit_opt(testSetTag_cases(?PER)),
 
1156
 
 
1157
    ?line ?uper_bin(testExternal:compile(Config,uper_bin,[])),
 
1158
    ?line ?uper_bin(testSetTag:compile(Config,uper_bin,[])), 
 
1159
    ?line ?uper_bin(testSetTag_cases(uper_bin)),
 
1160
 
 
1161
    ?line testExternal:compile(Config,?PER,[optimize]),
 
1162
    ?line testSetTag:compile(Config,?PER,[optimize]), 
 
1163
    ?line testSetTag_cases(?PER).
 
1164
 
 
1165
testSetTag_cases(Rules) ->
 
1166
    ?line testSetTag:main(Rules).
 
1167
 
 
1168
 
 
1169
 
 
1170
testSetTypeRefCho(suite) -> [];
 
1171
testSetTypeRefCho(Config) ->
 
1172
    ?line true = code:add_patha(?config(priv_dir,Config)),
 
1173
 
 
1174
    ?line testSetTypeRefCho:compile(Config,?BER,[]),
 
1175
    ?line testSetTypeRefCho_cases(?BER),
 
1176
 
 
1177
    ?line ?ber_driver(?BER,testSetTypeRefCho:compile(Config,?BER,[driver])),
 
1178
    ?line ?ber_driver(?BER,testSetTypeRefCho_cases(?BER)),
 
1179
 
 
1180
    ?line testSetTypeRefCho:compile(Config,?PER,[]), 
 
1181
    ?line testSetTypeRefCho_cases(?PER),
 
1182
 
 
1183
    ?line ?per_bit_opt(testSetTypeRefCho:compile(Config,?PER,[optimize])), 
 
1184
    ?line ?per_bit_opt(testSetTypeRefCho_cases(?PER)),
 
1185
 
 
1186
    ?line ?uper_bin(testSetTypeRefCho:compile(Config,uper_bin,[])), 
 
1187
    ?line ?uper_bin(testSetTypeRefCho_cases(uper_bin)),
 
1188
 
 
1189
    ?line testSetTypeRefCho:compile(Config,?PER,[optimize]), 
 
1190
    ?line testSetTypeRefCho_cases(?PER).
 
1191
 
 
1192
testSetTypeRefCho_cases(Rules) ->
 
1193
    ?line testSetTypeRefCho:main(Rules).
 
1194
 
 
1195
 
 
1196
 
 
1197
testSetTypeRefPrim(suite) -> [];
 
1198
testSetTypeRefPrim(Config) ->
 
1199
    ?line true = code:add_patha(?config(priv_dir,Config)),
 
1200
 
 
1201
    ?line testSetTypeRefPrim:compile(Config,?BER,[]),
 
1202
    ?line testSetTypeRefPrim_cases(?BER),
 
1203
 
 
1204
    ?line ?ber_driver(?BER,testSetTypeRefPrim:compile(Config,?BER,[driver])),
 
1205
    ?line ?ber_driver(?BER,testSetTypeRefPrim_cases(?BER)),
 
1206
 
 
1207
    ?line testSetTypeRefPrim:compile(Config,?PER,[]), 
 
1208
    ?line testSetTypeRefPrim_cases(?PER),
 
1209
 
 
1210
    ?line ?per_bit_opt(testSetTypeRefPrim:compile(Config,?PER,[optimize])), 
 
1211
    ?line ?per_bit_opt(testSetTypeRefPrim_cases(?PER)),
 
1212
 
 
1213
    ?line ?uper_bin(testSetTypeRefPrim:compile(Config,uper_bin,[])), 
 
1214
    ?line ?uper_bin(testSetTypeRefPrim_cases(uper_bin)),
 
1215
 
 
1216
    ?line testSetTypeRefPrim:compile(Config,?PER,[optimize]), 
 
1217
    ?line testSetTypeRefPrim_cases(?PER).
 
1218
 
 
1219
testSetTypeRefPrim_cases(Rules) ->
 
1220
    ?line testSetTypeRefPrim:main(Rules).
 
1221
 
 
1222
 
 
1223
 
 
1224
testSetTypeRefSeq(suite) -> [];
 
1225
testSetTypeRefSeq(Config) ->
 
1226
    ?line true = code:add_patha(?config(priv_dir,Config)),
 
1227
 
 
1228
    ?line testSetTypeRefSeq:compile(Config,?BER,[]),
 
1229
    ?line testSetTypeRefSeq_cases(?BER),
 
1230
 
 
1231
    ?line ?ber_driver(?BER,testSetTypeRefSeq:compile(Config,?BER,[driver])),
 
1232
    ?line ?ber_driver(?BER,testSetTypeRefSeq_cases(?BER)),
 
1233
 
 
1234
    ?line testSetTypeRefSeq:compile(Config,?PER,[]), 
 
1235
    ?line testSetTypeRefSeq_cases(?PER),
 
1236
 
 
1237
    ?line ?per_bit_opt(testSetTypeRefSeq:compile(Config,?PER,[optimize])), 
 
1238
    ?line ?per_bit_opt(testSetTypeRefSeq_cases(?PER)),
 
1239
 
 
1240
    ?line ?uper_bin(testSetTypeRefSeq:compile(Config,uper_bin,[])), 
 
1241
    ?line ?uper_bin(testSetTypeRefSeq_cases(uper_bin)),
 
1242
 
 
1243
    ?line testSetTypeRefSeq:compile(Config,?PER,[optimize]), 
 
1244
    ?line testSetTypeRefSeq_cases(?PER).
 
1245
 
 
1246
testSetTypeRefSeq_cases(Rules) ->
 
1247
    ?line testSetTypeRefSeq:main(Rules).
 
1248
 
 
1249
 
 
1250
 
 
1251
testSetTypeRefSet(suite) -> [];
 
1252
testSetTypeRefSet(Config) ->
 
1253
    ?line true = code:add_patha(?config(priv_dir,Config)),
 
1254
 
 
1255
    ?line testSetTypeRefSet:compile(Config,?BER,[]),
 
1256
    ?line testSetTypeRefSet_cases(?BER),
 
1257
 
 
1258
    ?line ?ber_driver(?BER,testSetTypeRefSet:compile(Config,?BER,[driver])),
 
1259
    ?line ?ber_driver(?BER,testSetTypeRefSet_cases(?BER)),
 
1260
 
 
1261
    ?line testSetTypeRefSet:compile(Config,?PER,[]), 
 
1262
    ?line testSetTypeRefSet_cases(?PER),
 
1263
 
 
1264
    ?line ?per_bit_opt(testSetTypeRefSet:compile(Config,?PER,[optimize])), 
 
1265
    ?line ?per_bit_opt(testSetTypeRefSet_cases(?PER)),
 
1266
 
 
1267
    ?line ?uper_bin(testSetTypeRefSet:compile(Config,uper_bin,[])), 
 
1268
    ?line ?uper_bin(testSetTypeRefSet_cases(uper_bin)),
 
1269
 
 
1270
    ?line testSetTypeRefSet:compile(Config,?PER,[optimize]), 
 
1271
    ?line testSetTypeRefSet_cases(?PER).
 
1272
 
 
1273
testSetTypeRefSet_cases(Rules) ->
 
1274
    ?line testSetTypeRefSet:main(Rules).
 
1275
 
 
1276
 
 
1277
 
 
1278
testSetOf(suite) -> [];
 
1279
testSetOf(Config) ->
 
1280
    ?line true = code:add_patha(?config(priv_dir,Config)),
 
1281
 
 
1282
    ?line testSetOf:compile(Config,?BER,[]),
 
1283
    ?line testSetOf_cases(?BER),
 
1284
 
 
1285
    ?line ?ber_driver(?BER,testSetOf:compile(Config,?BER,[driver])),
 
1286
    ?line ?ber_driver(?BER,testSetOf_cases(?BER)),
 
1287
 
 
1288
    ?line testSetOf:compile(Config,?PER,[]), 
 
1289
    ?line testSetOf_cases(?PER),
 
1290
 
 
1291
    ?line ?per_bit_opt(testSetOf:compile(Config,?PER,[optimize])), 
 
1292
    ?line ?per_bit_opt(testSetOf_cases(?PER)),
 
1293
 
 
1294
    ?line ?uper_bin(testSetOf:compile(Config,uper_bin,[])), 
 
1295
    ?line ?uper_bin(testSetOf_cases(uper_bin)),
 
1296
 
 
1297
    ?line testSetOf:compile(Config,?PER,[optimize]), 
 
1298
    ?line testSetOf_cases(?PER).
 
1299
 
 
1300
testSetOf_cases(Rules) ->
 
1301
    ?line testSetOf:main(Rules).
 
1302
 
 
1303
 
 
1304
 
 
1305
testSetOfCho(suite) -> [];
 
1306
testSetOfCho(Config) ->
 
1307
    ?line true = code:add_patha(?config(priv_dir,Config)),
 
1308
 
 
1309
    ?line testSetOfCho:compile(Config,?BER,[]),
 
1310
    ?line testSetOfCho_cases(?BER),
 
1311
 
 
1312
    ?line ?ber_driver(?BER,testSetOfCho:compile(Config,?BER,[driver])),
 
1313
    ?line ?ber_driver(?BER,testSetOfCho_cases(?BER)),
 
1314
 
 
1315
    ?line testSetOfCho:compile(Config,?PER,[]), 
 
1316
    ?line testSetOfCho_cases(?PER),
 
1317
 
 
1318
    ?line ?per_bit_opt(testSetOfCho:compile(Config,?PER,[optimize])), 
 
1319
    ?line ?per_bit_opt(testSetOfCho_cases(?PER)),
 
1320
 
 
1321
    ?line ?uper_bin(testSetOfCho:compile(Config,uper_bin,[])), 
 
1322
    ?line ?uper_bin(testSetOfCho_cases(uper_bin)),
 
1323
 
 
1324
    ?line testSetOfCho:compile(Config,?PER,[optimize]), 
 
1325
    ?line testSetOfCho_cases(?PER).
 
1326
 
 
1327
testSetOfCho_cases(Rules) ->
 
1328
    ?line testSetOfCho:main(Rules).
 
1329
 
 
1330
 
 
1331
testSetOfExternal(suite) -> [];
 
1332
testSetOfExternal(Config) ->
 
1333
    ?line true = code:add_patha(?config(priv_dir,Config)),
 
1334
 
 
1335
    ?line testExternal:compile(Config,?BER,[]),
 
1336
    ?line testSetOfExternal:compile(Config,?BER,[]),
 
1337
    ?line testSetOfExternal_cases(?BER),
 
1338
 
 
1339
    ?line ?ber_driver(?BER,testExternal:compile(Config,?BER,[driver])),
 
1340
    ?line ?ber_driver(?BER,testSetOfExternal:compile(Config,?BER,[driver])),
 
1341
    ?line ?ber_driver(?BER,testSetOfExternal_cases(?BER)),
 
1342
 
 
1343
    ?line testExternal:compile(Config,?PER,[]),
 
1344
    ?line testSetOfExternal:compile(Config,?PER,[]), 
 
1345
    ?line testSetOfExternal_cases(?PER),
 
1346
 
 
1347
    ?line ?per_bit_opt(testExternal:compile(Config,?PER,[optimize])),
 
1348
    ?line ?per_bit_opt(testSetOfExternal:compile(Config,?PER,[optimize])), 
 
1349
    ?line ?per_bit_opt(testSetOfExternal_cases(?PER)),
 
1350
 
 
1351
    ?line ?uper_bin(testExternal:compile(Config,uper_bin,[])),
 
1352
    ?line ?uper_bin(testSetOfExternal:compile(Config,uper_bin,[])), 
 
1353
    ?line ?uper_bin(testSetOfExternal_cases(uper_bin)),
 
1354
 
 
1355
    ?line testExternal:compile(Config,?PER,[optimize]),
 
1356
    ?line testSetOfExternal:compile(Config,?PER,[optimize]), 
 
1357
    ?line testSetOfExternal_cases(?PER).
 
1358
 
 
1359
testSetOfExternal_cases(Rules) ->
 
1360
    ?line testSetOfExternal:main(Rules).
 
1361
 
 
1362
 
 
1363
 
 
1364
 
 
1365
testSetOfTag(suite) -> [];
 
1366
testSetOfTag(Config) ->
 
1367
    ?line true = code:add_patha(?config(priv_dir,Config)),
 
1368
 
 
1369
    ?line testExternal:compile(Config,?BER,[]),
 
1370
    ?line testSetOfTag:compile(Config,?BER,[]),
 
1371
    ?line testSetOfTag_cases(?BER),
 
1372
 
 
1373
    ?line ?ber_driver(?BER,testExternal:compile(Config,?BER,[driver])),
 
1374
    ?line ?ber_driver(?BER,testSetOfTag:compile(Config,?BER,[driver])),
 
1375
    ?line ?ber_driver(?BER,testSetOfTag_cases(?BER)),
 
1376
 
 
1377
    ?line testExternal:compile(Config,?PER,[]),
 
1378
    ?line testSetOfTag:compile(Config,?PER,[]), 
 
1379
    ?line testSetOfTag_cases(?PER),
 
1380
 
 
1381
    ?line ?per_bit_opt(testExternal:compile(Config,?PER,[optimize])),
 
1382
    ?line ?per_bit_opt(testSetOfTag:compile(Config,?PER,[optimize])), 
 
1383
    ?line ?per_bit_opt(testSetOfTag_cases(?PER)),
 
1384
 
 
1385
    ?line ?uper_bin(testExternal:compile(Config,uper_bin,[])),
 
1386
    ?line ?uper_bin(testSetOfTag:compile(Config,uper_bin,[])), 
 
1387
    ?line ?uper_bin(testSetOfTag_cases(uper_bin)),
 
1388
 
 
1389
    ?line testExternal:compile(Config,?PER,[optimize]),
 
1390
    ?line testSetOfTag:compile(Config,?PER,[optimize]), 
 
1391
    ?line testSetOfTag_cases(?PER).
 
1392
 
 
1393
testSetOfTag_cases(Rules) ->
 
1394
    ?line testSetOfTag:main(Rules).
 
1395
 
 
1396
 
 
1397
c_syntax(suite) -> [];
 
1398
c_syntax(Config) ->
 
1399
    ?line DataDir%    ?line testExternal:compile(Config,?PER),     
 
1400
%    ?line testPrimExternal:compile(Config,?PER), 
 
1401
%    ?line testPrimExternal_cases(?PER).          
 
1402
 = ?config(data_dir,Config),
 
1403
    ?line _TempDir = ?config(priv_dir,Config),
 
1404
    ?line true = code:add_patha(?config(priv_dir,Config)),
 
1405
    ?line {error,_R1} = asn1ct:compile(filename:join(DataDir,"Syntax")),
 
1406
    ?line {error,_R2} = asn1ct:compile(filename:join(DataDir,"BadTypeEnding")),
 
1407
    ?line {error,_R3} = asn1ct:compile(filename:join(DataDir,
 
1408
                                                    "BadValueAssignment1")),
 
1409
    ?line {error,_R4} = asn1ct:compile(filename:join(DataDir,
 
1410
                                                    "BadValueAssignment2")),
 
1411
    ?line {error,_R5} = asn1ct:compile(filename:join(DataDir,
 
1412
                                                    "BadValueSet")),
 
1413
    ?line {error,_R6} = asn1ct:compile(filename:join(DataDir,
 
1414
                                                    "ChoiceBadExtension")),
 
1415
    ?line {error,_R7} = asn1ct:compile(filename:join(DataDir,
 
1416
                                                "EnumerationBadExtension")),
 
1417
    ?line {error,_R8} = asn1ct:compile(filename:join(DataDir,
 
1418
                                                    "Example")),
 
1419
    ?line {error,_R9} = asn1ct:compile(filename:join(DataDir,
 
1420
                                                    "Export1")),
 
1421
    ?line {error,_R10} = asn1ct:compile(filename:join(DataDir,
 
1422
                                                     "MissingEnd")),
 
1423
    ?line {error,_R11} = asn1ct:compile(filename:join(DataDir,
 
1424
                                                     "SequenceBadComma")),
 
1425
    ?line {error,_R12} = asn1ct:compile(filename:join(DataDir,
 
1426
                                                "SequenceBadComponentName")),
 
1427
    ?line {error,_R13} = asn1ct:compile(filename:join(DataDir,
 
1428
                                                "SequenceBadComponentType")),
 
1429
    ?line {error,_R14} = asn1ct:compile(filename:join(DataDir,
 
1430
                                                "SeqBadComma")).
 
1431
 
 
1432
 
 
1433
c_string_per(suite) -> [];
 
1434
c_string_per(Config) ->
 
1435
    ?line DataDir = ?config(data_dir,Config),
 
1436
    ?line TempDir = ?config(priv_dir,Config),
 
1437
    ?line true = code:add_patha(?config(priv_dir,Config)),
 
1438
    ?line ok = asn1ct:compile(filename:join(DataDir,"String"),[?PER,{outdir,TempDir}]).
 
1439
 
 
1440
c_string_ber(suite) -> [];
 
1441
c_string_ber(Config) ->
 
1442
    ?line DataDir = ?config(data_dir,Config),
 
1443
    ?line TempDir = ?config(priv_dir,Config),
 
1444
    ?line true = code:add_patha(?config(priv_dir,Config)),
 
1445
    ?line ok = asn1ct:compile(filename:join(DataDir,"String"),[?BER,{outdir,TempDir}]).
 
1446
 
 
1447
 
 
1448
c_implicit_before_choice(suite) -> [];
 
1449
c_implicit_before_choice(Config) ->
 
1450
    ?line DataDir = ?config(data_dir,Config),
 
1451
    ?line TempDir = ?config(priv_dir,Config),
 
1452
    ?line {error,_R2} = asn1ct:compile(filename:join(DataDir,"CCSNARG3"),[?BER,{outdir,TempDir}]).
 
1453
 
 
1454
parse(suite) -> [];
 
1455
parse(Config) ->
 
1456
    ?line DataDir = ?config(data_dir,Config),
 
1457
    ?line OutDir = ?config(priv_dir,Config),
 
1458
    ?line true = code:add_patha(?config(priv_dir,Config)),
 
1459
    M1 = test_modules(),
 
1460
%    M2 = parse_modules(),
 
1461
    ?line ok = parse1(M1,DataDir,OutDir).
 
1462
 
 
1463
parse1([M|T],DataDir,OutDir) ->
 
1464
    ?line ok = asn1ct:compile(DataDir ++ M,[abs,{outdir,OutDir}]),
 
1465
    parse1(T,DataDir,OutDir);
 
1466
parse1([],_,_) ->
 
1467
    ok.
 
1468
 
 
1469
per(suite) -> [];
 
1470
per(Config) ->
 
1471
    ?line DataDir = ?config(data_dir,Config),
 
1472
    ?line OutDir = ?config(priv_dir,Config),
 
1473
    ?line true = code:add_patha(?config(priv_dir,Config)),
 
1474
    ?line ok = per1(per_modules(),DataDir,OutDir),
 
1475
    ?line ?per_bit_opt(per1_bit_opt(per_modules(),DataDir,OutDir)),
 
1476
    ?line ok = per1_opt(per_modules(),DataDir,OutDir).
 
1477
 
 
1478
 
 
1479
per1([M|T],DataDir,OutDir) ->
 
1480
    ?line ok = asn1ct:compile(DataDir ++ M,[?PER,{outdir,OutDir}]),
 
1481
    ?line ok = asn1ct:test(list_to_atom(M)),
 
1482
    per1(T,DataDir,OutDir);
 
1483
per1([],_,_) ->
 
1484
    ok.
 
1485
 
 
1486
per1_bit_opt([M|T],DataDir,OutDir) ->
 
1487
    ?line ok = asn1ct:compile(DataDir ++ M,[?PER,optimize,{outdir,OutDir}]),
 
1488
    ?line ok = asn1ct:test(list_to_atom(M)),
 
1489
    per1_bit_opt(T,DataDir,OutDir);
 
1490
per1_bit_opt([],_,_) ->
 
1491
    ok.
 
1492
 
 
1493
per1_opt([M|T],DataDir,OutDir) ->
 
1494
    ?line ok = asn1ct:compile(DataDir ++ M,[?PER,optimized,{outdir,OutDir}]),
 
1495
    ?line ok = asn1ct:test(list_to_atom(M)),
 
1496
    per1_opt(T,DataDir,OutDir);
 
1497
per1_opt([],_,_) ->
 
1498
    ok.
 
1499
 
 
1500
 
 
1501
ber_choiceinseq(suite) ->[];
 
1502
ber_choiceinseq(Config) ->
 
1503
    ?line DataDir = ?config(data_dir,Config),
 
1504
    ?line OutDir = ?config(priv_dir,Config),
 
1505
    ?line true = code:add_patha(?config(priv_dir,Config)),
 
1506
    ?line ok = asn1ct:compile(filename:join(DataDir,"ChoiceInSeq"),[?BER,{outdir,OutDir}]).
 
1507
 
 
1508
ber_optional(suite) ->[];
 
1509
ber_optional(Config) ->
 
1510
    ?line DataDir = ?config(data_dir,Config),
 
1511
    ?line OutDir = ?config(priv_dir,Config),
 
1512
    ?line true = code:add_patha(?config(priv_dir,Config)),
 
1513
    ?line ok = asn1ct:compile(filename:join(DataDir,"SOpttest"),[?BER,{outdir,OutDir}]),
 
1514
    ?line V = {'S',{'A',10,asn1_NOVALUE,asn1_NOVALUE},
 
1515
         {'B',asn1_NOVALUE,asn1_NOVALUE,asn1_NOVALUE},
 
1516
         {'C',asn1_NOVALUE,111,asn1_NOVALUE}},
 
1517
    ?line {ok,B} = asn1_wrapper:encode('SOpttest','S',V),
 
1518
    ?line Bytes = lists:flatten(B),
 
1519
    ?line V2 = asn1_wrapper:decode('SOpttest','S',Bytes),
 
1520
    ?line ok = eq(V,element(2,V2)).
 
1521
 
 
1522
ber_optional_keyed_list(suite) ->[];
 
1523
ber_optional_keyed_list(Config) ->
 
1524
    case ?BER of
 
1525
        ber_bin_v2 -> ok;
 
1526
        _ ->
 
1527
           ?line DataDir = ?config(data_dir,Config),
 
1528
           ?line OutDir = ?config(priv_dir,Config),
 
1529
           ?line true = code:add_patha(?config(priv_dir,Config)),
 
1530
           ?line ok = asn1ct:compile(filename:join(DataDir,"SOpttest"),
 
1531
                              [?BER,keyed_list,{outdir,OutDir}]),
 
1532
           ?line Vrecord = {'S',{'A',10,asn1_NOVALUE,asn1_NOVALUE},
 
1533
              {'B',asn1_NOVALUE,asn1_NOVALUE,asn1_NOVALUE},
 
1534
              {'C',asn1_NOVALUE,111,asn1_NOVALUE}},
 
1535
           ?line V = [ {a,[{scriptKey,10}]},
 
1536
                       {b,[]},
 
1537
                       {c,[{callingPartysCategory,111}]} ],
 
1538
           ?line {ok,B} = asn1_wrapper:encode('SOpttest','S',V),
 
1539
           ?line Bytes = lists:flatten(B),
 
1540
           ?line V2 = asn1_wrapper:decode('SOpttest','S',Bytes),
 
1541
           ?line ok = eq(Vrecord,element(2,V2))
 
1542
    end.
 
1543
 
 
1544
 
 
1545
eq(V,V) ->
 
1546
    ok.
 
1547
 
 
1548
 
 
1549
ber_other(suite) ->[];
 
1550
ber_other(Config) ->
 
1551
    ?line DataDir = ?config(data_dir,Config),
 
1552
    ?line OutDir = ?config(priv_dir,Config),
 
1553
    ?line true = code:add_patha(?config(priv_dir,Config)),
 
1554
    ?line ok = ber1(ber_modules(),DataDir,OutDir).
 
1555
 
 
1556
 
 
1557
ber1([M|T],DataDir,OutDir) ->
 
1558
    ?line ok = asn1ct:compile(DataDir ++ M,[?BER,{outdir,OutDir}]),
 
1559
    ?line ok = asn1ct:test(list_to_atom(M)),
 
1560
    ber1(T,DataDir,OutDir);
 
1561
ber1([],_,_) ->
 
1562
    ok.
 
1563
 
 
1564
default_per(suite) ->[];
 
1565
default_per(Config) ->
 
1566
    default1(?PER,Config,[]).
 
1567
 
 
1568
default_per_opt(suite) -> [];
 
1569
default_per_opt(Config) ->
 
1570
    ?per_bit_opt(default1(?PER,Config,[optimize])),
 
1571
    default1(?PER,Config,[optimize]).
 
1572
 
 
1573
default_ber(suite) ->[];
 
1574
default_ber(Config) ->
 
1575
    default1(?BER,Config,[]).
 
1576
 
 
1577
default1(Rule,Config,Options) ->
 
1578
    ?line DataDir = ?config(data_dir,Config),
 
1579
    ?line OutDir = ?config(priv_dir,Config),
 
1580
    ?line true = code:add_patha(?config(priv_dir,Config)),
 
1581
    ?line ok = asn1ct:compile(DataDir ++ "Def",[Rule,{outdir,OutDir}]++Options),
 
1582
    ?line {ok,Bytes1} = asn1_wrapper:encode('Def','Def1',#'Def1'{bool0 = true,
 
1583
                                                 bool1 = true,
 
1584
                                                 bool2 = true,
 
1585
                                                 bool3 = true}),
 
1586
    ?line {ok,{'Def1',true,true,true,true}} = asn1_wrapper:decode('Def','Def1',lists:flatten(Bytes1)),
 
1587
    
 
1588
    ?line {ok,Bytes2} = asn1_wrapper:encode('Def','Def1',#'Def1'{bool0 = true}),
 
1589
    ?line {ok,{'Def1',true,false,false,false}} = asn1_wrapper:decode('Def','Def1',lists:flatten(Bytes2)),
 
1590
 
 
1591
    ?line {ok,Bytes3} = asn1_wrapper:encode('Def','Def1',#'Def1'{bool0 = true,bool2=false}),
 
1592
    ?line {ok,{'Def1',true,false,false,false}} = asn1_wrapper:decode('Def','Def1',lists:flatten(Bytes3)).
 
1593
    
 
1594
    
 
1595
value_test(suite) ->[];
 
1596
value_test(Config) ->
 
1597
    ?line DataDir = ?config(data_dir,Config),
 
1598
    ?line OutDir = ?config(priv_dir,Config),
 
1599
    ?line true = code:add_patha(?config(priv_dir,Config)),
 
1600
    ?line ok = asn1ct:compile(DataDir ++ "ObjIdValues",[?BER,{outdir,OutDir}]),
 
1601
    ?line {ok,_} = asn1_wrapper:encode('ObjIdValues','ObjIdType','ObjIdValues':'mobileDomainId'()),
 
1602
    ?line ok = asn1ct:compile(DataDir ++ "ObjIdValues",[?PER,{outdir,OutDir}]),
 
1603
    ?line {ok,_} = asn1_wrapper:encode('ObjIdValues','ObjIdType','ObjIdValues':'mobileDomainId'()),
 
1604
    ?line ok = test_bad_values:tests(Config),
 
1605
    ok.
 
1606
 
 
1607
 
 
1608
constructed(suite) ->
 
1609
     [];
 
1610
constructed(Config) ->
 
1611
    ?line DataDir = ?config(data_dir,Config),
 
1612
    ?line OutDir = ?config(priv_dir,Config),
 
1613
    ?line true = code:add_patha(?config(priv_dir,Config)),
 
1614
    ?line ok = asn1ct:compile(DataDir ++ "Constructed",[?BER,{outdir,OutDir}]),
 
1615
    ?line {ok,B} = asn1_wrapper:encode('Constructed','S',{'S',false}),
 
1616
    ?line [40,3,1,1,0] = lists:flatten(B),
 
1617
    ?line {ok,B1} = asn1_wrapper:encode('Constructed','S2',{'S2',false}),
 
1618
    ?line [40,5,48,3,1,1,0] = lists:flatten(B1),
 
1619
    ?line {ok,B2} = asn1_wrapper:encode('Constructed','I',10),
 
1620
    ?line [136,1,10] = lists:flatten(B2),
 
1621
    ok.
 
1622
    
 
1623
ber_decode_error(suite) -> [];
 
1624
ber_decode_error(Config) ->
 
1625
    ?line ok = ber_decode_error:compile(Config,?BER,[]),
 
1626
    ?line ok = ber_decode_error:run([]),
 
1627
 
 
1628
    ?line ok = ?ber_driver(?BER,ber_decode_error:compile(Config,?BER,[driver])),
 
1629
    ?line ok = ?ber_driver(?BER,ber_decode_error:run([driver])),
 
1630
        ok.   
 
1631
 
 
1632
h323test(suite) -> 
 
1633
    [];
 
1634
h323test(Config) ->
 
1635
    ?line ok = h323test:compile(Config,?PER,[]),
 
1636
    ?line ok = h323test:run(?PER),
 
1637
    ?line ?per_bit_opt(h323test:compile(Config,?PER,[optimize])),
 
1638
    ?line ?per_bit_opt(h323test:run(?PER)),
 
1639
    ?line ?uper_bin(h323test:compile(Config,uper_bin,[])),
 
1640
    ?line ?uper_bin(h323test:run(uper_bin)),
 
1641
    ?line ok = h323test:compile(Config,?PER,[optimize]),
 
1642
    ?line ok = h323test:run(?PER),
 
1643
    ok.
 
1644
 
 
1645
per_GeneralString(suite) ->
 
1646
     [];
 
1647
per_GeneralString(Config) ->
 
1648
    case erlang:module_loaded('MULTIMEDIA-SYSTEM-CONTROL') of
 
1649
        true ->
 
1650
            ok;
 
1651
        false ->
 
1652
            h323test:compile(Config,?PER,[])
 
1653
    end,
 
1654
    UI = [109,64,1,57],
 
1655
    ?line {ok,_V} = asn1_wrapper:decode('MULTIMEDIA-SYSTEM-CONTROL',
 
1656
                                 'MultimediaSystemControlMessage',UI).
 
1657
 
 
1658
per_open_type(suite) ->
 
1659
    [];
 
1660
per_open_type(Config) ->
 
1661
    ?line DataDir = ?config(data_dir,Config),
 
1662
    ?line OutDir = ?config(priv_dir,Config),
 
1663
    ?line ok = asn1ct:compile(DataDir ++ "OpenType",[?PER,{outdir,OutDir}]),
 
1664
    Stype = {'Stype',10,true},
 
1665
    ?line {ok,Bytes} = asn1_wrapper:encode('OpenType','Ot',Stype),
 
1666
    ?line {ok,Stype} = asn1_wrapper:decode('OpenType','Ot',Bytes),
 
1667
 
 
1668
    ?line ?per_bit_opt(ok = asn1ct:compile(DataDir ++ "OpenType",
 
1669
                              [?PER,optimize,{outdir,OutDir}])),
 
1670
    ?line ?per_bit_opt({ok,Bytes}=asn1_wrapper:encode('OpenType','Ot',Stype)),
 
1671
    ?line ?per_bit_opt({ok,Stype}=asn1_wrapper:decode('OpenType','Ot',Bytes)),
 
1672
 
 
1673
    ?line ?uper_bin(ok = asn1ct:compile(DataDir ++ "OpenType",
 
1674
                              [uper_bin,{outdir,OutDir}])),
 
1675
    ?line ?uper_bin({ok,Bytes}=asn1_wrapper:encode('OpenType','Ot',Stype)),
 
1676
    ?line ?uper_bin({ok,Stype}=asn1_wrapper:decode('OpenType','Ot',Bytes)),
 
1677
 
 
1678
    ?line ok = asn1ct:compile(DataDir ++ "OpenType",
 
1679
                              [?PER,optimize,{outdir,OutDir}]),
 
1680
    ?line {ok,Bytes} = asn1_wrapper:encode('OpenType','Ot',Stype),
 
1681
    ?line {ok,Stype} = asn1_wrapper:decode('OpenType','Ot',Bytes).
 
1682
 
 
1683
testConstraints(suite) ->
 
1684
        [];
 
1685
testConstraints(Config) ->
 
1686
    ?line true = code:add_patha(?config(priv_dir,Config)),
 
1687
 
 
1688
    ?line testConstraints:compile(Config,?BER,[]),
 
1689
    ?line testConstraints:int_constraints(?BER),
 
1690
 
 
1691
    ?line ?ber_driver(?BER,testConstraints:compile(Config,?BER,[driver])),
 
1692
    ?line ?ber_driver(?BER,testConstraints:int_constraints(?BER)),
 
1693
 
 
1694
    ?line testConstraints:compile(Config,?PER,[]),
 
1695
    ?line testConstraints:int_constraints(?PER),
 
1696
    ?line testConstraints:refed_NNL_name(?PER),
 
1697
 
 
1698
    ?line ?per_bit_opt(testConstraints:compile(Config,?PER,[optimize])),
 
1699
    ?line ?per_bit_opt(testConstraints:int_constraints(?PER)),
 
1700
    ?line ?per_bit_opt(testConstraints:refed_NNL_name(?PER)),
 
1701
 
 
1702
    ?line ?uper_bin(testConstraints:compile(Config,uper_bin,[])),
 
1703
    ?line ?uper_bin(testConstraints:int_constraints(uper_bin)),
 
1704
    ?line ?uper_bin(testConstraints:refed_NNL_name(uper_bin)),
 
1705
 
 
1706
    ?line testConstraints:compile(Config,?PER,[optimize]),
 
1707
    ?line testConstraints:int_constraints(?PER),
 
1708
    ?line testConstraints:refed_NNL_name(?PER).
 
1709
 
 
1710
testSeqIndefinite(suite) -> [];
 
1711
testSeqIndefinite(Config) ->
 
1712
    ?line true = code:add_patha(?config(priv_dir,Config)),
 
1713
 
 
1714
    ?line testSeqIndefinite:compile(Config,?BER,[]),
 
1715
    ?line testSeqIndefinite:main(?BER),
 
1716
 
 
1717
    ?line ?ber_driver(?BER,testSeqIndefinite:compile(Config,?BER,[driver])),
 
1718
    ?line ?ber_driver(?BER,testSeqIndefinite:main(?BER)).
 
1719
 
 
1720
testSetIndefinite(suite) -> [];
 
1721
testSetIndefinite(Config) ->
 
1722
    ?line true = code:add_patha(?config(priv_dir,Config)),
 
1723
 
 
1724
    ?line testSetIndefinite:compile(Config,?BER,[]),
 
1725
    ?line testSetIndefinite:main(?BER),
 
1726
 
 
1727
    ?line ?ber_driver(?BER,testSetIndefinite:compile(Config,?BER,[driver])),
 
1728
    ?line ?ber_driver(?BER,testSetIndefinite:main(?BER)).
 
1729
 
 
1730
testChoiceIndefinite(suite) -> [];
 
1731
testChoiceIndefinite(Config) ->
 
1732
    ?line true = code:add_patha(?config(priv_dir,Config)),
 
1733
 
 
1734
    ?line testChoiceIndefinite:compile(Config,?BER,[]),
 
1735
    ?line testChoiceIndefinite:main(?BER),
 
1736
 
 
1737
    ?line ?ber_driver(?BER,testChoiceIndefinite:compile(Config,?BER,[driver])),
 
1738
    ?line ?ber_driver(?BER,testChoiceIndefinite:main(?BER)).
 
1739
 
 
1740
testInfObjectClass(suite) ->
 
1741
    [];
 
1742
testInfObjectClass(Config) ->
 
1743
    ?line true = code:add_patha(?config(priv_dir,Config)),
 
1744
    
 
1745
    ?line testInfObjectClass:compile(Config,?PER,[]),
 
1746
    ?line testInfObjectClass:main(?PER),
 
1747
    ?line testInfObj:compile(Config,?PER,[]),
 
1748
    ?line testInfObj:main(?PER),
 
1749
 
 
1750
    ?line ?per_bit_opt(testInfObjectClass:compile(Config,?PER,[optimize])),
 
1751
    ?line ?per_bit_opt(testInfObjectClass:main(?PER)),
 
1752
    ?line ?per_bit_opt(testInfObj:compile(Config,?PER,[optimize])),
 
1753
    ?line ?per_bit_opt(testInfObj:main(?PER)),
 
1754
 
 
1755
    ?line ?uper_bin(testInfObjectClass:compile(Config,uper_bin,[])),
 
1756
    ?line ?uper_bin(testInfObjectClass:main(uper_bin)),
 
1757
    ?line ?uper_bin(testInfObj:compile(Config,uper_bin,[])),
 
1758
    ?line ?uper_bin(testInfObj:main(uper_bin)),
 
1759
 
 
1760
    ?line testInfObjectClass:compile(Config,?PER,[optimize]),
 
1761
    ?line testInfObjectClass:main(?PER),
 
1762
    ?line testInfObj:compile(Config,?PER,[optimize]),
 
1763
    ?line testInfObj:main(?PER),
 
1764
 
 
1765
    ?line testInfObjectClass:compile(Config,?BER,[]),
 
1766
    ?line testInfObjectClass:main(?BER),
 
1767
    ?line testInfObj:compile(Config,?BER,[]),
 
1768
    ?line testInfObj:main(?BER),
 
1769
 
 
1770
    ?line ?ber_driver(?BER,testInfObjectClass:compile(Config,?BER,[driver])),
 
1771
    ?line ?ber_driver(?BER,testInfObjectClass:main(?BER)),
 
1772
    ?line ?ber_driver(?BER,testInfObj:compile(Config,?BER,[driver])),
 
1773
    ?line ?ber_driver(?BER,testInfObj:main(?BER)),
 
1774
 
 
1775
    ?line testInfObj:compile_RANAPfiles(Config,?PER,[]),
 
1776
 
 
1777
    ?line ?per_bit_opt(testInfObj:compile_RANAPfiles(Config,?PER,[optimize])),
 
1778
 
 
1779
    ?line ?uper_bin(testInfObj:compile_RANAPfiles(Config,uper_bin,[])),
 
1780
 
 
1781
    ?line testInfObj:compile_RANAPfiles(Config,?PER,[optimize]),
 
1782
 
 
1783
    ?line testInfObj:compile_RANAPfiles(Config,?BER,[]).
 
1784
 
 
1785
testParameterizedInfObj(suite) ->
 
1786
    [];
 
1787
testParameterizedInfObj(Config) ->
 
1788
    ?line true = code:add_patha(?config(priv_dir,Config)),
 
1789
    
 
1790
    ?line testParameterizedInfObj:compile(Config,?PER,[]),
 
1791
    ?line testParameterizedInfObj:main(?PER),
 
1792
 
 
1793
    ?line ?per_bit_opt(testParameterizedInfObj:compile(Config,?PER,[optimize])),
 
1794
    ?line ?per_bit_opt(testParameterizedInfObj:main(?PER)),
 
1795
 
 
1796
    ?line ?uper_bin(testParameterizedInfObj:compile(Config,uper_bin,[])),
 
1797
    ?line ?uper_bin(testParameterizedInfObj:main(uper_bin)),
 
1798
 
 
1799
    ?line testParameterizedInfObj:compile(Config,?PER,[optimize]),
 
1800
    ?line testParameterizedInfObj:main(?PER),
 
1801
 
 
1802
    ?line testParameterizedInfObj:compile(Config,?BER,[]),
 
1803
    ?line testParameterizedInfObj:main(?BER),
 
1804
 
 
1805
    ?line ?ber_driver(?BER,testParameterizedInfObj:compile(Config,?BER,[driver])),
 
1806
    ?line ?ber_driver(?BER,testParameterizedInfObj:main(?BER)).
 
1807
 
 
1808
testMergeCompile(suite) ->
 
1809
    [];
 
1810
testMergeCompile(Config) ->
 
1811
    ?line true = code:add_patha(?config(priv_dir,Config)),
 
1812
    
 
1813
    ?line testMergeCompile:compile(Config,?PER,[]),
 
1814
    ?line testMergeCompile:main(?PER),
 
1815
    ?line testMergeCompile:mvrasn(?PER),
 
1816
 
 
1817
    ?line ?per_bit_opt(testMergeCompile:compile(Config,?PER,[optimize])),
 
1818
    ?line ?per_bit_opt(testMergeCompile:main(?PER)),
 
1819
    ?line ?per_bit_opt(testMergeCompile:mvrasn(?PER)),
 
1820
 
 
1821
    ?line ?uper_bin(testMergeCompile:compile(Config,uper_bin,[])),
 
1822
    ?line ?uper_bin(testMergeCompile:main(uper_bin)),
 
1823
    ?line ?uper_bin(testMergeCompile:mvrasn(uper_bin)),
 
1824
 
 
1825
    ?line testMergeCompile:compile(Config,?BER,[]),
 
1826
    ?line testMergeCompile:main(?BER),
 
1827
    ?line testMergeCompile:mvrasn(?BER),
 
1828
 
 
1829
    ?line ?ber_driver(?BER,testMergeCompile:compile(Config,?BER,[driver])),
 
1830
    ?line ?ber_driver(?BER,testMergeCompile:main(?BER)),
 
1831
    ?line ?ber_driver(?BER,testMergeCompile:mvrasn(?BER)).
 
1832
 
 
1833
testobj(suite) ->
 
1834
    [];
 
1835
testobj(Config) ->
 
1836
    ?line true = code:add_patha(?config(priv_dir,Config)),
 
1837
    
 
1838
    ?line ok = testRANAP:compile(Config,?PER,[]),
 
1839
    ?line ok = testRANAP:testobj(?PER),
 
1840
    ?line ok = testParameterizedInfObj:ranap(?PER),
 
1841
    
 
1842
    ?line ?per_bit_opt(ok = testRANAP:compile(Config,?PER,[optimize])),
 
1843
    ?line ?per_bit_opt(ok = testRANAP:testobj(?PER)),
 
1844
    ?line ?per_bit_opt(ok = testParameterizedInfObj:ranap(?PER)),
 
1845
    
 
1846
    ?line ?uper_bin(ok = testRANAP:compile(Config,uper_bin,[])),
 
1847
    ?line ?uper_bin(ok = testRANAP:testobj(uper_bin)),
 
1848
    ?line ?uper_bin(ok = testParameterizedInfObj:ranap(uper_bin)),
 
1849
    
 
1850
    ?line ok = testRANAP:compile(Config,?PER,[optimize]),
 
1851
    ?line ok = testRANAP:testobj(?PER),
 
1852
    ?line ok = testParameterizedInfObj:ranap(?PER),
 
1853
 
 
1854
    ?line ok = testRANAP:compile(Config,?BER,[]),
 
1855
    ?line ok = testRANAP:testobj(?BER),
 
1856
    ?line ok = testParameterizedInfObj:ranap(?BER),
 
1857
 
 
1858
    ?line ?ber_driver(?BER,testRANAP:compile(Config,?BER,[driver])),
 
1859
    ?line ?ber_driver(?BER,testRANAP:testobj(?BER)),
 
1860
    ?line ?ber_driver(?BER,testParameterizedInfObj:ranap(?BER)).
 
1861
 
 
1862
 
 
1863
testDeepTConstr(suite) ->
 
1864
    [];
 
1865
testDeepTConstr(Config) ->
 
1866
    ?line true = code:add_patha(?config(priv_dir,Config)),
 
1867
 
 
1868
    ?line testDeepTConstr:compile(Config,?PER,[]),
 
1869
    ?line testDeepTConstr:main(?PER),
 
1870
 
 
1871
    ?line ?per_bit_opt(testDeepTConstr:compile(Config,?PER,[optimize])),
 
1872
    ?line ?per_bit_opt(testDeepTConstr:main(?PER)),
 
1873
 
 
1874
    ?line ?uper_bin(testDeepTConstr:compile(Config,uper_bin,[])),
 
1875
    ?line ?uper_bin(testDeepTConstr:main(uper_bin)),
 
1876
 
 
1877
    ?line testDeepTConstr:compile(Config,?PER,[optimize]),
 
1878
    ?line testDeepTConstr:main(?PER),
 
1879
 
 
1880
    ?line testDeepTConstr:compile(Config,?BER,[]),
 
1881
    ?line testDeepTConstr:main(?BER),
 
1882
 
 
1883
    ?line ?ber_driver(?BER,testDeepTConstr:compile(Config,?BER,[driver])),
 
1884
    ?line ?ber_driver(?BER,testDeepTConstr:main(?BER)).
 
1885
 
 
1886
testInvokeMod(suite) ->
 
1887
    [];
 
1888
testInvokeMod(Config) ->
 
1889
    ?line DataDir = ?config(data_dir,Config),
 
1890
    ?line OutDir = ?config(priv_dir,Config),
 
1891
    ?line true = code:add_patha(?config(priv_dir,Config)),
 
1892
 
 
1893
    ?line ok = asn1ct:compile(filename:join(DataDir,"PrimStrings"),[{outdir,OutDir}]),
 
1894
    ?line {ok,_Result1} = 'PrimStrings':encode('Bs1',[1,0,1,0]),
 
1895
    ?line ok = asn1ct:compile(filename:join(DataDir,"PrimStrings"),[?PER,{outdir,OutDir}]),
 
1896
    ?line {ok,_Result2} = 'PrimStrings':encode('Bs1',[1,0,1,0]).
 
1897
 
 
1898
testExport(suite) ->
 
1899
    [];
 
1900
testExport(Config) ->
 
1901
    ?line DataDir = ?config(data_dir,Config),
 
1902
    ?line OutDir = ?config(priv_dir,Config),
 
1903
    ?line true = code:add_patha(?config(priv_dir,Config)),
 
1904
 
 
1905
    ?line {error,{asn1,_Reason}} = asn1ct:compile(filename:join(DataDir,"IllegalExport"),[{outdir,OutDir}]).
 
1906
 
 
1907
testImport(suite) ->
 
1908
    [];
 
1909
testImport(Config) ->
 
1910
    ?line DataDir = ?config(data_dir,Config),
 
1911
    ?line _OutDir = ?config(priv_dir,Config),
 
1912
    ?line {error,_} = asn1ct:compile(filename:join(DataDir,"ImportsFrom"),[?BER]),
 
1913
    ok.
 
1914
 
 
1915
testMegaco(suite) ->
 
1916
    [];
 
1917
testMegaco(Config) ->
 
1918
    ?line true = code:add_patha(?config(priv_dir,Config)),
 
1919
    io:format("Config: ~p~n",[Config]),
 
1920
    ?line {ok,ModuleName1,ModuleName2} = testMegaco:compile(Config,?BER,[]),
 
1921
    ?line ok = testMegaco:main(ModuleName1,Config),
 
1922
    ?line ok = testMegaco:main(ModuleName2,Config),
 
1923
 
 
1924
    case ?BER of
 
1925
        ber_bin_v2 ->
 
1926
            ?line {ok,ModuleName3,ModuleName4} = testMegaco:compile(Config,?BER,[driver]),
 
1927
            ?line ok = testMegaco:main(ModuleName3,Config),
 
1928
            ?line ok = testMegaco:main(ModuleName4,Config);
 
1929
        _-> ok
 
1930
    end,
 
1931
 
 
1932
    ?line {ok,ModuleName5,ModuleName6} = testMegaco:compile(Config,?PER,[]),
 
1933
    ?line ok = testMegaco:main(ModuleName5,Config),
 
1934
    ?line ok = testMegaco:main(ModuleName6,Config),
 
1935
 
 
1936
    ?line ?per_bit_opt({ok,ModuleName5,ModuleName6} = testMegaco:compile(Config,?PER,[optimize])),
 
1937
    ?line ?per_bit_opt(ok = testMegaco:main(ModuleName5,Config)),
 
1938
    ?line ?per_bit_opt(ok = testMegaco:main(ModuleName6,Config)),
 
1939
 
 
1940
    ?line ?uper_bin({ok,ModuleName5,ModuleName6} = testMegaco:compile(Config,uper_bin,[])),
 
1941
    ?line ?uper_bin(ok = testMegaco:main(ModuleName5,Config)),
 
1942
    ?line ?uper_bin(ok = testMegaco:main(ModuleName6,Config)),
 
1943
 
 
1944
    ?line {ok,ModuleName7,ModuleName8} = testMegaco:compile(Config,?PER,[optimize]),
 
1945
    ?line ok = testMegaco:main(ModuleName7,Config),
 
1946
    ?line ok = testMegaco:main(ModuleName8,Config).
 
1947
 
 
1948
 
 
1949
testMvrasn6(suite) -> [];
 
1950
testMvrasn6(Config) ->
 
1951
    ?line true = code:add_patha(?config(priv_dir,Config)),
 
1952
 
 
1953
    ?line testMvrasn6:compile(Config,?BER),
 
1954
    ?line testMvrasn6:main().
 
1955
 
 
1956
testContextSwitchingTypes(suite) -> [];
 
1957
testContextSwitchingTypes(Config) ->
 
1958
    ?line true = code:add_patha(?config(priv_dir,Config)),
 
1959
 
 
1960
    ?line testContextSwitchingTypes:compile(Config,?BER,[]),
 
1961
    ?line testContextSwitchingTypes:test(),
 
1962
 
 
1963
    ?line ?ber_driver(?BER,testContextSwitchingTypes:compile(Config,?BER,[driver])),
 
1964
    ?line ?ber_driver(?BER,testContextSwitchingTypes:test()),
 
1965
 
 
1966
    ?line testContextSwitchingTypes:compile(Config,?PER,[]),
 
1967
    ?line testContextSwitchingTypes:test(),
 
1968
 
 
1969
    ?line ?per_bit_opt(testContextSwitchingTypes:compile(Config,?PER,[optimize])),
 
1970
    ?line ?per_bit_opt(testContextSwitchingTypes:test()),
 
1971
 
 
1972
    ?line ?uper_bin(testContextSwitchingTypes:compile(Config,uper_bin,[])),
 
1973
    ?line ?uper_bin(testContextSwitchingTypes:test()),
 
1974
 
 
1975
    ?line testContextSwitchingTypes:compile(Config,?PER,[optimize]),
 
1976
    ?line testContextSwitchingTypes:test().
 
1977
 
 
1978
testTypeValueNotation(suite) -> [];
 
1979
testTypeValueNotation(Config) ->
 
1980
    ?line true = code:add_patha(?config(priv_dir,Config)),
 
1981
 
 
1982
    case ?BER of
 
1983
        Ber when Ber == ber; Ber == ber_bin ->
 
1984
            ?line testTypeValueNotation:compile(Config,?BER,[]),
 
1985
            ?line testTypeValueNotation:main(?BER,dummy);
 
1986
        _ ->
 
1987
            ok
 
1988
    end,
 
1989
 
 
1990
    ?line ?ber_driver(?BER,testTypeValueNotation:compile(Config,?BER,[driver])),
 
1991
    ?line ?ber_driver(?BER,testTypeValueNotation:main(?BER,optimize)),
 
1992
 
 
1993
    case ?BER of
 
1994
        Ber2 when Ber2 == ber; Ber2 == ber_bin ->
 
1995
            ?line testTypeValueNotation:compile(Config,?PER,[]),
 
1996
            ?line testTypeValueNotation:main(?PER,dummy);
 
1997
        _ ->
 
1998
            ok
 
1999
    end,
 
2000
 
 
2001
    ?line ?per_bit_opt(testTypeValueNotation:compile(Config,?PER,[optimize])),
 
2002
    ?line ?per_bit_opt(testTypeValueNotation:main(?PER,optimize)),
 
2003
 
 
2004
    ?line ?uper_bin(testTypeValueNotation:compile(Config,uper_bin,[])),
 
2005
    ?line ?uper_bin(testTypeValueNotation:main(uper_bin,optimize)),
 
2006
    case ?BER of
 
2007
        Ber3 when Ber3 == ber; Ber3 == ber_bin ->
 
2008
            ?line testTypeValueNotation:compile(Config,?PER,[optimize]),
 
2009
            ?line testTypeValueNotation:main(?PER,optimize);
 
2010
        _ ->
 
2011
            ok
 
2012
     end.
 
2013
 
 
2014
testOpenTypeImplicitTag(suite) -> [];
 
2015
testOpenTypeImplicitTag(Config) ->
 
2016
    ?line true = code:add_patha(?config(priv_dir,Config)),
 
2017
 
 
2018
    ?line testOpenTypeImplicitTag:compile(Config,?BER,[]),
 
2019
    ?line testOpenTypeImplicitTag:main(?BER),
 
2020
 
 
2021
    ?line ?ber_driver(?BER,testOpenTypeImplicitTag:compile(Config,?BER,[driver])),
 
2022
    ?line ?ber_driver(?BER,testOpenTypeImplicitTag:main(?BER)),
 
2023
 
 
2024
    ?line testOpenTypeImplicitTag:compile(Config,?PER,[]),
 
2025
    ?line testOpenTypeImplicitTag:main(?PER),
 
2026
 
 
2027
    ?line ?per_bit_opt(testOpenTypeImplicitTag:compile(Config,?PER,[optimize])),
 
2028
    ?line ?per_bit_opt(testOpenTypeImplicitTag:main(?PER)),
 
2029
 
 
2030
    ?line ?uper_bin(testOpenTypeImplicitTag:compile(Config,uper_bin,[])),
 
2031
    ?line ?uper_bin(testOpenTypeImplicitTag:main(uper_bin)),
 
2032
 
 
2033
    ?line testOpenTypeImplicitTag:compile(Config,?PER,[optimize]),
 
2034
    ?line testOpenTypeImplicitTag:main(?PER).
 
2035
 
 
2036
duplicate_tags(suite) -> [];
 
2037
duplicate_tags(Config) ->
 
2038
        ?line DataDir = ?config(data_dir,Config),
 
2039
        {error,{asn1,[{error,{type,_,_,'SeqOpt1Imp',{asn1,{duplicates_of_the_tags,_}}}}]}} = 
 
2040
        asn1ct:compile(filename:join(DataDir,"SeqOptional2"),[abs]),
 
2041
        ok.
 
2042
 
 
2043
rtUI(suite) -> [];
 
2044
rtUI(Config) -> 
 
2045
    ?line DataDir = ?config(data_dir,Config),
 
2046
    ?line ok = asn1ct:compile(filename:join(DataDir,"Prim"),[?BER]),
 
2047
    ?line {ok,_} = asn1rt:info('Prim'),
 
2048
 
 
2049
    ?line ok = asn1ct:compile(filename:join(DataDir,"Prim"),[?PER]),
 
2050
    ?line {ok,_} = asn1rt:info('Prim'),
 
2051
 
 
2052
    ?line ok = asn1rt:load_driver(),
 
2053
    ?line ok = asn1rt:load_driver(),
 
2054
    ?line ok = asn1rt:unload_driver().
 
2055
 
 
2056
testROSE(suite) -> [];
 
2057
testROSE(Config) -> 
 
2058
    ?line true = code:add_patha(?config(priv_dir,Config)),
 
2059
 
 
2060
    ?line testROSE:compile(Config,?BER,[]),
 
2061
 
 
2062
    ?line testROSE:compile(Config,?PER,[]),
 
2063
    ?line ?per_bit_opt(testROSE:compile(Config,?PER,[optimize])),
 
2064
    ?line ?uper_bin(testROSE:compile(Config,uper_bin,[])),
 
2065
    ?line testROSE:compile(Config,?PER,[optimize]).
 
2066
 
 
2067
testINSTANCE_OF(suite) -> [];
 
2068
testINSTANCE_OF(Config) ->
 
2069
    ?line testINSTANCE_OF:compile(Config,?BER,[]),
 
2070
    ?line testINSTANCE_OF:main(?BER),
 
2071
 
 
2072
    ?line ?ber_driver(?BER,testINSTANCE_OF:compile(Config,?BER,[driver])),
 
2073
    ?line ?ber_driver(?BER,testINSTANCE_OF:main(?BER)),
 
2074
 
 
2075
    ?line testINSTANCE_OF:compile(Config,?PER,[]),
 
2076
    ?line testINSTANCE_OF:main(?PER),
 
2077
 
 
2078
    ?line ?per_bit_opt(testINSTANCE_OF:compile(Config,?PER,[optimize])),
 
2079
    ?line ?per_bit_opt(testINSTANCE_OF:main(?PER)),
 
2080
 
 
2081
    ?line ?uper_bin(testINSTANCE_OF:compile(Config,uper_bin,[])),
 
2082
    ?line ?uper_bin(testINSTANCE_OF:main(uper_bin)),
 
2083
 
 
2084
    ?line testINSTANCE_OF:compile(Config,?PER,[optimize]),
 
2085
    ?line testINSTANCE_OF:main(?PER).
 
2086
 
 
2087
testTCAP(suite) -> [];
 
2088
testTCAP(Config) ->
 
2089
    ?line true = code:add_patha(?config(priv_dir,Config)),
 
2090
 
 
2091
    ?line testTCAP:compile(Config,?BER,[]),
 
2092
    ?line testTCAP:test(?BER,Config),
 
2093
 
 
2094
    ?line ?ber_driver(?BER,testTCAP:compile(Config,?BER,[driver])),
 
2095
    ?line ?ber_driver(?BER,testTCAP:test(?BER,Config)),
 
2096
 
 
2097
    ?line ?ber_driver(?BER,testTCAP:compile_asn1config(Config,?BER,[asn1config])),
 
2098
    ?line ?ber_driver(?BER,testTCAP:test_asn1config()).
 
2099
 
 
2100
testDER(suite) ->[];
 
2101
testDER(Config) ->
 
2102
    ?line true = code:add_patha(?config(priv_dir,Config)),
 
2103
 
 
2104
    ?line testDER:compile(Config,?BER,[]),
 
2105
    ?line testDER:test(),
 
2106
 
 
2107
    ?line ?ber_driver(?BER,testDER:compile(Config,?BER,[driver])),
 
2108
    ?line ?ber_driver(?BER,testDER:test()),
 
2109
 
 
2110
    ?line testParamBasic:compile_der(Config,?BER),
 
2111
    ?line testParamBasic_cases(der),
 
2112
 
 
2113
 
 
2114
    ?line testSeqSetDefaultVal:compile(Config,?BER),
 
2115
    ?line testSeqSetDefaultVal_cases(?BER).
 
2116
 
 
2117
testSeqSetDefaultVal_cases(?BER) ->
 
2118
    ?line testSeqSetDefaultVal:main(?BER).
 
2119
 
 
2120
 
 
2121
specialized_decodes(suite) -> [];
 
2122
specialized_decodes(Config) ->
 
2123
    ?line test_partial_incomplete_decode:compile(Config,?BER,[optimize]),
 
2124
    ?line test_partial_incomplete_decode:test(?BER,Config),
 
2125
    ?line test_selective_decode:test(?BER,Config).
 
2126
 
 
2127
special_decode_performance(suite) ->[];
 
2128
special_decode_performance(Config) ->
 
2129
    ?line ?ber_driver(?BER,test_special_decode_performance:compile(Config,?BER)),
 
2130
    ?line ?ber_driver(?BER,test_special_decode_performance:go(all)).
 
2131
 
 
2132
 
 
2133
test_driver_load(suite) -> [];
 
2134
test_driver_load(Config) ->
 
2135
    ?line test_driver_load:compile(Config,?PER),
 
2136
    ?line test_driver_load:test(?PER,5).
 
2137
 
 
2138
test_ParamTypeInfObj(suite) -> [];
 
2139
test_ParamTypeInfObj(Config) ->
 
2140
    ?line DataDir = ?config(data_dir,Config),
 
2141
    ?line ok = asn1ct:compile(filename:join(DataDir,"IN-CS-1-Datatypes"),[ber_bin]).
 
2142
 
 
2143
test_WS_ParamClass(suite) -> [];
 
2144
test_WS_ParamClass(Config) ->
 
2145
    ?line DataDir = ?config(data_dir,Config),
 
2146
    ?line ok = asn1ct:compile(filename:join(DataDir,"InformationFramework"),
 
2147
                                [ber_bin]).
 
2148
 
 
2149
test_Defed_ObjectIdentifier(suite) -> [];
 
2150
test_Defed_ObjectIdentifier(Config) ->
 
2151
    ?line DataDir = ?config(data_dir,Config),
 
2152
    ?line ok = asn1ct:compile(filename:join(DataDir,"UsefulDefinitions"),
 
2153
                                [ber_bin]).
 
2154
 
 
2155
testSelectionType(suite) -> [];
 
2156
testSelectionType(Config) ->
 
2157
 
 
2158
    ?line ok = testSelectionTypes:compile(Config,?BER,[]),
 
2159
    ?line {ok,_}  = testSelectionTypes:test(),
 
2160
 
 
2161
    ?line ok = testSelectionTypes:compile(Config,?PER,[]),
 
2162
    ?line {ok,_}  = testSelectionTypes:test().
 
2163
 
 
2164
testSSLspecs(suite) -> [];
 
2165
testSSLspecs(Config) ->
 
2166
 
 
2167
    ?line ok = testSSLspecs:compile(Config,?BER,
 
2168
                                [optimize,compact_bit_string,der]),
 
2169
    ?line testSSLspecs:run(?BER),
 
2170
 
 
2171
    case code:which(asn1ct) of
 
2172
       cover_compiled ->
 
2173
           ok;
 
2174
       _ ->
 
2175
           ?line ok = testSSLspecs:compile_inline(Config,?BER),
 
2176
           ?line ok = testSSLspecs:run_inline(?BER)
 
2177
    end.
 
2178
 
 
2179
testNortel(suite) -> [];
 
2180
testNortel(Config) ->
 
2181
    ?line DataDir = ?config(data_dir,Config),
 
2182
 
 
2183
    ?line ok = asn1ct:compile(filename:join(DataDir,"Nortel"),[?BER]),
 
2184
    ?line ok = asn1ct:compile(filename:join(DataDir,"Nortel"),
 
2185
                                [?BER,optimize]),
 
2186
    ?line ok = asn1ct:compile(filename:join(DataDir,"Nortel"),
 
2187
                                [?BER,optimize,driver]),
 
2188
    ?line ok = asn1ct:compile(filename:join(DataDir,"Nortel"),[?PER]),
 
2189
    ?line ?per_bit_opt(ok = asn1ct:compile(filename:join(DataDir,"Nortel"),
 
2190
                                [?PER,optimize])),
 
2191
    ?line ?uper_bin(ok = asn1ct:compile(filename:join(DataDir,"Nortel"),[uper_bin])),
 
2192
    ?line ok = asn1ct:compile(filename:join(DataDir,"Nortel"),
 
2193
                                [?PER,optimize]).
 
2194
test_undecoded_rest(suite) -> [];
 
2195
test_undecoded_rest(Config) ->
 
2196
 
 
2197
    ?line ok = test_undecoded_rest:compile(Config,?BER,[]),
 
2198
    ?line ok = test_undecoded_rest:test([]),
 
2199
 
 
2200
    ?line ok = test_undecoded_rest:compile(Config,?BER,[undec_rest]),
 
2201
    ?line ok = test_undecoded_rest:test(undec_rest),
 
2202
 
 
2203
    ?line ok = test_undecoded_rest:compile(Config,?PER,[]),
 
2204
    ?line ok = test_undecoded_rest:test([]),
 
2205
 
 
2206
    ?line ?per_bit_opt(ok = test_undecoded_rest:compile(Config,?PER,[optimize,undec_rest])),
 
2207
    ?line ?per_bit_opt(ok = test_undecoded_rest:test(undec_rest)),
 
2208
 
 
2209
    ?line ?uper_bin(ok = test_undecoded_rest:compile(Config,uper_bin,[undec_rest])),
 
2210
    ?line ?uper_bin(ok = test_undecoded_rest:test(undec_rest)),
 
2211
 
 
2212
    ?line ok = test_undecoded_rest:compile(Config,?PER,[undec_rest]),
 
2213
    ?line ok = test_undecoded_rest:test(undec_rest).
 
2214
 
 
2215
test_inline(suite) -> [];
 
2216
test_inline(Config) ->
 
2217
    case code:which(asn1ct) of
 
2218
       cover_compiled ->
 
2219
          {skip,"Not runnable when cover compiled"};
 
2220
       _  ->
 
2221
          ?line ok=test_inline:compile(Config,?BER,[]),
 
2222
          ?line test_inline:main(?BER),
 
2223
          ?line test_inline:inline1(Config,?BER,[]),
 
2224
          ?line test_inline:performance2()
 
2225
    end.
 
2226
 
 
2227
%test_inline_prf(suite) -> [];
 
2228
%test_inline_prf(Config) ->
 
2229
%    ?line test_inline:performance(Config).
 
2230
 
 
2231
testTcapsystem(suite) -> [];
 
2232
testTcapsystem(Config) ->
 
2233
    ?line ok=testTcapsystem:compile(Config,?BER,[]).
 
2234
 
 
2235
testNBAPsystem(suite) -> [];
 
2236
testNBAPsystem(Config) ->
 
2237
    ?line ok=testNBAPsystem:compile(Config,?PER,?per_optimize(?BER)),
 
2238
    ?line ok=testNBAPsystem:test(?PER,Config).
 
2239
 
 
2240
test_compile_options(suite) -> [];
 
2241
test_compile_options(Config) ->
 
2242
    case code:which(asn1ct) of
 
2243
       cover_compiled ->
 
2244
          {skip,"Not runnable when cover compiled"};
 
2245
       _  ->
 
2246
          ?line ok = test_compile_options:wrong_path(Config),
 
2247
          ?line ok = test_compile_options:path(Config),
 
2248
          ?line ok = test_compile_options:noobj(Config),
 
2249
          ?line ok = test_compile_options:record_name_prefix(Config),
 
2250
          ?line ok = test_compile_options:verbose(Config)
 
2251
    end.
 
2252
testDoubleEllipses(suite) ->  [];
 
2253
testDoubleEllipses(Config) ->
 
2254
    ?line testDoubleEllipses:compile(Config,?BER,[]),
 
2255
    ?line testDoubleEllipses:main(?BER),
 
2256
    ?line ?ber_driver(?BER,testDoubleEllipses:compile(Config,?BER,[driver])),
 
2257
    ?line ?ber_driver(?BER,testDoubleEllipses:main(?BER)),
 
2258
    ?line ?per_bit_opt(testDoubleEllipses:compile(Config,?PER,[optimize])),
 
2259
    ?line ?per_bit_opt(testDoubleEllipses:main(?PER)),
 
2260
    ?line ?uper_bin(testDoubleEllipses:compile(Config,uper_bin,[])),
 
2261
    ?line ?uper_bin(testDoubleEllipses:main(uper_bin)),
 
2262
    ?line testDoubleEllipses:compile(Config,?PER,?per_optimize(?BER)),
 
2263
    ?line testDoubleEllipses:main(?PER).
 
2264
 
 
2265
test_modified_x420(suite) -> [];
 
2266
test_modified_x420(Config) ->
 
2267
    ?line test_modified_x420:compile(Config),
 
2268
    ?line test_modified_x420:test_io(Config).
 
2269
 
 
2270
testX420(suite) -> [];
 
2271
testX420(Config) ->
 
2272
    ?line testX420:compile(?BER,[der],Config),
 
2273
    ?line ok = testX420:ticket7759(?BER,Config),
 
2274
    ?line testX420:compile(?PER,[],Config).
 
2275
 
 
2276
test_x691(suite) -> [];
 
2277
test_x691(Config) ->
 
2278
    case ?PER of
 
2279
        per ->
 
2280
           ?line ok = test_x691:compile(Config,uper_bin,[]),
 
2281
           ?line true = test_x691:cases(uper_bin,unaligned),
 
2282
           ?line ok = test_x691:compile(Config,?PER,[]),
 
2283
           ?line true = test_x691:cases(?PER,aligned),
 
2284
%%         ?line ok = asn1_test_lib:ticket_7678(Config,[]),
 
2285
           ?line ok = asn1_test_lib:ticket_7708(Config,[]),
 
2286
           ?line ok = asn1_test_lib:ticket_7763(Config);
 
2287
        _ ->
 
2288
           ?line ok = test_x691:compile(Config,?PER,?per_optimize(?BER)),
 
2289
           ?line true = test_x691:cases(?PER,aligned)
 
2290
    end.
 
2291
%%    ?line ok = asn1_test_lib:ticket_7876(Config,?PER,[]),
 
2292
%%    ?line ok = asn1_test_lib:ticket_7876(Config,?PER,[compact_bit_string]),
 
2293
%%    ?line ok = asn1_test_lib:ticket_7876(Config,?PER,[optimize]),
 
2294
%%    ?line ok = asn1_test_lib:ticket_7876(Config,?PER,[optimize,compact_bit_string]).
 
2295
 
 
2296
 
 
2297
ticket_6143(suite) -> [];
 
2298
ticket_6143(Config) ->
 
2299
    ?line ok = test_compile_options:ticket_6143(Config).
 
2300
 
 
2301
testExtensionAdditionGroup(suite) -> [];
 
2302
testExtensionAdditionGroup(Config) ->
 
2303
        ?line DataDir = ?config(data_dir,Config),
 
2304
        ?line PrivDir = ?config(priv_dir,Config),
 
2305
        ?line Path = code:get_path(),
 
2306
        ?line code:add_patha(PrivDir),
 
2307
        DoIt = fun(Erule) ->
 
2308
                ?line ok = asn1ct:compile(filename:join(DataDir,"Extension-Addition-Group"),[Erule,{outdir,PrivDir}]),
 
2309
                ?line {ok,_M} = compile:file(filename:join(DataDir,"extensionAdditionGroup"),[{i,PrivDir},{outdir,PrivDir},debug_info]),
 
2310
                ?line ok = extensionAdditionGroup:run(Erule)
 
2311
               end,
 
2312
        ?line [DoIt(Rule)|| Rule <- [per_bin,uper_bin,ber_bin]],
 
2313
        ?line code:set_path(Path).
 
2314
 
 
2315
 
 
2316
 
 
2317
% parse_modules() ->
 
2318
%       ["ImportsFrom"].
 
2319
 
 
2320
per_modules() ->
 
2321
        [X || X <- test_modules()].
 
2322
ber_modules() ->
 
2323
        [X || X <- test_modules(),
 
2324
                X =/= "CommonDataTypes",
 
2325
                X =/= "DS-EquipmentUser-CommonFunctionOrig-TransmissionPath",
 
2326
                X =/= "H323-MESSAGES",
 
2327
                X =/= "H235-SECURITY-MESSAGES",
 
2328
                X =/= "MULTIMEDIA-SYSTEM-CONTROL"].
 
2329
test_modules() ->
 
2330
    _Modules = [
 
2331
               "BitStr",
 
2332
               "CommonDataTypes",
 
2333
               "Constraints",
 
2334
               "ContextSwitchingTypes",
 
2335
               "DS-EquipmentUser-CommonFunctionOrig-TransmissionPath",
 
2336
               "Enum",
 
2337
               "From",
 
2338
               "H235-SECURITY-MESSAGES",
 
2339
               "H323-MESSAGES",
 
2340
               %%"MULTIMEDIA-SYSTEM-CONTROL", recursive type , problem for asn1ct:value
 
2341
               "Import",
 
2342
               "Int",
 
2343
               "MAP-commonDataTypes",
 
2344
% ambigous tags        "MAP-insertSubscriberData-def",
 
2345
               "Null",
 
2346
               "Octetstr",
 
2347
               "One",
 
2348
               "P-Record",
 
2349
               "P",
 
2350
%              "PDUs",
 
2351
               "Person",
 
2352
               "PrimStrings",
 
2353
               "Real",
 
2354
               "XSeq",
 
2355
               "XSeqOf",
 
2356
               "XSet",
 
2357
               "XSetOf",
 
2358
               "String",
 
2359
               "SwCDR",
 
2360
%              "Syntax",
 
2361
               "Time"
 
2362
% ANY          "Tst",
 
2363
%              "Two",
 
2364
% errors that should be detected      "UndefType"
 
2365
] ++
 
2366
        [
 
2367
         "SeqSetLib", % must be compiled before Seq and Set
 
2368
         "Seq",
 
2369
         "Set",
 
2370
         "SetOf",
 
2371
         "SeqOf",
 
2372
         "Prim",
 
2373
         "Cho",
 
2374
         "Def",
 
2375
         "Opt",
 
2376
         "ELDAPv3",
 
2377
         "LDAP"
 
2378
        ].
 
2379
 
 
2380
 
 
2381
%%
 
2382
%% %CopyrightBegin%
 
2383
%% 
 
2384
%% Copyright Ericsson AB 2005-2010. All Rights Reserved.
 
2385
%% 
 
2386
%% The contents of this file are subject to the Erlang Public License,
 
2387
%% Version 1.1, (the "License"); you may not use this file except in
 
2388
%% compliance with the License. You should have received a copy of the
 
2389
%% Erlang Public License along with this software. If not, it can be
 
2390
%% retrieved online at http://www.erlang.org/.
 
2391
%% 
 
2392
%% Software distributed under the License is distributed on an "AS IS"
 
2393
%% basis, WITHOUT WARRANTY OF ANY KIND, either express or implied. See
 
2394
%% the License for the specific language governing rights and limitations
 
2395
%% under the License.
 
2396
%% 
 
2397
%% %CopyrightEnd%
 
2398
%%
 
2399
%%
 
2400
 
 
2401
common() -> 
 
2402
[{group, app_test}, {group, appup_test}, testTimer_ber,
 
2403
 testTimer_ber_bin, testTimer_ber_bin_opt,
 
2404
 testTimer_ber_bin_opt_driver, testTimer_per,
 
2405
 testTimer_per_bin, testTimer_per_bin_opt,
 
2406
 testTimer_uper_bin, testComment, testName2Number].
 
2407
 
 
2408
 
 
2409
 
 
2410
testTimer_ber(suite) -> [];
 
2411
testTimer_ber(Config) ->
 
2412
    ?line testTimer:compile(Config,ber,[]),
 
2413
    ?line testTimer:go(Config,ber).
 
2414
 
 
2415
testTimer_ber_bin(suite) -> [];
 
2416
testTimer_ber_bin(Config) ->
 
2417
    ?line testTimer:compile(Config,ber_bin,[]),
 
2418
    ?line testTimer:go(Config,ber_bin).
 
2419
 
 
2420
testTimer_ber_bin_opt(suite) -> [];
 
2421
testTimer_ber_bin_opt(Config) ->
 
2422
    ?line testTimer:compile(Config,ber_bin,[optimize]),
 
2423
    ?line testTimer:go(Config,ber_bin).
 
2424
 
 
2425
testTimer_ber_bin_opt_driver(suite) -> [];
 
2426
testTimer_ber_bin_opt_driver(Config) ->
 
2427
    ?line testTimer:compile(Config,ber_bin,[optimize,driver]),
 
2428
    ?line testTimer:go(Config,ber_bin).
 
2429
 
 
2430
testTimer_per(suite) -> [];
 
2431
testTimer_per(Config) ->
 
2432
    ?line testTimer:compile(Config,per,[]),
 
2433
    ?line testTimer:go(Config,per).
 
2434
 
 
2435
testTimer_per_bin(suite) -> [];
 
2436
testTimer_per_bin(Config) ->
 
2437
    ?line testTimer:compile(Config,per_bin,[]),
 
2438
    ?line testTimer:go(Config,per_bin).
 
2439
 
 
2440
testTimer_per_bin_opt(suite) -> [];
 
2441
testTimer_per_bin_opt(Config) ->
 
2442
    ?line testTimer:compile(Config,per_bin,[optimize]),
 
2443
    ?line testTimer:go(Config,per_bin).
 
2444
 
 
2445
 
 
2446
testTimer_uper_bin(suite) -> [];
 
2447
testTimer_uper_bin(Config) ->
 
2448
    ?line ok=testTimer:compile(Config,uper_bin,[]),
 
2449
    ?line {comment,_} = testTimer:go(Config,uper_bin).
 
2450
 
 
2451
%% Test of multiple-line comment, OTP-8043
 
2452
testComment(suite) -> [];
 
2453
testComment(Config) ->
 
2454
    ?line DataDir = ?config(data_dir,Config),
 
2455
    ?line OutDir = ?config(priv_dir,Config),
 
2456
 
 
2457
    ?line ok = asn1ct:compile(DataDir ++ "Comment",[{outdir,OutDir}]),
 
2458
 
 
2459
    ?line {ok,Enc} = asn1_wrapper:encode('Comment','Seq',{'Seq',12,true}),
 
2460
    ?line {ok,{'Seq',12,true}} = asn1_wrapper:decode('Comment','Seq',Enc),
 
2461
    ok.
 
2462
 
 
2463
testName2Number(suite) -> [];
 
2464
testName2Number(Config) -> 
 
2465
    DataDir = ?config(data_dir,Config),
 
2466
    OutDir = ?config(priv_dir,Config),
 
2467
    N2NOptions = [{n2n,Type}|| Type <- 
 
2468
                                   ['CauseMisc','CauseProtocol',
 
2469
                                    %% 'CauseNetwork',
 
2470
                                    'CauseRadioNetwork',
 
2471
                                    'CauseTransport','CauseNas']],
 
2472
    ?line ok = asn1ct:compile(DataDir ++ "S1AP-IEs",[{outdir,OutDir}]++N2NOptions),
 
2473
    ?line true = code:add_patha(OutDir),
 
2474
 
 
2475
    ?line 0 = 'S1AP-IEs':name2num_CauseMisc('control-processing-overload'),
 
2476
    ?line 'unknown-PLMN' = 'S1AP-IEs':num2name_CauseMisc(5),
 
2477
    ok.
 
2478
 
 
2479
 
 
2480
particular() -> 
 
2481
    [ticket_7407].
 
2482
 
 
2483
ticket_7407(suite) -> [];
 
2484
ticket_7407(Config) ->
 
2485
    ?line ok = asn1_test_lib:ticket_7407_compile(Config,[]),
 
2486
    ?line ok = asn1_test_lib:ticket_7407_code(true),
 
2487
 
 
2488
    ?line ok = asn1_test_lib:ticket_7407_compile(Config,[no_final_padding]),
 
2489
    ?line ok = asn1_test_lib:ticket_7407_code(false).