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

« back to all changes in this revision

Viewing changes to lib/asn1/test/asn1_SUITE.erl.src

  • Committer: Package Import Robot
  • Author(s): Sergei Golovan
  • Date: 2011-12-15 19:20:10 UTC
  • mfrom: (1.1.18) (3.5.15 sid)
  • mto: (3.5.16 sid)
  • mto: This revision was merged to the branch mainline in revision 33.
  • Revision ID: package-import@ubuntu.com-20111215192010-jnxcfe3tbrpp0big
Tags: 1:15.b-dfsg-1
* New upstream release.
* Upload to experimental because this release breaks external drivers
  API along with ABI, so several applications are to be fixed.
* Removed SSL patch because the old SSL implementation is removed from
  the upstream distribution.
* Removed never used patch which added native code to erlang beam files.
* Removed the erlang-docbuilder binary package because the docbuilder
  application was dropped by upstream.
* Documented dropping ${erlang-docbuilder:Depends} substvar in
  erlang-depends(1) manpage.
* Made erlang-base and erlang-base-hipe provide virtual package
  erlang-abi-15.b (the number means the first erlang version, which
  provides current ABI).

Show diffs side-by-side

added added

removed removed

Lines of Context:
1
1
%%
2
2
%% %CopyrightBegin%
3
3
%%
4
 
%% Copyright Ericsson AB 2001-2010. All Rights Reserved.
 
4
%% Copyright Ericsson AB 2001-2011. All Rights Reserved.
5
5
%%
6
6
%% The contents of this file are subject to the Erlang Public License,
7
7
%% Version 1.1, (the "License"); you may not use this file except in
60
60
%-record('Def3',{
61
61
%bool30 = asn1_DEFAULT, bool31 = asn1_DEFAULT, bool32 = asn1_DEFAULT, bool33 = asn1_DEFAULT}).
62
62
 
63
 
 
64
 
 
65
 
