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

« back to all changes in this revision

Viewing changes to lib/asn1/test/asn1_SUITE_data/P-Record.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
%% Generated by the Erlang ASN.1 BER-compiler version, utilizing bit-syntax:1.3.1.4
 
2
%% Purpose: encoder and decoder to the types in mod P-Record
 
3
 
 
4
-module('P-Record').
 
5
-include("P-Record.hrl").
 
6
-define('RT_PER',asn1rt_per_bin).
 
7
-export([encoding_rule/0]).
 
8
-export([
 
9
'enc_PersonnelRecord'/1,
 
10
'enc_ChildInformation'/1,
 
11
'enc_Name'/1,
 
12
'enc_EmployeeNumber'/1,
 
13
'enc_Date'/1
 
14
]).
 
15
 
 
16
-export([
 
17
'dec_PersonnelRecord'/2,
 
18
'dec_ChildInformation'/2,
 
19
'dec_Name'/2,
 
20
'dec_EmployeeNumber'/2,
 
21
'dec_Date'/2
 
22
]).
 
23
 
 
24
-export([
 
25
'v'/0
 
26
]).
 
27
 
 
28
 
 
29
 
 
30
-export([encode/2,decode/2,encode_disp/2,decode_disp/2]).
 
31
 
 
32
encoding_rule() ->
 
33
   per_bin.
 
34
 
 
35
encode(Type,Data) ->
 
36
case catch ?RT_PER:complete(encode_disp(Type,Data)) of
 
37
  {'EXIT',{error,Reason}} ->
 
38
    {error,Reason};
 
39
  {'EXIT',Reason} ->
 
40
    {error,{asn1,Reason}};
 
41
  {Bytes,Len} ->
 
42
    {ok,Bytes};
 
43
  X ->
 
44
    {ok,X}
 
45
end.
 
46
 
 
47
decode(Type,Data) ->
 
48
case catch decode_disp(Type,Data) of
 
49
  {'EXIT',{error,Reason}} ->
 
50
    {error,Reason};
 
51
  {'EXIT',Reason} ->
 
52
    {error,{asn1,Reason}};
 
53
  {X,_Rest} ->
 
54
    {ok,X};
 
55
  {X,_Rest,_Len} ->
 
56
    {ok,X}
 
57
end.
 
58
 
 
59
encode_disp('PersonnelRecord',Data) -> 'enc_PersonnelRecord'(Data);
 
60
encode_disp('ChildInformation',Data) -> 'enc_ChildInformation'(Data);
 
61
encode_disp('Name',Data) -> 'enc_Name'(Data);
 
62
encode_disp('EmployeeNumber',Data) -> 'enc_EmployeeNumber'(Data);
 
63
encode_disp('Date',Data) -> 'enc_Date'(Data);
 
64
encode_disp(Type,Data) -> exit({error,{asn1,{undefined_type,Type}}}).
 
65
 
 
66
 
 
67
decode_disp('PersonnelRecord',Data) -> 'dec_PersonnelRecord'(Data,mandatory);
 
68
decode_disp('ChildInformation',Data) -> 'dec_ChildInformation'(Data,mandatory);
 
69
decode_disp('Name',Data) -> 'dec_Name'(Data,mandatory);
 
70
decode_disp('EmployeeNumber',Data) -> 'dec_EmployeeNumber'(Data,mandatory);
 
71
decode_disp('Date',Data) -> 'dec_Date'(Data,mandatory);
 
72
decode_disp(Type,Data) -> exit({error,{asn1,{undefined_type,Type}}}).
 
73
 
 
74
 
 
75
 
 
76
 
 
77
 
 
78
'enc_PersonnelRecord'(Val) ->
 
79
{Val1,Opt} = ?RT_PER:fixoptionals([{children,6}],Val),
 
