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

« back to all changes in this revision

Viewing changes to lib/dialyzer/test/r9c_tests_SUITE_data/src/asn1/asn1ct_value.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
%% ``The contents of this file are subject to the Erlang Public License,
 
2
%% Version 1.1, (the "License"); you may not use this file except in
 
3
%% compliance with the License. You should have received a copy of the
 
4
%% Erlang Public License along with this software. If not, it can be
 
5
%% retrieved via the world wide web at http://www.erlang.org/.
 
6
%% 
 
7
%% Software distributed under the License is distributed on an "AS IS"
 
8
%% basis, WITHOUT WARRANTY OF ANY KIND, either express or implied. See
 
9
%% the License for the specific language governing rights and limitations
 
10
%% under the License.
 
11
%% 
 
12
%% The Initial Developer of the Original Code is Ericsson Utvecklings AB.
 
13
%% Portions created by Ericsson are Copyright 1999, Ericsson Utvecklings
 
14
%% AB. All Rights Reserved.''
 
15
%% 
 
16
%%     $Id: asn1ct_value.erl,v 1.1 2008/12/17 09:53:30 mikpe Exp $
 
17
%%
 
18
-module(asn1ct_value).
 
19
 
 
20
%%  Generate Erlang values for ASN.1 types.
 
21
%%  The value is randomized within it's constraints
 
22
 
 
23
-include("asn1_records.hrl").
 
24
%-compile(export_all).
 
25
 
 
26
-export([get_type/3]).
 
27
 
 
28
 
 
29
 
 
30
%% Generate examples of values ******************************
 
31
%%****************************************x
 
32
 
 
33
 
 
34
get_type(M,Typename,Tellname) ->
 
35
    case asn1_db:dbget(M,Typename) of
 
36
        undefined -> 
 
37
            {asn1_error,{not_found,{M,Typename}}};
 
38
        Tdef when record(Tdef,typedef) ->
 
39
            Type = Tdef#typedef.typespec,
 
40
            get_type(M,[Typename],Type,Tellname);
 
41
        Err ->
 
42
            {asn1_error,{other,Err}}
 
43
    end.
 
44
 
 
45
get_type(M,Typename,Type,Tellname) when record(Type,type) ->
 