all(suite) -> [compile,parse,default_per,default_ber,default_per_opt,per,
66
 
               ber,testPrim, 
 
63
suite() -> [{ct_hooks,[ts_install_cth]}].
 
64
 
 
65
all() -> [{group,compile},parse,default_per,default_ber,default_per_opt,per,
 
66
               {group,ber},testPrim, 
67
67
               testPrimStrings, testPrimExternal, testChoPrim, 
68
68
               testChoExtension, testChoExternal, testChoOptional, 
69
69
               testChoOptionalImplicitTag, testChoRecursive, 
99
99
               testX420, test_x691,ticket_6143, testExtensionAdditionGroup
100
100
               ] ++ common() ++ particular().
101
101
 
 
102
groups() -> 
 
103
    [
 
104
     {compile, [],
 
105
      [c_syntax, c_string_per, c_string_ber,
 
106
       c_implicit_before_choice]},
 
107
     {ber, [],
 
108
      [ber_choiceinseq, ber_optional, ber_optional_keyed_list,
 
109
       ber_other]},
 
110
     {app_test, [], [{asn1_app_test, all}]},
 
111
     {appup_test, [], [{asn1_appup_test, all}]}
 
112
    ].
 
113
 
 
114
init_per_suite(Config) ->
 
115
    io:format("code:lib_dir(asn1) = ~p~n",[code:lib_dir(asn1)]),
 
116
    Config.
 
117
 
 
118
end_per_suite(_Config) ->
 
119
    ok.
 
120
 
 
121
init_per_group(_GroupName, Config) ->
 
122
        Config.
 
123
 
 
124
end_per_group(_GroupName, Config) ->
 
125
        Config.
 
126
 
 
127
 
102
128
%all(suite) -> [test_inline,testNBAPsystem,test_compile_options,ticket_6143].
103
129
 
104
 
option_tests(suite) ->
105
 
    [test_compile_options,ticket_6143].
106
 
 
107
 
infobj(suite) ->
108
 
    [testInfObjectClass, testParameterizedInfObj, testMergeCompile, 
109
 
     testobj, testDeepTConstr].
110
 
 
111
 
performance(suite) ->
112
 
    [testTimer_ber, testTimer_ber_opt_driver, 
113
 
     testTimer_per, testTimer_per_opt, testTimer_uper_bin].
114
 
 
115
 
bugs(suite) ->
116
 
   [test_ParamTypeInfObj, test_WS_ParamClass,test_Defed_ObjectIdentifier].
117
130
 
118
131
init_per_testcase(Func,Config) ->
119
132
    %%?line test_server:format("Func: ~p~n",[Func]),
129
142
%%    Dog=test_server:timetrap(1800000), % 30 minutes
130
143
    [{watchdog, Dog}|Config].
131
144
 
132
 
fin_per_testcase(_Func,Config) ->
 
145
end_per_testcase(_Func,Config) ->
133
146
          Dog=?config(watchdog, Config),
134
147
          test_server:timetrap_cancel(Dog).
135
148
 
1371
1384
 
1372
1385
sequence(suite) -> [{sequence,all}].
1373
1386
 
1374
 
compile(suite) -> [c_syntax,c_string_per,c_string_ber,c_implicit_before_choice];
1375
 
compile(Config) ->
1376
 
    ?line DataDir = ?config(data_dir,Config),
1377
 
    ?line TempDir = ?config(priv_dir,Config),
1378
 
    ?line True = lists:member(TempDir,code:get_path()),
1379
 
    ?line test_server:format("~p~n",[True]),
1380
 
    ?line test_server:format("~p~n",[code:get_path()]),
1381
 
    ?line true = code:add_patha(?config(priv_dir,Config)),
1382
 
    ?line {error,_R1} = asn1ct:compile(filename:join(DataDir,"Syntax")),
1383
 
    ?line ok = asn1ct:compile(filename:join(DataDir,"String"),[?PER,{outdir,TempDir}]),
1384
 
    test_server:format("first String ok~n"),
1385
 
    ?line ok = asn1ct:compile(filename:join(DataDir,"String"),[?BER,{outdir,TempDir}]),
1386
 
    ?line {error,_R2} = asn1ct:compile(filename:join(DataDir,"CCSNARG3"),[?BER,{outdir,TempDir}]),
1387
 
    ?line {error,_} = asn1ct:compile(filename:join(DataDir,"ImportsFrom"),[?BER,{outdir,TempDir}]),
1388
 
    ok.
1389
 
 
1390
1387
c_syntax(suite) -> [];
1391
1388
c_syntax(Config) ->
1392
1389
    ?line DataDir%    ?line testExternal:compile(Config,?PER),     
1490
1487
per1_opt([],_,_) ->
1491
1488
    ok.
1492
1489
 
1493
 
ber(suite) -> [ber_choiceinseq,ber_optional,ber_optional_keyed_list,ber_other].
1494
 
 
1495
1490
ber_choiceinseq(suite) ->[];
1496
1491
ber_choiceinseq(Config) ->
1497
1492
    ?line DataDir = ?config(data_dir,Config),
2041
2036
    ?line {ok,_} = asn1rt:info('Prim'),
2042
2037
 
2043
2038
    ?line ok = asn1ct:compile(filename:join(DataDir,"Prim"),[?PER]),
2044
 
    ?line {ok,_} = asn1rt:info('Prim'),
2045
 
 
2046
 
    ?line ok = asn1rt:load_driver(),
2047
 
    ?line ok = asn1rt:load_driver(),
2048
 
    ?line ok = asn1rt:unload_driver().
 
2039
    ?line {ok,_} = asn1rt:info('Prim').
2049
2040
 
2050
2041
testROSE(suite) -> [];
2051
2042
testROSE(Config) -> 
2241
2232
          ?line ok = test_compile_options:path(Config),
2242
2233
          ?line ok = test_compile_options:noobj(Config),
2243
2234
          ?line ok = test_compile_options:record_name_prefix(Config),
2244
 
          ?line ok = test_compile_options:verbose(Config)
 
2235
          ?line ok = test_compile_options:verbose(Config),
 
2236
          ?line ok = test_compile_options:warnings_as_errors(Config)
2245
2237
    end.
 
2238
 
2246
2239
testDoubleEllipses(suite) ->  [];
2247
2240
testDoubleEllipses(Config) ->
2248
2241
    ?line testDoubleEllipses:compile(Config,?BER,[]),
2327
2320
test_modules() ->
2328
2321
    _Modules = [
2329
2322
               "BitStr",
 
2323
               "CAP",
2330
2324
               "CommonDataTypes",
2331
2325
               "Constraints",
2332
2326
               "ContextSwitchingTypes",