80
[
 
81
?RT_PER:setoptionals(Opt),
 
82
 
 
83
%% attribute number 1 with type Externaltypereference6P-RecordName
 
84
'enc_Name'(?RT_PER:cindex(2,Val1,name)),
 
85
 
 
86
%% attribute number 2 with type VisibleString
 
87
?RT_PER:encode_VisibleString([],?RT_PER:cindex(3,Val1,title)),
 
88
 
 
89
%% attribute number 3 with type INTEGER
 
90
?RT_PER:encode_integer([],?RT_PER:cindex(4,Val1,number)),
 
91
 
 
92
%% attribute number 4 with type VisibleString
 
93
?RT_PER:encode_VisibleString([],?RT_PER:cindex(5,Val1,dateOfHire)),
 
94
 
 
95
%% attribute number 5 with type Externaltypereference10P-RecordName
 
96
'enc_Name'(?RT_PER:cindex(6,Val1,nameOfSpouse)),
 
97
case ?RT_PER:cindex(7,Val1,children) of
 
98
asn1_DEFAULT -> [];
 
99
_ ->
 
100
 
 
101
%% attribute number 6 with type SEQUENCE OF
 
102
'enc_PersonnelRecord_children'(?RT_PER:cindex(7,Val1,children))
 
103
end].
 
104
 
 
105
'enc_PersonnelRecord_children'({'PersonnelRecord_children',Val}) ->
 
106
'enc_PersonnelRecord_children'(Val);
 
107
 
 
108
'enc_PersonnelRecord_children'(Val) ->
 
109
[
 
110
 
 
111
   ?RT_PER:encode_length(undefined,length(Val)),
 
112
   'enc_PersonnelRecord_children_components'(Val, [])
 
113
].
 
114
'enc_PersonnelRecord_children_components'([], Acc) -> lists:reverse(Acc);
 
115
 
 
116
'enc_PersonnelRecord_children_components'([H|T], Acc) ->
 
117
'enc_PersonnelRecord_children_components'(T, ['enc_ChildInformation'(H)
 
118
 
 
119
 | Acc]).
 
120
 
 
121
'dec_PersonnelRecord_children'(Bytes,Telltype) ->
 
122
 
 
123
{Num,Bytes1} = ?RT_PER:decode_length(Bytes,undefined),
 
124
'dec_PersonnelRecord_children_components'(Num, Bytes1, Telltype, []).
 
125
'dec_PersonnelRecord_children_components'(0, Bytes, Telltype, Acc) ->
 
126
   {lists:reverse(Acc), Bytes};
 
127
'dec_PersonnelRecord_children_components'(Num, Bytes, Telltype, Acc) ->
 
128
   {Term,Remain} = 'P-Record':'dec_ChildInformation'(Bytes,Telltype),
 
129
   'dec_PersonnelRecord_children_components'(Num-1, Remain, Telltype, [Term|Acc]).
 
130
 
 
131
 
 
132
'dec_PersonnelRecord'(Bytes,Telltype) ->
 
133
{Opt,Bytes1} = ?RT_PER:getoptionals(Bytes,1), 
 
134
%%  attribute number 1 with type Name
 
135
{Term1,Bytes2} = 'dec_Name'(Bytes1,telltype),
 
136
 
 
137
%% attribute number 2 with type VisibleString
 
138
{Term2,Bytes3} = ?RT_PER:decode_VisibleString(Bytes2,[]),
 
139
 
 
140
%% attribute number 3 with type INTEGER
 
141
{Term3,Bytes4} = ?RT_PER:decode_integer(Bytes3,[]),
 
142
 
 
143
%% attribute number 4 with type VisibleString
 
144
{Term4,Bytes5} = ?RT_PER:decode_VisibleString(Bytes4,[]),
 
145
 
 
146
%%  attribute number 5 with type Name
 
147
{Term5,Bytes6} = 'dec_Name'(Bytes5,telltype),
 
148
 
 
149
%% attribute number 6 with type SEQUENCE OF
 
150
{Term6,Bytes7} = case element(1,Opt) of
 
151
1 ->'dec_PersonnelRecord_children'(Bytes6, Telltype);
 
152
0 ->{[],Bytes6}
 
153
 
 
154
end,
 
155
{{'PersonnelRecord',Term1,Term2,Term3,Term4,Term5,Term6},Bytes7}.
 
156
 
 
157
'enc_ChildInformation'(Val) ->
 
158
{Val1,Opt} = ?RT_PER:fixoptionals([{name,1},{dateOfBirth,2}],Val),
 