46
    InnerType = get_inner(Type#type.def),
 
47
    case asn1ct_gen:type(InnerType) of
 
48
        #'Externaltypereference'{module=Emod,type=Etype} ->
 
49
            get_type(Emod,Etype,Tellname);
 
50
        {_,user} ->
 
51
            case Tellname of
 
52
                yes -> {Typename,get_type(M,InnerType,no)};
 
53
                no -> get_type(M,InnerType,no)
 
54
            end;
 
55
        {notype,_} ->
 
56
            true;
 
57
        {primitive,bif} ->
 
58
            get_type_prim(Type);
 
59
        'ASN1_OPEN_TYPE' ->
 
60
            case  Type#type.constraint of
 
61
                [#'Externaltypereference'{type=TrefConstraint}] ->
 
62
                    get_type(M,TrefConstraint,no);
 
63
                _ ->
 
64
                    "open_type"
 
65
            end;
 
66
        {constructed,bif} ->
 
67
            get_type_constructed(M,Typename,InnerType,Type)
 
68
    end;
 
69
get_type(M,Typename,#'ComponentType'{name = Name,typespec = Type},_)  ->
 
70
    get_type(M,[Name|Typename],Type,no);
 
71
get_type(_,_,_,_) -> % 'EXTENSIONMARK'
 
72
    undefined.
 
73
 
 
74
get_inner(A) when atom(A) -> A;    
 
75
get_inner(Ext) when record(Ext,'Externaltypereference') -> Ext;    
 
76
get_inner({typereference,_Pos,Name}) -> Name;
 
77
get_inner(T) when tuple(T) -> 
 
78
    case asn1ct_gen:get_inner(T) of
 
79
        {fixedtypevaluefield,_,Type} ->
 
80
            Type#type.def;
 
81
        {typefield,_FieldName} -> 
 
82
            'ASN1_OPEN_TYPE';
 
83
        Other ->
 
84
            Other
 
85
    end.
 
86
%%get_inner(T) when tuple(T) -> element(1,T).
 
87
 
 
88
 
 
89
 
 
90
get_type_constructed(M,Typename,InnerType,D) when record(D,type) ->
 
91
    case InnerType of
 
92
        'SET' ->
 
93
            get_sequence(M,Typename,D);
 
94
        'SEQUENCE' ->
 
95
            get_sequence(M,Typename,D);
 
96
        'CHOICE' ->
 
97
            get_choice(M,Typename,D);
 
98
        'SEQUENCE OF' ->
 
99
            {_,Type} = D#type.def,
 
100
            NameSuffix = asn1ct_gen:constructed_suffix(InnerType,Type#type.def),
 
101
            get_sequence_of(M,Typename,D,NameSuffix);
 
102
        'SET OF' ->
 
103
            {_,Type} = D#type.def,
 
104
            NameSuffix = asn1ct_gen:constructed_suffix(InnerType,Type#type.def),
 
105
            get_sequence_of(M,Typename,D,NameSuffix);
 
106
        _ ->
 
107
            exit({nyi,InnerType})
 
108
    end.
 
109
 
 
110
get_sequence(M,Typename,Type) ->
 
111
    {_SEQorSET,CompList} = 
 
112
        case Type#type.def of
 
113
            #'SEQUENCE'{components=Cl} -> {'SEQUENCE',Cl};
 
114
            #'SET'{components=Cl} -> {'SET',Cl}
 
115
        end,
 
116
    case get_components(M,Typename,CompList) of
 
117
        [] ->
 
118
            {list_to_atom(asn1ct_gen:list2rname(Typename))};
 
119
        C ->
 
120
            list_to_tuple([list_to_atom(asn1ct_gen:list2rname(Typename))|C])
 
121
    end.
 
122
 
 
123
get_components(M,Typename,{Root,Ext}) ->
 
124
    get_components(M,Typename,Root++Ext);
 
125
 
 
126
%% Should enhance this *** HERE *** with proper handling of extensions
 
127
 
 
128
get_components(M,Typename,[H|T]) ->
 
129
    [get_type(M,Typename,H,no)|
 
130
    get_components(M,Typename,T)];
 
131
get_components(_,_,[]) ->
 
132
    [].
 
133
 
 
134
get_choice(M,Typename,Type) ->
 
135
    {'CHOICE',TCompList} = Type#type.def,
 
136
    case TCompList of
 
137
        [] -> 
 
138
            {asn1_EMPTY,asn1_EMPTY};
 
139
        {CompList,ExtList} -> % Should be enhanced to handle extensions too
 
140
            CList = CompList ++ ExtList,
 
141
            C = lists:nth(random(length(CList)),CList),
 
142
            {C#'ComponentType'.name,get_type(M,Typename,C,no)};
 
143
        CompList when list(CompList) ->
 
144
            C = lists:nth(random(length(CompList)),CompList),
 
145
            {C#'ComponentType'.name,get_type(M,Typename,C,no)}
 
146
    end.
 
147
    
 
148
get_sequence_of(M,Typename,Type,TypeSuffix) ->
 
149
    %% should generate length according to constraints later
 
150
    {_,Oftype} = Type#type.def,
 
151
    C = Type#type.constraint,
 
152
    S = size_random(C),
 
153
    NewTypeName = [TypeSuffix|Typename],
 
154
    gen_list(M,NewTypeName,Oftype,no,S).
 
155
 
 
156
gen_list(_,_,_,_,0) ->
 
157
    [];
 
158
gen_list(M,Typename,Oftype,Tellname,N) ->
 
159
    [get_type(M,Typename,Oftype,no)|gen_list(M,Typename,Oftype,Tellname,N-1)].
 
160
    
 
161
get_type_prim(D) ->
 
162
    C = D#type.constraint,
 
163
    case D#type.def of
 
164
        'INTEGER' ->
 
165
            i_random(C);
 
166
        {'INTEGER',NamedNumberList} ->
 
167
            NN = [X||{X,_} <- NamedNumberList],
 
168
            case NN of 
 
169
                [] ->
 
170
                    i_random(C);
 
171
                _ ->
 
172
                    lists:nth(random(length(NN)),NN)
 
173
            end;
 
174
        Enum when tuple(Enum),element(1,Enum)=='ENUMERATED' ->
 
175
            NamedNumberList =
 
176
                case Enum of
 
177
                    {_,_,NNL} -> NNL;
 
178
                    {_,NNL} -> NNL
 
179
                end,
 
180
            NNew=
 
181
                case NamedNumberList of
 
182
                    {N1,N2} ->
 
183
                        N1 ++ N2;
 
184
                    _->
 
185
                        NamedNumberList
 
186
                end,
 
187
            NN = [X||{X,_} <- NNew],
 
188
            case NN of
 
189
                [] ->
 
190
                    asn1_EMPTY;
 
191
                _ ->
 
192
                    lists:nth(random(length(NN)),NN)
 
193
            end;
 
194
        {'BIT STRING',NamedNumberList} ->
 
195
%%          io:format("get_type_prim 1: ~w~n",[NamedNumberList]),
 
196
            NN = [X||{X,_} <- NamedNumberList],
 
197
            case NN of
 
198
                [] ->
 
199
                    Bl1 =lists:reverse(adjust_list(size_random(C),[1,0,1,1])),
 
200
                    lists:reverse(lists:dropwhile(fun(0)->true;(1)->false end,Bl1));
 
201
                _ ->
 
202
%%                  io:format("get_type_prim 2: ~w~n",[NN]),
 
203
                    [lists:nth(random(length(NN)),NN)]
 
204
            end;
 
205
        'ANY' ->
 
206
            exit({asn1_error,nyi,'ANY'});
 
207
        'NULL' ->
 
208
            'NULL';
 
209
        'OBJECT IDENTIFIER' ->
 
210
            Len = random(3),
 
211
            Olist = [(random(1000)-1)||_X <-lists:seq(1,Len)],
 
212
            list_to_tuple([random(3)-1,random(40)-1|Olist]);
 
213
        'ObjectDescriptor' ->
 
214
            object_descriptor_nyi;
 
215
        'BOOLEAN' ->
 
216
            true;
 
217
        'OCTET STRING' ->
 
218
            adjust_list(size_random(C),c_string(C,"OCTET STRING"));
 
219
        'NumericString' ->
 
220
            adjust_list(size_random(C),c_string(C,"0123456789"));
 
221
        'TeletexString' ->
 
222
            adjust_list(size_random(C),c_string(C,"TeletexString"));
 
223
        'VideotexString' ->
 
224
            adjust_list(size_random(C),c_string(C,"VideotexString"));
 
225
        'UTCTime' ->
 
226
            "97100211-0500";
 
227
        'GeneralizedTime' ->
 
228
            "19971002103130.5";
 
229
        'GraphicString' ->
 
230
            adjust_list(size_random(C),c_string(C,"GraphicString"));
 
231
        'VisibleString' ->
 
232
            adjust_list(size_random(C),c_string(C,"VisibleString"));
 
233
        'GeneralString' ->
 
234
            adjust_list(size_random(C),c_string(C,"GeneralString"));
 
235
        'PrintableString' ->
 
236
            adjust_list(size_random(C),c_string(C,"PrintableString"));
 
237
        'IA5String' ->
 
238
            adjust_list(size_random(C),c_string(C,"IA5String"));
 
239
        'BMPString' ->
 
240
            adjust_list(size_random(C),c_string(C,"BMPString"));
 
241
        'UniversalString' ->
 
242
            adjust_list(size_random(C),c_string(C,"UniversalString"));
 
243
        XX ->
 
244
            exit({asn1_error,nyi,XX})
 
245
    end.
 
246
 
 
247
c_string(undefined,Default) ->
 
248
    Default;
 
249
c_string(C,Default) ->
 
250
    case get_constraint(C,'PermittedAlphabet') of
 
251
        {'SingleValue',Sv} when list(Sv) ->
 
252
            Sv;
 
253
        {'SingleValue',V} when integer(V) ->
 
254
            [V];
 
255
        no ->
 
256
            Default
 
257
    end.
 
258
 
 
259
random(Upper) ->
 
260
    {A1,A2,A3} = erlang:now(),
 
261
    random:seed(A1,A2,A3),
 
262
    random:uniform(Upper).
 
263
 
 
264
size_random(C) ->
 
265
    case get_constraint(C,'SizeConstraint') of
 
266
        no ->
 
267
            c_random({0,5},no);
 
268
        {Lb,Ub} when Ub-Lb =< 4 ->
 
269
            c_random({Lb,Ub},no);
 
270
        {Lb,_}  ->
 
271
            c_random({Lb,Lb+4},no);
 
272
        Sv ->
 
273
            c_random(no,Sv)
 
274
    end.
 
275
        
 
276
i_random(C) ->
 
277
    c_random(get_constraint(C,'ValueRange'),get_constraint(C,'SingleValue')).
 
278
 
 
279
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
280
%% c_random(Range,SingleValue)
 
281
%% only called from other X_random functions
 
282
 
 
283
c_random(VRange,Single) ->
 
284
    case {VRange,Single} of
 
285
        {no,no} ->
 
286
            random(16#fffffff) - (16#fffffff bsr 1);
 
287
        {R,no} ->
 
288
            case R of 
 
289
                {Lb,Ub} when integer(Lb),integer(Ub) ->
 
290
                    Range = Ub - Lb +1,
 
291
                    Lb + (random(Range)-1);
 
292
                {Lb,'MAX'} ->
 
293
                    Lb + random(16#fffffff)-1;
 
294
                {'MIN',Ub} ->
 
295
                    Ub - random(16#fffffff)-1;
 
296
                {A,{'ASN1_OK',B}} ->
 
297
                    Range = B - A +1,
 
298
                    A + (random(Range)-1)
 
299
            end;
 
300
        {_,S} when integer(S) ->
 
301
            S;
 
302
        {_,S} when list(S) ->
 
303
            lists:nth(random(length(S)),S)
 
304
%%      {S1,S2} ->
 
305
%%          io:format("asn1ct_value: hejsan hoppsan~n");
 
306
%%      _ ->
 
307
%%          io:format("asn1ct_value: hejsan hoppsan 2~n")
 
308
%%          io:format("asn1ct_value: c_random/2: S1 = ~w~n"
 
309
%%                    "S2 = ~w,~n",[S1,S2])
 
310
%%          exit(self(),goodbye)
 
311
    end.
 
312
 
 
313
adjust_list(Len,Orig) ->
 
314
    adjust_list1(Len,Orig,Orig,[]).
 
315
 
 
316
adjust_list1(0,_Orig,[_Oh|_Ot],Acc) ->
 
317
    lists:reverse(Acc);
 
318
adjust_list1(Len,Orig,[],Acc) ->
 
319
    adjust_list1(Len,Orig,Orig,Acc);
 
320
adjust_list1(Len,Orig,[Oh|Ot],Acc) ->
 
321
    adjust_list1(Len-1,Orig,Ot,[Oh|Acc]).
 
322
 
 
323
 
 
324
get_constraint(C,Key) ->
 
325
    case lists:keysearch(Key,1,C) of
 
326
        false ->
 
327
             no;
 
328
        {value,{_,V}} -> 
 
329
            V
 
330
    end.