~statik/ubuntu/maverick/erlang/erlang-merge-testing

« back to all changes in this revision

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

  • Committer: Bazaar Package Importer
  • Author(s): Sergei Golovan
  • Date: 2009-05-01 10:14:38 UTC
  • mfrom: (3.1.4 sid)
  • Revision ID: james.westby@ubuntu.com-20090501101438-6qlr6rsdxgyzrg2z
Tags: 1:13.b-dfsg-2
* Cleaned up patches: removed unneeded patch which helped to support
  different SCTP library versions, made sure that changes for m68k
  architecture applied only when building on this architecture.
* Removed duplicated information from binary packages descriptions.
* Don't require libsctp-dev build-dependency on solaris-i386 architecture
  which allows to build Erlang on Nexenta (thanks to Tim Spriggs for
  the suggestion).

Show diffs side-by-side

added added

removed removed

Lines of Context:
1
 
%%<copyright>
2
 
%% <year>2001-2008</year>
3
 
%% <holder>Ericsson AB, All Rights Reserved</holder>
4
 
%%</copyright>
5
 
%%<legalnotice>
 
1
%%
 
2
%% %CopyrightBegin%
 
3
%% 
 
4
%% Copyright Ericsson AB 2001-2009. All Rights Reserved.
 
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
8
8
%% compliance with the License. You should have received a copy of the
9
9
%% Erlang Public License along with this software. If not, it can be
10
10
%% retrieved online at http://www.erlang.org/.
11
 
%%
 
11
%% 
12
12
%% Software distributed under the License is distributed on an "AS IS"
13
13
%% basis, WITHOUT WARRANTY OF ANY KIND, either express or implied. See
14
14
%% the License for the specific language governing rights and limitations
15
15
%% under the License.
 
16
%% 
 
17
%% %CopyrightEnd%
16
18
%%
17
 
%% The Initial Developer of the Original Code is Ericsson AB.
18
 
%%</legalnotice>
19
19
%%
20
20
-module(asn1rt_check).
21
21
 
47
47
 
48
48
check_int(_,asn1_DEFAULT,_) ->
49
49
    true;
50
 
check_int(Value,Value,_) when integer(Value) ->
 
50
check_int(Value,Value,_) when is_integer(Value) ->
51
51
    true;
52
 
check_int(DefValue,Value,NNL) when atom(Value) ->
 
52
check_int(DefValue,Value,NNL) when is_atom(Value) ->
53
53
    case lists:keysearch(Value,1,NNL) of
54
54
        {value,{_,DefValue}} ->
55
55
            true;
59
59
check_int(DefaultValue,_Value,_) ->
60
60
    throw({error,DefaultValue}).
61
61
 
62
 
% check_bitstring([H|T],[H|T],_) when integer(H) ->
 
62
% check_bitstring([H|T],[H|T],_) when is_integer(H) ->
63
63
%     true;
64
 
% check_bitstring(V,V,_) when integer(V) ->
 
64
% check_bitstring(V,V,_) when is_integer(V) ->
65
65
%     true;
66
66
%% Two equal lists or integers
67
67
check_bitstring(_,asn1_DEFAULT,_) ->
69
69
check_bitstring(V,V,_) ->
70
70
    true;
71
71
%% Default value as a list of 1 and 0 and user value as an integer
72
 
check_bitstring(L=[H|T],Int,_) when integer(Int),integer(H) ->
 
72
check_bitstring(L=[H|T],Int,_) when is_integer(Int),is_integer(H) ->
73
73
    case bit_list_to_int(L,length(T)) of
74
74
        Int -> true;
75
75
        _ -> throw({error,L,Int})
76
76
    end;
77
77
%% Default value as an integer, val as list
78
 
check_bitstring(Int,Val,NBL) when integer(Int),list(Val) ->
 
78
check_bitstring(Int,Val,NBL) when is_integer(Int),is_list(Val) ->
79
79
    BL = int_to_bit_list(Int,[],length(Val)),
80
80
    check_bitstring(BL,Val,NBL);
81
81
%% Default value and user value as lists of ones and zeros
82
 
check_bitstring(L1=[H1|_T1],L2=[H2|_T2],NBL=[_H|_T]) when integer(H1),integer(H2) ->
 
82
check_bitstring(L1=[H1|_T1],L2=[H2|_T2],NBL=[_H|_T]) when is_integer(H1),is_integer(H2) ->
83
83
    L2new = remove_trailing_zeros(L2),
84
84
    check_bitstring(L1,L2new,NBL);
85
85
%% Default value as a list of 1 and 0 and user value as a list of atoms
86
 
check_bitstring(L1=[H1|_T1],L2=[H2|_T2],NBL) when integer(H1),atom(H2) ->
 
86
check_bitstring(L1=[H1|_T1],L2=[H2|_T2],NBL) when is_integer(H1),is_atom(H2) ->
87
87
    L3 = bit_list_to_nbl(L1,NBL,0,[]),
88
88
    check_bitstring(L3,L2,NBL);
89
89
%% Both default value and user value as a list of atoms
90
90
check_bitstring(L1=[H1|T1],L2=[H2|_T2],_) 
91
 
  when atom(H1),atom(H2),length(L1) == length(L2) ->
 
91
  when is_atom(H1),is_atom(H2),length(L1) == length(L2) ->
92
92
    case lists:member(H1,L2) of