159
[
 
160
?RT_PER:setoptionals(Opt),
 
161
case ?RT_PER:cindex(2,Val1,name) of
 
162
asn1_NOVALUE -> [];
 
163
_ ->
 
164
 
 
165
%% attribute number 1 with type Externaltypereference15P-RecordName
 
166
'enc_Name'(?RT_PER:cindex(2,Val1,name))
 
167
end,
 
168
case ?RT_PER:cindex(3,Val1,dateOfBirth) of
 
169
asn1_NOVALUE -> [];
 
170
_ ->
 
171
 
 
172
%% attribute number 2 with type VisibleString
 
173
?RT_PER:encode_VisibleString([],?RT_PER:cindex(3,Val1,dateOfBirth))
 
174
end].
 
175
 
 
176
 
 
177
'dec_ChildInformation'(Bytes,Telltype) ->
 
178
{Opt,Bytes1} = ?RT_PER:getoptionals(Bytes,2), 
 
179
%%  attribute number 1 with type Name
 
180
{Term1,Bytes2} = case element(1,Opt) of
 
181
1 ->'dec_Name'(Bytes1,telltype);
 
182
0 ->{asn1_NOVALUE,Bytes1}
 
183
 
 
184
end,
 
185
 
 
186
%% attribute number 2 with type VisibleString
 
187
{Term2,Bytes3} = case element(2,Opt) of
 
188
1 ->?RT_PER:decode_VisibleString(Bytes2,[]);
 
189
0 ->{asn1_NOVALUE,Bytes2}
 
190
 
 
191
end,
 
192
{{'ChildInformation',Term1,Term2},Bytes3}.
 
193
 
 
194
'enc_Name'(Val) ->
 
195
Val1 = ?RT_PER:list_to_record('Name', Val),
 
196
[
 
197
 
 
198
%% attribute number 1 with type VisibleString
 
199
?RT_PER:encode_VisibleString([],?RT_PER:cindex(2,Val1,givenName)),
 
200
 
 
201
%% attribute number 2 with type VisibleString
 
202
?RT_PER:encode_VisibleString([],?RT_PER:cindex(3,Val1,initial)),
 
203
 
 
204
%% attribute number 3 with type VisibleString
 
205
?RT_PER:encode_VisibleString([],?RT_PER:cindex(4,Val1,familyName))].
 
206
 
 
207
 
 
208
'dec_Name'(Bytes,Telltype) ->
 
209
 
 
210
%% attribute number 1 with type VisibleString
 
211
{Term1,Bytes1} = ?RT_PER:decode_VisibleString(Bytes,[]),
 
212
 
 
213
%% attribute number 2 with type VisibleString
 
214
{Term2,Bytes2} = ?RT_PER:decode_VisibleString(Bytes1,[]),
 
215
 
 
216
%% attribute number 3 with type VisibleString
 
217
{Term3,Bytes3} = ?RT_PER:decode_VisibleString(Bytes2,[]),
 
218
{{'Name',Term1,Term2,Term3},Bytes3}.
 
219
 
 
220
 
 
221
'enc_EmployeeNumber'({'EmployeeNumber',Val}) ->
 
222
'enc_EmployeeNumber'(Val);
 
223
 
 
224
'enc_EmployeeNumber'(Val) ->
 
225
?RT_PER:encode_integer([],Val).
 
226
 
 
227
 
 
228
'dec_EmployeeNumber'(Bytes,Telltype) ->
 
229
?RT_PER:decode_integer(Bytes,[]).
 
230
 
 
231
 
 
232
'enc_Date'({'Date',Val}) ->
 
233
'enc_Date'(Val);
 
234
 
 
235
'enc_Date'(Val) ->
 
236
?RT_PER:encode_VisibleString([],Val).
 
237
 
 
238
 
 
239
'dec_Date'(Bytes,Telltype) ->
 
240
?RT_PER:decode_VisibleString(Bytes,[]).
 
241
 
 
242
'v'() ->
 
243
{'PersonnelRecord',{'Name',{74,111,104,110},[80],[83,109,105,116,104]},[68,105,114,101,99,116,111,114],51,[49,57,55,49,48,57,49,55],{'Name',{77,97,114,121},[84],[83,109,105,116,104]},[{'ChildInformation',{'Name',[82,97,108,112,104],[84],[83,109,105,116,104]},[49,57,53,55,49,49,49,49]},{'ChildInformation',{'Name',[83,117,115,97,110],[66],[74,111,110,101,115]},[49,57,53,57,48,55,49,55]}]}.
 
244