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

« back to all changes in this revision

Viewing changes to lib/asn1/src/asn1ct_value.erl

  • Committer: Bazaar Package Importer
  • Author(s): Sergei Golovan
  • Date: 2009-02-15 16:42:52 UTC
  • mfrom: (1.1.13 upstream)
  • Revision ID: james.westby@ubuntu.com-20090215164252-dxpjjuq108nz4noa
Tags: 1:12.b.5-dfsg-2
Upload to unstable after lenny is released.

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,
 
1
%%<copyright>
 
2
%% <year>1997-2008</year>
 
3
%% <holder>Ericsson AB, All Rights Reserved</holder>
 
4
%%</copyright>
 
5
%%<legalnotice>
 
6
%% The contents of this file are subject to the Erlang Public License,
2
7
%% Version 1.1, (the "License"); you may not use this file except in
3
8
%% compliance with the License. You should have received a copy of the
4
9
%% 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
 
%% 
 
10
%% retrieved online at http://www.erlang.org/.
 
11
%%
7
12
%% Software distributed under the License is distributed on an "AS IS"
8
13
%% basis, WITHOUT WARRANTY OF ANY KIND, either express or implied. See
9
14
%% the License for the specific language governing rights and limitations
10
15
%% 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$
 
16
%%
 
17
%% The Initial Developer of the Original Code is Ericsson AB.
 
18
%%</legalnotice>
17
19
%%
18
20
-module(asn1ct_value).
19
21
 
115
117
    {_SEQorSET,CompList} = 
116
118
        case Type#type.def of
117
119
            #'SEQUENCE'{components=Cl} -> {'SEQUENCE',Cl};
118
 
            #'SET'{components=Cl} -> {'SET',Cl}
 
120
            #'SET'{components=Cl} -> {'SET',to_textual_order(Cl)}
119
121
        end,
120
122
    case get_components(M,Typename,CompList) of
121
123
        [] ->
225
227
            Len = random(3),
226
228
            Olist = [(random(1000)-1)||_X <-lists:seq(1,Len)],
227
229
            list_to_tuple([random(3)-1,random(40)-1|Olist]);
 
230
        'RELATIVE-OID' ->
 
231
            Len = random(5),
 
232
            Olist = [(random(16#ffff)-1)||_X <-lists:seq(1,Len)],
 
233
            list_to_tuple(Olist);
228
234
        'ObjectDescriptor' ->
229
235
            "Dummy ObjectDescriptor";
 
236
        'REAL' ->
 
237
            %% Base is 2 or 10, format is string (base 10) or tuple
 
238
            %% (base 2 or 10)
 
239
            %% Tuple: {Mantissa, Base, Exponent}
 
240
            case random(3) of
 
241
                1 ->
 
242
                    %% base 2
 
243
                    case random(3) of
 
244
                        3 ->
 
245
                            {129,2,10};
 
246
                        2 ->
 
247
                            {1,2,1};
 
248
                        _ ->
 
249
                            {2#11111111,2,2}
 
250
                    end;
 
251
%%                  Sign1 = random_sign(integer),
 
252
%%                  Sign2 = random_sign(integer),
 
253
%%                  {Sign1*random(10000),2,Sign2*random(1028)};
 
254
%%              2 ->
 
255
%%                  %% base 10 tuple format
 
256
%%                  Sign1 = random_sign(integer),
 
257
%%                  Sign2 = random_sign(integer),
 
258
%%                  {Sign1*random(10000),10,Sign2*random(1028)};
 
259
                _ ->
 
260
                    %% base 10 string format, NR3 format
 
261
                    case random(2) of
 
262
                        2 ->
 
263
                            "123.E10";
 
264
                        _ ->
 
265
                            "-123.E-10"
 
266
                    end
 
267
            end;
230
268
        'BOOLEAN' ->
231
269
            true;
232
270
        'OCTET STRING' ->
235
273
            adjust_list(size_random(C),c_string(C,"0123456789"));
236
274
        'TeletexString' ->
237
275
            adjust_list(size_random(C),c_string(C,"TeletexString"));
 
276
        'T61String' ->
 
277
            adjust_list(size_random(C),c_string(C,"T61String"));
238
278
        'VideotexString' ->
239
279
            adjust_list(size_random(C),c_string(C,"VideotexString"));
240
280
        'UTCTime' ->
277
317
            Default
278
318
    end.
279
319
 
 
320
random_sign(integer) ->
 
321
    case random(2) of
 
322
        2 ->
 
323
            -1;
 
324
        _ ->
 
325
            1
 
326
    end;
 
327
random_sign(string) ->
 
328
    case random(2) of
 
329
        2 ->
 
330
            "-";
 
331
        _ ->
 
332
            ""
 
333
    end.
 
334
 
280
335
random(Upper) ->
281
336
    {A1,A2,A3} = erlang:now(),
282
337
    random:seed(A1,A2,A3),
384
439
%    <<10,9,111,112,101,110,95,116,121,112,101>>;
385
440
open_type_value(_) ->
386
441
    [4,9,111,112,101,110,95,116,121,112,101].
 
442
 
 
443
to_textual_order({Root,Ext}) ->
 
444
    {to_textual_order(Root),Ext};
 
445
to_textual_order(Cs) when is_list(Cs) ->
 
446
    case Cs of
 
447
        [#'ComponentType'{textual_order=undefined}|_] ->
 
448
            Cs;
 
449
        _ ->
 
450
            lists:keysort(#'ComponentType'.textual_order,Cs)
 
451
    end.