~ubuntu-branches/debian/squeeze/erlang/squeeze

« back to all changes in this revision

Viewing changes to lib/asn1/test/testSeqOfCho.erl

  • Committer: Bazaar Package Importer
  • Author(s): Sergei Golovan
  • Date: 2010-03-09 17:34:57 UTC
  • mfrom: (10.1.2 sid)
  • Revision ID: james.westby@ubuntu.com-20100309173457-4yd6hlcb2osfhx31
Tags: 1:13.b.4-dfsg-3
Manpages in section 1 are needed even if only arch-dependent packages are
built. So, re-enabled them.

Show diffs side-by-side

added added

removed removed

Lines of Context:
 
1
%%
 
2
%% %CopyrightBegin%
 
3
%% 
 
4
%% Copyright Ericsson AB 1997-2009. 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
-module(testSeqOfCho).
 
21
 
 
22
-export([compile/3]).
 
23
-export([main/1]).
 
24
 
 
25
-include("test_server.hrl").
 
26
 
 
27
-record('SeqChoDef',{bool1, int1, seq1 = asn1_DEFAULT}).
 
28
-record('SeqChoOpt',{bool1, int1, seq1 = asn1_NOVALUE}).
 
29
-record('SeqChoEmbDef',{bool1, int1, seq1 = asn1_DEFAULT}).
 
30
-record('SeqChoEmbOpt',{bool1, int1, seq1 = asn1_NOVALUE}).
 
31
-record('SeqOfChoEmbDef_SEQOF',{bool1, int1, seq1 = asn1_DEFAULT}).
 
32
-record('SeqOfChoEmbOpt_SEQOF',{bool1, int1, seq1 = asn1_NOVALUE}).
 
33
 
 
34
 
 
35
 
 
36
compile(Config,Rules,Options) ->
 
37
 
 
38
    ?line DataDir = ?config(data_dir,Config),
 
39
    ?line OutDir = ?config(priv_dir,Config),
 
40
    ?line true = code:add_patha(?config(priv_dir,Config)),
 
41
    ?line ok = asn1ct:compile(DataDir ++ "SeqOfCho",[Rules,{outdir,OutDir}]++Options).
 
42
 
 
43
 
 
44
 
 
45
main(_Rules) ->
 
46
    
 
47
    ?line {ok,Bytes11} = 
 
48
        asn1_wrapper:encode('SeqOfCho','SeqChoDef',#'SeqChoDef'{bool1 = true,
 
49
                                                          int1 = 17}),
 
50
    ?line {ok,{'SeqChoDef',true,17,[]}} = 
 
51
        asn1_wrapper:decode('SeqOfCho','SeqChoDef',lists:flatten(Bytes11)),
 
52
    
 
53
    
 
54
    ?line {ok,Bytes12} = 
 
55
        asn1_wrapper:encode('SeqOfCho','SeqChoDef',#'SeqChoDef'{bool1 = true,
 
56
                                                          int1 = 17,
 
57
                                                          seq1 = [{boolIn,true},
 
58
                                                                  {intIn,25}]}),
 
59
    ?line {ok,{'SeqChoDef',true,17,[{boolIn,true},{intIn,25}]}} = 
 
60
        asn1_wrapper:decode('SeqOfCho','SeqChoDef',lists:flatten(Bytes12)),
 
61
    
 
62
    
 
63
    
 
64
    ?line {ok,Bytes15} = 
 
65
        asn1_wrapper:encode('SeqOfCho','SeqChoOpt',#'SeqChoOpt'{bool1 = true,
 
66
                                                          int1 = 17}),
 
67
    ?line {ok,{'SeqChoOpt',true,17,asn1_NOVALUE}} = 
 
68
        asn1_wrapper:decode('SeqOfCho','SeqChoOpt',lists:flatten(Bytes15)),
 
69
    
 
70
    
 
71
    ?line {ok,Bytes16} = 
 
72
        asn1_wrapper:encode('SeqOfCho','SeqChoOpt',#'SeqChoOpt'{bool1 = true,
 
73
                                                          int1 = 17,
 
74
                                                          seq1 = [{boolIn,true},
 
75
                                                                  {intIn,25}]}),
 
76
    ?line {ok,{'SeqChoOpt',true,17,[{boolIn,true},{intIn,25}]}} = 
 
77
        asn1_wrapper:decode('SeqOfCho','SeqChoOpt',lists:flatten(Bytes16)),
 
78
    
 
79
    
 
80
    
 
81
    
 
82
    
 
83
    ?line {ok,Bytes21} = 
 
84
        asn1_wrapper:encode('SeqOfCho','SeqChoEmbDef',#'SeqChoEmbDef'{bool1 = true,
 
85
                                                                int1 = 17}),
 