93
93
        true ->
94
94
            check_bitstring1(T1,L2);
95
95
        false -> throw({error,L2})
96
96
    end;
97
97
%% Default value as a list of atoms and user value as a list of 1 and 0
98
 
check_bitstring(L1=[H1|_T1],L2=[H2|_T2],NBL) when atom(H1),integer(H2) ->
 
98
check_bitstring(L1=[H1|_T1],L2=[H2|_T2],NBL) when is_atom(H1),is_integer(H2) ->
99
99
    L3 = bit_list_to_nbl(L2,NBL,0,[]),
100
100
    check_bitstring(L1,L3,NBL);
101
101
%% User value in compact format
161
161
    true;
162
162
check_octetstring(L,L) ->
163
163
    true;
164
 
check_octetstring(L,Int) when list(L),integer(Int) ->
 
164
check_octetstring(L,Int) when is_list(L),is_integer(Int) ->
165
165
    case integer_to_octetlist(Int) of
166
166
        L -> true;
167
167
        V -> throw({error,V})
187
187
    true;
188
188
check_objectidentifier(OI,OI) ->
189
189
    true;
190
 
check_objectidentifier(DOI,OI) when tuple(DOI),tuple(OI) ->
 
190
check_objectidentifier(DOI,OI) when is_tuple(DOI),is_tuple(OI) ->
191
191
    check_objectidentifier1(tuple_to_list(DOI),tuple_to_list(OI));
192
192
check_objectidentifier(_,OI) ->
193
193
    throw({error,OI}).
255
255
    true;
256
256
check_enum(Val,Val,_) ->
257
257
    true;
258
 
check_enum(Int,Atom,Enumerations) when integer(Int),atom(Atom) ->
 
258
check_enum(Int,Atom,Enumerations) when is_integer(Int),is_atom(Atom) ->
259
259
    case lists:keysearch(Atom,1,Enumerations) of
260
260
        {value,{_,Int}} -> true;
261
261
        _ -> throw({error,{enumerated,Int,Atom}})
284
284
check_restrictedstring([V1,V2,V3,V4],{V1,V2,V3,V4}) ->
285
285
    true;
286
286
%% character string list
287
 
check_restrictedstring(V1,V2) when list(V1),tuple(V2) ->
 
287
check_restrictedstring(V1,V2) when is_list(V1),is_tuple(V2) ->
288
288
    check_restrictedstring(V1,tuple_to_list(V2));
289
289
check_restrictedstring(V1,V2) ->
290
290
    throw({error,{restricted,string,V1,V2}}).
291
291
 
292
 
transform_to_EXTERNAL1990(Val) when tuple(Val),size(Val) == 4 ->
 
292
transform_to_EXTERNAL1990(Val) when is_tuple(Val),size(Val) == 4 ->
293
293
    transform_to_EXTERNAL1990(tuple_to_list(Val),[]);
294
 
transform_to_EXTERNAL1990(Val) when tuple(Val) ->
 
294
transform_to_EXTERNAL1990(Val) when is_tuple(Val) ->
295
295
    %% Data already in ASN1 1990 format
296
296
    Val.
297
297
 
306
306
    transform_to_EXTERNAL1990(Rest,[Presentation_Cid,Transfer_syntax|Acc]);
307
307
transform_to_EXTERNAL1990([asn1_NOVALUE|Rest],Acc) ->
308
308
    transform_to_EXTERNAL1990(Rest,[asn1_NOVALUE|Acc]);
309
 
transform_to_EXTERNAL1990([Data_val_desc,Data_value],Acc) when list(Data_value)->
 
309
transform_to_EXTERNAL1990([Data_val_desc,Data_value],Acc) when is_list(Data_value)->
310
310
    list_to_tuple(lists:reverse([{'octet-aligned',Data_value},
311
311
                                 Data_val_desc|Acc]));
312
312
transform_to_EXTERNAL1990([Data_val_desc,Data_value],Acc)
313
 
  when binary(Data_value)->
 
313
  when is_binary(Data_value)->
314
314
    list_to_tuple(lists:reverse([{'octet-aligned',binary_to_list(Data_value)},
315
315
                                 Data_val_desc|Acc]));
316
 
transform_to_EXTERNAL1990([Data_value],Acc) when list(Data_value)->
 
316
transform_to_EXTERNAL1990([Data_value],Acc) when is_list(Data_value)->
317
317
    list_to_tuple(lists:reverse([{'octet-aligned',Data_value}|Acc])).
318
318
 
319
319
 
329
329
                 {'EXTERNAL_identification_context-negotiation',IndRef,DRef}}
330
330
        end,
331
331
    case Encoding of
332
 
        {_,Val} when list(Val);binary(Val) ->
 
332
        {_,Val} when is_list(Val);is_binary(Val) ->
333
333
            {'EXTERNAL',Identification,Data_v_desc,Val};
334
334
        
335
335
        _  ->
356
356
%% Res -> list()
357
357
%% Sorts the elements in Arg in increasing size
358
358
dynamicsort_SETOF(ListOfEncVal) ->
359
 
    BinL = lists:map(fun(L) when list(L) -> list_to_binary(L);
 
359
    BinL = lists:map(fun(L) when is_list(L) -> list_to_binary(L);
360
360
                        (B) -> B end,ListOfEncVal),
361
361
    lists:sort(BinL).