86
    ?line {ok,{'SeqChoEmbDef',true,17,[]}} = 
 
87
        asn1_wrapper:decode('SeqOfCho','SeqChoEmbDef',lists:flatten(Bytes21)),
 
88
    
 
89
    
 
90
    ?line {ok,Bytes22} = 
 
91
        asn1_wrapper:encode('SeqOfCho','SeqChoEmbDef',#'SeqChoEmbDef'{bool1 = true,
 
92
                                                                int1 = 17,
 
93
                                                                seq1 = [{boolIn,true},
 
94
                                                                        {intIn,25}]}),
 
95
    ?line {ok,{'SeqChoEmbDef',true,17,[{boolIn,true},{intIn,25}]}} = 
 
96
        asn1_wrapper:decode('SeqOfCho','SeqChoEmbDef',lists:flatten(Bytes22)),
 
97
    
 
98
    
 
99
    
 
100
    ?line {ok,Bytes25} = 
 
101
        asn1_wrapper:encode('SeqOfCho','SeqChoEmbOpt',#'SeqChoEmbOpt'{bool1 = true,
 
102
                                                                int1 = 17}),
 
103
    ?line {ok,{'SeqChoEmbOpt',true,17,asn1_NOVALUE}} = 
 
104
        asn1_wrapper:decode('SeqOfCho','SeqChoEmbOpt',lists:flatten(Bytes25)),
 
105
    
 
106
    
 
107
    ?line {ok,Bytes26} = 
 
108
        asn1_wrapper:encode('SeqOfCho','SeqChoEmbOpt',#'SeqChoEmbOpt'{bool1 = true,
 
109
                                                                int1 = 17,
 
110
                                                                seq1 = [{boolIn,true},
 
111
                                                                        {intIn,25}]}),
 
112
    ?line {ok,{'SeqChoEmbOpt',true,17,[{boolIn,true},{intIn,25}]}} = 
 
113
        asn1_wrapper:decode('SeqOfCho','SeqChoEmbOpt',lists:flatten(Bytes26)),
 
114
    
 
115
    
 
116
    
 
117
    
 
118
    
 
119
    
 
120
    ?line {ok,Bytes31} = 
 
121
        asn1_wrapper:encode('SeqOfCho','SeqOfChoEmbDef',[#'SeqOfChoEmbDef_SEQOF'{bool1 = true,
 
122
                                                                           int1 = 17}]),
 
123
    ?line {ok,[{'SeqOfChoEmbDef_SEQOF',true,17,[]}]} = 
 
124
        asn1_wrapper:decode('SeqOfCho','SeqOfChoEmbDef',lists:flatten(Bytes31)),
 
125
    
 
126
    
 
127
    ?line {ok,Bytes32} = 
 
128
        asn1_wrapper:encode('SeqOfCho','SeqOfChoEmbDef',
 
129
                      [#'SeqOfChoEmbDef_SEQOF'{bool1 = true,
 
130
                                               int1 = 17,
 
131
                                               seq1 = [{boolIn,true},
 
132
                                                       {intIn,25}]}]),
 
133
    ?line {ok,[{'SeqOfChoEmbDef_SEQOF',true,17,[{boolIn,true},{intIn,25}]}]} = 
 
134
        asn1_wrapper:decode('SeqOfCho','SeqOfChoEmbDef',lists:flatten(Bytes32)),
 
135
    
 
136
    
 
137
    
 
138
    ?line {ok,Bytes35} = 
 
139
        asn1_wrapper:encode('SeqOfCho','SeqOfChoEmbOpt',[#'SeqOfChoEmbOpt_SEQOF'{bool1 = true,
 
140
                                                                           int1 = 17}]),
 
141
    ?line {ok,[{'SeqOfChoEmbOpt_SEQOF',true,17,asn1_NOVALUE}]} = 
 
142
        asn1_wrapper:decode('SeqOfCho','SeqOfChoEmbOpt',lists:flatten(Bytes35)),
 
143
    
 
144
    
 
145
    ?line {ok,Bytes36} = 
 
146
        asn1_wrapper:encode('SeqOfCho','SeqOfChoEmbOpt',
 
147
                      [#'SeqOfChoEmbOpt_SEQOF'{bool1 = true,
 
148
                                               int1 = 17,
 
149
                                               seq1 = [{boolIn,true},
 
150
                                                       {intIn,25}]}]),
 
151
    ?line {ok,[{'SeqOfChoEmbOpt_SEQOF',true,17,[{boolIn,true},{intIn,25}]}]} = 
 
152
        asn1_wrapper:decode('SeqOfCho','SeqOfChoEmbOpt',lists:flatten(Bytes36)),
 
153
    
 
154
    
 
155
    
 
156
    
 
157
    ok.
 
158
 
 
159