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

« back to all changes in this revision

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

  • Committer: Bazaar Package Importer
  • Author(s): Sergei Golovan
  • Date: 2009-05-07 15:07:37 UTC
  • mfrom: (1.2.1 upstream) (5.1.2 sid)
  • Revision ID: james.westby@ubuntu.com-20090507150737-i4yb5elwinm7r0hc
Tags: 1:13.b-dfsg1-1
* Removed another bunch of non-free RFCs from original tarball
  (closes: #527053).
* Fixed build-dependencies list by adding missing comma. This requires
  libsctp-dev again. Also, added libsctp1 dependency to erlang-base and
  erlang-base-hipe packages because the shared library is loaded via
  dlopen now and cannot be added using dh_slibdeps (closes: #526682).
* Weakened dependency of erlang-webtool on erlang-observer to recommends
  to avoid circular dependencies (closes: #526627).
* Added solaris-i386 to HiPE enabled architectures.
* Made script sources in /usr/lib/erlang/erts-*/bin directory executable,
  which is more convenient if a user wants to create a target Erlang system.
* Shortened extended description line for erlang-dev package to make it
  fit 80x25 terminals.

Show diffs side-by-side

added added

removed removed

Lines of Context:
1
 
%%<copyright>
2
 
%% <year>2002-2008</year>
3
 
%% <holder>Ericsson AB, All Rights Reserved</holder>
4
 
%%</copyright>
5
 
%%<legalnotice>
 
1
%%
 
2
%% %CopyrightBegin%
 
3
%% 
 
4
%% Copyright Ericsson AB 2002-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_per_bin_rt2ct).
21
21
 
95
95
    end.
96
96
 
97
97
%% converts a list to a record if necessary
98
 
list_to_record(_,Tuple) when tuple(Tuple) ->
 
98
list_to_record(_,Tuple) when is_tuple(Tuple) ->
99
99
    Tuple;
100
 
list_to_record(Name,List) when list(List) ->
 
100
list_to_record(Name,List) when is_list(List) ->
101
101
    list_to_tuple([Name|List]).
102
102
 
103
103
%%--------------------------------------------------------
121
121
%    [{debug,ext},{bits,1,1}];
122
122
    [1].
123
123
 
124
 
fixoptionals(OptList,_OptLength,Val) when tuple(Val) ->
 
124
fixoptionals(OptList,_OptLength,Val) when is_tuple(Val) ->
125
125
%    Bits = fixoptionals(OptList,Val,0),
126
126
%    {Val,{bits,OptLength,Bits}};
127
127
%    {Val,[10,OptLength,Bits]};
130
130
fixoptionals([],_,Acc) ->
131
131
    %% Optbits
132
132
    lists:reverse(Acc);
 
133
fixoptionals([{Pos,DefVal}|Ot],Val,Acc) ->
 
134
    case element(Pos,Val) of
 
135
        asn1_DEFAULT -> fixoptionals(Ot,Val,[0|Acc]);
 
136
        DefVal -> fixoptionals(Ot,Val,[0|Acc]);
 
137
        _ -> fixoptionals(Ot,Val,[1|Acc])
 
138
    end;
133
139
fixoptionals([Pos|Ot],Val,Acc) ->
134
140
    case element(Pos,Val) of
135
141
        asn1_NOVALUE -> fixoptionals(Ot,Val,[0|Acc]);
266
272
%%
267
273
set_choice(Alt,{L1,L2},{Len1,_Len2}) ->
268
274
    case set_choice_tag(Alt,L1) of
269
 
        N when integer(N), Len1 > 1 ->
 
275
        N when is_integer(N), Len1 > 1 ->
270
276
%           [{bits,1,0}, % the value is in the root set
271
277
%            encode_constrained_number({0,Len1-1},N)];
272
278
            [0, % the value is in the root set
273
279
             encode_constrained_number({0,Len1-1},N)];
274
 
        N when integer(N) ->
 
280
        N when is_integer(N) ->
275
281
%           [{bits,1,0}]; % no encoding if only 0 or 1 alternative
276
282
            [0]; % no encoding if only 0 or 1 alternative
277
283
        false ->
278
284
%           [{bits,1,1}, % extension value
279
285
            [1, % extension value
280
286
             case set_choice_tag(Alt,L2) of
281
 
                 N2 when integer(N2) ->
 
287
                 N2 when is_integer(N2) ->
282
288
                     encode_small_number(N2);
283
289
                 false ->
284
290
                     unknown_choice_alt
286
292
    end;
287
293
set_choice(Alt,L,Len) ->
288
294
    case set_choice_tag(Alt,L) of
289
 
        N when integer(N), Len > 1 ->
 
295
        N when is_integer(N), Len > 1 ->
290
296
            encode_constrained_number({0,Len-1},N);
291
 
        N when integer(N) ->
 
297
        N when is_integer(N) ->
292
298
            []; % no encoding if only 0 or 1 alternative
293
299
        false ->
294
300
            [unknown_choice_alt]
324
330
decode_fragmented_bits(<<0:1,0:7,Bin/binary>>,C,Acc) ->
325
331
    BinBits = erlang:list_to_bitstring(lists:reverse(Acc)),
326
332
    case C of
327
 
        Int when integer(Int),C == bit_size(BinBits) ->
 
333
        Int when is_integer(Int),C == bit_size(BinBits) ->
328
334
            {BinBits,Bin};
329
 
        Int when integer(Int) ->
 
335
        Int when is_integer(Int) ->
330
336
            exit({error,{asn1,{illegal_value,C,BinBits}}})
331
337
    end;
332
338
decode_fragmented_bits(<<0:1,Len:7,Bin/binary>>,C,Acc) ->
333
339
    <<Value:Len/bitstring,Rest/bitstring>> = Bin,
334
340
    BinBits = erlang:list_to_bitstring([Value|Acc]),
335
341
    case C of
336
 
        Int when integer(Int),C == bit_size(BinBits) ->
 
342
        Int when is_integer(Int),C == bit_size(BinBits) ->
337
343
            {BinBits,Rest};
338
 
        Int when integer(Int) ->
 
344
        Int when is_integer(Int) ->
339
345
            exit({error,{asn1,{illegal_value,C,BinBits}}})
340
346
    end.
341
347
 
349
355
decode_fragmented_octets(<<0:1,0:7,Bin/binary>>,C,Acc) ->
350
356
    Octets = list_to_binary(lists:reverse(Acc)),
351
357
    case C of
352
 
        Int when integer(Int), C == size(Octets) ->
 
358
        Int when is_integer(Int), C == size(Octets) ->
353
359
            {Octets,Bin};
354
 
        Int when integer(Int) ->
 
360
        Int when is_integer(Int) ->
355
361
            exit({error,{asn1,{illegal_value,C,Octets}}})
356
362
    end;
357
363
decode_fragmented_octets(<<0:1,Len:7,Bin/binary>>,C,Acc) ->
358
364
    <<Value:Len/binary-unit:8,Bin2/binary>> = Bin,
359
365
    BinOctets = list_to_binary(lists:reverse([Value|Acc])),
360
366
    case C of
361
 
        Int when integer(Int),size(BinOctets) == Int ->
 
367
        Int when is_integer(Int),size(BinOctets) == Int ->
362
368
            {BinOctets,Bin2};
363
 
        Int when integer(Int) ->
 
369
        Int when is_integer(Int) ->
364
370
            exit({error,{asn1,{illegal_value,C,BinOctets}}})
365
371
    end.
366
372
 
372
378
%%         | binary
373
379
%% Contraint = not used in this version
374
380
%%
375
 
encode_open_type(_Constraint, Val) when list(Val) ->
 
381
encode_open_type(_Constraint, Val) when is_list(Val) ->
376
382
    Bin = list_to_binary(Val),
377
383
    case size(Bin) of 
378
384
        Size when Size>255 ->
380
386
        Size ->
381
387
            [encode_length(undefined,Size),[20,Size,Bin]]
382
388
    end;
383
 
encode_open_type(_Constraint, Val) when binary(Val) ->
 
389
encode_open_type(_Constraint, Val) when is_binary(Val) ->
384
390
    case size(Val) of
385
391
        Size when Size>255 ->
386
392
            [encode_length(undefined,size(Val)),[21,<<Size:16>>,Val]]; % octets implies align
405
411
%% encode_integer(Constraint,{Name,Value}) -> CompleteList
406
412
%% 
407
413
%%
408
 
encode_integer(C,V,NamedNumberList) when atom(V) ->
 
414
encode_integer(C,V,NamedNumberList) when is_atom(V) ->
409
415
    case lists:keysearch(V,1,NamedNumberList) of
410
416
        {value,{_,NewV}} -> 
411
417
            encode_integer(C,NewV);
412
418
        _ -> 
413
419
            exit({error,{asn1,{namednumber,V}}})
414
420
    end;
415
 
encode_integer(C,V,_NamedNumberList) when integer(V) ->
 
421
encode_integer(C,V,_NamedNumberList) when is_integer(V) ->
416
422
    encode_integer(C,V);
417
 
encode_integer(C,{Name,V},NamedNumberList) when atom(Name) ->
 
423
encode_integer(C,{Name,V},NamedNumberList) when is_atom(Name) ->
418
424
    encode_integer(C,V,NamedNumberList).
419
425
 
420
 
encode_integer(C,{Name,Val}) when atom(Name) ->
 
426
encode_integer(C,{Name,Val}) when is_atom(Name) ->
421
427
    encode_integer(C,Val);
422
428
 
423
 
encode_integer([{Rc,_Ec}],Val) when tuple(Rc) -> % XXX when is this invoked? First argument most often a list,...Ok this is the extension case...but it doesn't work.
 
429
encode_integer([{Rc,_Ec}],Val) when is_tuple(Rc) -> % XXX when is this invoked? First argument most often a list,...Ok this is the extension case...but it doesn't work.
424
430
    case (catch encode_integer([Rc],Val)) of
425
431
        {'EXIT',{error,{asn1,_}}} ->
426
432
%           [{bits,1,1},encode_unconstrained_number(Val)];
457
463
        _ -> {Val,Buffer2}
458
464
    end.
459
465
 
460
 
decode_integer(Buffer,[{Rc,_Ec}]) when tuple(Rc) ->
 
466
decode_integer(Buffer,[{Rc,_Ec}]) when is_tuple(Rc) ->
461
467
    {Ext,Buffer2} = getext(Buffer),
462
468
    case Ext of
463
469
        0 -> decode_integer(Buffer2,[Rc]);
467
473
    decode_unconstrained_number(Buffer);
468
474
decode_integer(Buffer,C) ->
469
475
    case get_constraint(C,'SingleValue') of
470
 
        V when integer(V) ->
 
476
        V when is_integer(V) ->
471
477
            {V,Buffer};
472
478
        _ ->
473
479
            decode_integer1(Buffer,C)
486
492
%% X.691:10.6 Encoding of a normally small non-negative whole number
487
493
%% Use this for encoding of CHOICE index if there is an extension marker in 
488
494
%% the CHOICE
489
 
encode_small_number({Name,Val}) when atom(Name) ->
 
495
encode_small_number({Name,Val}) when is_atom(Name) ->
490
496
    encode_small_number(Val);
491
497
encode_small_number(Val) when Val =< 63 ->
492
498
%    [{bits,1,0},{bits,6,Val}];
507
513
 
508
514
%% X.691:10.7 Encoding of a semi-constrained whole number
509
515
%% might be an optimization encode_semi_constrained_number(0,Val) ->
510
 
encode_semi_constrained_number(C,{Name,Val}) when atom(Name) ->
 
516
encode_semi_constrained_number(C,{Name,Val}) when is_atom(Name) ->
511
517
    encode_semi_constrained_number(C,Val);
512
518
encode_semi_constrained_number({Lb,'MAX'},Val) ->
513
519
    encode_semi_constrained_number(Lb,Val);
568
574
            exit({not_supported,{integer_range,Range}})
569
575
    end.
570
576
 
571
 
encode_constrained_number(Range,{Name,Val}) when atom(Name) ->
 
577
encode_constrained_number(Range,{Name,Val}) when is_atom(Name) ->
572
578
    encode_constrained_number(Range,Val);
573
579
encode_constrained_number({Lb,Ub},Val) when Val >= Lb, Ub >= Val -> 
574
580
    Range = Ub - Lb + 1,
769
775
    encode_length(undefined,Len);
770
776
encode_length(Vr={Lb,Ub},Len) when Ub =< 65535 ,Lb >= 0 -> % constrained
771
777
    encode_constrained_number(Vr,Len);
772
 
encode_length({Lb,_Ub},Len) when integer(Lb), Lb >= 0 -> % Ub > 65535
 
778
encode_length({Lb,_Ub},Len) when is_integer(Lb), Lb >= 0 -> % Ub > 65535
773
779
    encode_length(undefined,Len);
774
780
encode_length({Vr={Lb,Ub},Ext},Len) 
775
781
  when Ub =< 65535 ,Lb >= 0,Len=<Ub, is_list(Ext) -> 
777
783
    [0,encode_constrained_number(Vr,Len)];
778
784
encode_length({{Lb,_},Ext},Len) when is_list(Ext) -> 
779
785
    [1,encode_semi_constrained_number(Lb,Len)];
780
 
encode_length(SingleValue,_Len) when integer(SingleValue) ->
 
786
encode_length(SingleValue,_Len) when is_integer(SingleValue) ->
781
787
    [].
782
788
 
783
789
%% X.691 10.9.3.4 (only used for length of bitmap that prefixes extension 
816
822
 
817
823
decode_length(Buffer,{Lb,Ub}) when Ub =< 65535 ,Lb >= 0 -> % constrained
818
824
    decode_constrained_number(Buffer,{Lb,Ub});
819
 
decode_length(Buffer,{Lb,_Ub}) when integer(Lb), Lb >= 0 -> % Ub > 65535
 
825
decode_length(Buffer,{Lb,_Ub}) when is_integer(Lb), Lb >= 0 -> % Ub > 65535
820
826
    decode_length(Buffer,undefined);
821
827
decode_length(Buffer,{{Lb,Ub},Ext}) when is_list(Ext) -> 
822
828
    case getbit(Buffer) of
823
829
        {0,Buffer2} ->
824
 
            decode_length(Buffer2, {Lb,Ub})
 
830
            decode_length(Buffer2, {Lb,Ub});
 
831
        {1,Buffer2} ->
 
832
            decode_length(Buffer2, undefined)
825
833
    end;
826
834
 
827
835
 
839
847
                    exit({error,{asn1,{decode_length,{nyi,length_above_64K}}}})
840
848
            end
841
849
    end;
842
 
decode_length(Buffer,SingleValue) when integer(SingleValue) ->
 
850
decode_length(Buffer,SingleValue) when is_integer(SingleValue) ->
843
851
    {SingleValue,Buffer}.
844
852
 
845
853
 
852
860
 
853
861
 
854
862
%% ENUMERATED with extension marker
855
 
decode_enumerated(Buffer,C,{Ntup1,Ntup2}) when tuple(Ntup1), tuple(Ntup2) ->
 
863
decode_enumerated(Buffer,C,{Ntup1,Ntup2}) when is_tuple(Ntup1), is_tuple(Ntup2) ->
856
864
    {Ext,Buffer2} = getext(Buffer),
857
865
    case Ext of
858
866
        0 -> % not an extension value
859
867
            {Val,Buffer3} = decode_integer(Buffer2,C),
860
868
            case catch (element(Val+1,Ntup1)) of
861
 
                NewVal when atom(NewVal) -> {NewVal,Buffer3};
 
869
                NewVal when is_atom(NewVal) -> {NewVal,Buffer3};
862
870
                _Error -> exit({error,{asn1,{decode_enumerated,{Val,[Ntup1,Ntup2]}}}})
863
871
            end;
864
872
        1 -> % this an extension value
865
873
            {Val,Buffer3} = decode_small_number(Buffer2),
866
874
            case catch (element(Val+1,Ntup2)) of
867
 
                NewVal when atom(NewVal) -> {NewVal,Buffer3};
 
875
                NewVal when is_atom(NewVal) -> {NewVal,Buffer3};
868
876
                _ -> {{asn1_enum,Val},Buffer3}
869
877
            end
870
878
    end;
871
879
 
872
 
decode_enumerated(Buffer,C,NamedNumberTup) when tuple(NamedNumberTup) ->
 
880
decode_enumerated(Buffer,C,NamedNumberTup) when is_tuple(NamedNumberTup) ->
873
881
    {Val,Buffer2} = decode_integer(Buffer,C),
874
882
    case catch (element(Val+1,NamedNumberTup)) of
875
 
        NewVal when atom(NewVal) -> {NewVal,Buffer2};
 
883
        NewVal when is_atom(NewVal) -> {NewVal,Buffer2};
876
884
        _Error -> exit({error,{asn1,{decode_enumerated,{Val,NamedNumberTup}}}})
877
885
    end.
878
886
 
905
913
%% Unused = integer(),
906
914
%% BinBits = binary().
907
915
 
908
 
encode_bit_string(C,Bin={Unused,BinBits},NamedBitList) when integer(Unused),
909
 
                                                            binary(BinBits) ->
 
916
encode_bit_string(C,Bin={Unused,BinBits},NamedBitList) when is_integer(Unused),
 
917
                                                            is_binary(BinBits) ->
910
918
    encode_bin_bit_string(C,Bin,NamedBitList);
911
919
 
912
920
%% when the value is a list of named bits
913
921
 
914
 
encode_bit_string(C, LoNB=[FirstVal | _RestVal], NamedBitList) when atom(FirstVal) ->
 
922
encode_bit_string(C, LoNB=[FirstVal | _RestVal], NamedBitList) when is_atom(FirstVal) ->
915
923
    ToSetPos = get_all_bitposes(LoNB, NamedBitList, []),
916
924
    BitList = make_and_set_list(ToSetPos,0),
917
925
    encode_bit_string(C,BitList,NamedBitList);% consider the constraint
923
931
 
924
932
%% when the value is a list of ones and zeroes
925
933
encode_bit_string(Int, BitListValue, _) 
926
 
  when list(BitListValue),integer(Int),Int =< 16 ->
 
934
  when is_list(BitListValue),is_integer(Int),Int =< 16 ->
927
935
    %% The type is constrained by a single value size constraint
928
936
    [40,Int,length(BitListValue),BitListValue];
929
937
encode_bit_string(Int, BitListValue, _) 
930
 
  when list(BitListValue),integer(Int), Int =< 255 ->
 
938
  when is_list(BitListValue),is_integer(Int), Int =< 255 ->
931
939
    %% The type is constrained by a single value size constraint
932
940
    [2,40,Int,length(BitListValue),BitListValue];
933
941
encode_bit_string(Int, BitListValue, _) 
934
 
  when list(BitListValue),integer(Int), Int < ?'64K' ->
 
942
  when is_list(BitListValue),is_integer(Int), Int < ?'64K' ->
935
943
    {Code,DesiredLength,Length} = 
936
944
        case length(BitListValue) of
937
945
            B1 when B1 > Int ->
947
955
    %% The type is constrained by a single value size constraint
948
956
    [2,Code,DesiredLength,Length,BitListValue];
949
957
encode_bit_string(no, BitListValue,[]) 
950
 
  when list(BitListValue) ->
 
958
  when is_list(BitListValue) ->
951
959
    [encode_length(undefined,length(BitListValue)),
952
960
     2,BitListValue];
 
961
encode_bit_string({{Fix,Fix},Ext}, BitListValue,[]) 
 
962
  when is_integer(Fix), is_list(Ext) ->
 
963
    case length(BitListValue) of
 
964
        Len when Len =< Fix ->
 
965
            [0,encode_bit_string(Fix,BitListValue,[])];
 
966
        _ ->
 
967
            [1,encode_bit_string(no,BitListValue,[])]
 
968
    end;
953
969
encode_bit_string(C, BitListValue,[]) 
954
 
  when list(BitListValue) ->
 
970
  when is_list(BitListValue) ->
955
971
    [encode_length(C,length(BitListValue)),
956
972
     2,BitListValue];
957
973
encode_bit_string(no, BitListValue,_NamedBitList) 
958
 
  when list(BitListValue) ->
 
974
  when is_list(BitListValue) ->
959
975
    %% this case with an unconstrained BIT STRING can be made more efficient
960
976
    %% if the complete driver can take a special code so the length field
961
977
    %% is encoded there.
963
979
                                            lists:reverse(BitListValue))),
964
980
    [encode_length(undefined,length(NewBitLVal)),
965
981
     2,NewBitLVal];
 
982
encode_bit_string({{Fix,Fix},Ext}, BitListValue,_NamedBitList) 
 
983
  when is_integer(Fix), is_list(Ext) ->
 
984
    case length(BitListValue) of
 
985
        Len when Len =< Fix ->
 
986
            [0,encode_bit_string(Fix,BitListValue,_NamedBitList)];
 
987
        _ ->
 
988
            [1,encode_bit_string(no,BitListValue,_NamedBitList)]
 
989
    end;
966
990
encode_bit_string(C,BitListValue,_NamedBitList) 
967
 
  when list(BitListValue) ->% C = {_,'MAX'}
 
991
  when is_list(BitListValue) ->% C = {_,'MAX'}
968
992
%     NewBitLVal = lists:reverse(lists:dropwhile(fun(0)->true;(1)->false end,
969
993
%                                           lists:reverse(BitListValue))),
970
994
    NewBitLVal = bit_string_trailing_zeros(BitListValue,C),
973
997
 
974
998
 
975
999
%% when the value is an integer
976
 
encode_bit_string(C, IntegerVal, NamedBitList) when integer(IntegerVal)->
 
1000
encode_bit_string(C, IntegerVal, NamedBitList) when is_integer(IntegerVal)->
977
1001
    BitList = int_to_bitlist(IntegerVal),
978
1002
    encode_bit_string(C,BitList,NamedBitList);
979
1003
 
980
1004
%% when the value is a tuple
981
 
encode_bit_string(C,{Name,Val}, NamedBitList) when atom(Name) ->
 
1005
encode_bit_string(C,{Name,Val}, NamedBitList) when is_atom(Name) ->
982
1006
    encode_bit_string(C,Val,NamedBitList).
983
1007
 
984
 
bit_string_trailing_zeros(BitList,C) when integer(C) ->
 
1008
bit_string_trailing_zeros(BitList,C) when is_integer(C) ->
985
1009
    bit_string_trailing_zeros1(BitList,C,C);
986
 
bit_string_trailing_zeros(BitList,{Lb,Ub}) when integer(Lb) ->
 
1010
bit_string_trailing_zeros(BitList,{Lb,Ub}) when is_integer(Lb) ->
987
1011
    bit_string_trailing_zeros1(BitList,Lb,Ub);
988
 
bit_string_trailing_zeros(BitList,{{Lb,Ub},_}) when integer(Lb) ->
 
1012
bit_string_trailing_zeros(BitList,{{Lb,Ub},_}) when is_integer(Lb) ->
989
1013
    bit_string_trailing_zeros1(BitList,Lb,Ub);
990
1014
bit_string_trailing_zeros(BitList,_) ->
991
1015
    BitList.
1006
1030
%% Unused = integer(),i.e. number unused bits in least sign. byte of
1007
1031
%% BinBits = binary().
1008
1032
encode_bin_bit_string(C,{_,BinBits},_NamedBitList)
1009
 
  when integer(C),C=<16 ->
 
1033
  when is_integer(C),C=<16 ->
1010
1034
    [45,C,size(BinBits),BinBits];
1011
1035
encode_bin_bit_string(C,{_Unused,BinBits},_NamedBitList)
1012
 
  when integer(C) ->
 
1036
  when is_integer(C), C =< 255 ->
1013
1037
    [2,45,C,size(BinBits),BinBits];
 
1038
encode_bin_bit_string(C,{_Unused,BinBits},_NamedBitList)
 
1039
  when is_integer(C), C =< 65535 ->
 
1040
    case size(BinBits) of
 
1041
        Size when Size =< 255 ->
 
1042
            [2,46,<<C:16>>,Size,BinBits];
 
1043
        Size ->
 
1044
            [2,47,<<C:16>>,<<Size:16>>,BinBits]
 
1045
    end;
 
1046
%% encode_bin_bit_string(C,{_Unused,BinBits},_NamedBitList)
 
1047
%%   when is_integer(C) ->
 
1048
%%     exit({error,{asn1, {bitstring_size, not_supported, C}}});
1014
1049
encode_bin_bit_string(C,UnusedAndBin={_,_},NamedBitList) ->
1015
1050
%    UnusedAndBin1 = {Unused1,Bin1} = 
1016
1051
    {Unused1,Bin1} = 
1017
1052
        %% removes all trailing bits if NamedBitList is not empty
1018
1053
        remove_trailing_bin(NamedBitList,UnusedAndBin),
1019
1054
    case C of
1020
 
        {Lb,Ub} when integer(Lb),integer(Ub) ->
 
1055
        {Lb,Ub} when is_integer(Lb),is_integer(Ub) ->
1021
1056
%           [encode_length({Lb,Ub},size(Bin1)*8 - Unused1),
1022
1057
%            align,UnusedAndBin1];
1023
1058
            Size=size(Bin1),
1027
1062
            Size=size(Bin1),
1028
1063
            [encode_length(undefined,Size*8 - Unused1),
1029
1064
             2,octets_unused_to_complete(Unused1,Size,Bin1)];
 
1065
        {{Fix,Fix},Ext} when is_integer(Fix),is_list(Ext) ->
 
1066
            %%[encode_length(Sc,size(Bin1)*8 - Unused1),
 
1067
            case size(Bin1)*8 - Unused1 of
 
1068
                Size when Size =< Fix  ->
 
1069
                    [0,encode_bin_bit_string(Fix,UnusedAndBin,NamedBitList)];
 
1070
                _Size ->
 
1071
                    [1,encode_bin_bit_string(no,UnusedAndBin,NamedBitList)]
 
1072
            end;
1030
1073
        Sc -> 
1031
1074
            Size=size(Bin1),
1032
1075
            [encode_length(Sc,Size*8 - Unused1),
1100
1143
    case get_constraint(C,'SizeConstraint') of
1101
1144
        0 -> % fixed length
1102
1145
            {{8,0},Buffer};
1103
 
        V when integer(V),V=<16 -> %fixed length 16 bits or less
 
1146
        V when is_integer(V),V=<16 -> %fixed length 16 bits or less
1104
1147
            compact_bit_string(Buffer,V,NamedNumberList);
1105
 
        V when integer(V),V=<65536 -> %fixed length > 16 bits
 
1148
        V when is_integer(V),V=<65536 -> %fixed length > 16 bits
1106
1149
            Bytes2 = align(Buffer),
1107
1150
            compact_bit_string(Bytes2,V,NamedNumberList);
1108
 
        V when integer(V) -> % V > 65536 => fragmented value
 
1151
        V when is_integer(V) -> % V > 65536 => fragmented value
1109
1152
            {BitStr,Buffer2} = decode_fragmented_bits(Buffer,V),
1110
1153
            case bit_size(BitStr) band 7 of
1111
1154
                0 -> {{0,BitStr},Buffer2};
1112
1155
                N -> {{8-N,<<BitStr/bitstring,0:(8-N)>>},Buffer2}
1113
1156
            end;
1114
 
        {Lb,Ub} when integer(Lb),integer(Ub) ->
 
1157
        {Lb,Ub} when is_integer(Lb),is_integer(Ub) ->
1115
1158
            %% This case may demand decoding of fragmented length/value
1116
1159
            {Len,Bytes2} = decode_length(Buffer,{Lb,Ub}),
1117
1160
            Bytes3 = align(Bytes2),
1121
1164
            {Len,Bytes2} = decode_length(Buffer,undefined),
1122
1165
            Bytes3 = align(Bytes2),
1123
1166
            compact_bit_string(Bytes3,Len,NamedNumberList);
 
1167
        {{Fix,Fix},Ext} = Sc when is_integer(Fix), is_list(Ext) ->
 
1168
            case decode_length(Buffer,Sc) of
 
1169
                {Len,Bytes2} when Len > Fix ->
 
1170
                    Bytes3 = align(Bytes2),
 
1171
                    compact_bit_string(Bytes3,Len,NamedNumberList);
 
1172
                {Len,Bytes2} when Len > 16 ->
 
1173
                    Bytes3 = align(Bytes2),
 
1174
                    compact_bit_string(Bytes3,Len,NamedNumberList);
 
1175
                {Len,Bytes2} ->
 
1176
                    compact_bit_string(Bytes2,Len,NamedNumberList)
 
1177
            end;
1124
1178
        Sc ->
1125
1179
            {Len,Bytes2} = decode_length(Buffer,Sc),
1126
1180
            Bytes3 = align(Bytes2),
1134
1188
%% 
1135
1189
decode_bit_string(Buffer, C, NamedNumberList) ->
1136
1190
    case get_constraint(C,'SizeConstraint') of
1137
 
        {Lb,Ub} when integer(Lb),integer(Ub) ->
 
1191
        {Lb,Ub} when is_integer(Lb),is_integer(Ub) ->
1138
1192
            {Len,Bytes2} = decode_length(Buffer,{Lb,Ub}),
1139
1193
            Bytes3 = align(Bytes2),
1140
1194
            bit_list_or_named(Bytes3,Len,NamedNumberList);
1144
1198
            bit_list_or_named(Bytes3,Len,NamedNumberList);
1145
1199
        0 -> % fixed length
1146
1200
            {[],Buffer}; % nothing to encode
1147
 
        V when integer(V),V=<16 -> % fixed length 16 bits or less
 
1201
        V when is_integer(V),V=<16 -> % fixed length 16 bits or less
1148
1202
            bit_list_or_named(Buffer,V,NamedNumberList);
1149
 
        V when integer(V),V=<65536 ->
 
1203
        V when is_integer(V),V=<65536 ->
1150
1204
            Bytes2 = align(Buffer),
1151
1205
            bit_list_or_named(Bytes2,V,NamedNumberList);
1152
 
        V when integer(V) ->
 
1206
        V when is_integer(V) ->
1153
1207
            Bytes2 = align(Buffer),
1154
1208
            {BinBits,_Bytes3} = decode_fragmented_bits(Bytes2,V),
1155
1209
            bit_list_or_named(BinBits,V,NamedNumberList);
 
1210
        {{Fix,Fix},Ext} =Sc when is_integer(Fix), is_list(Ext) ->
 
1211
            case decode_length(Buffer,Sc) of
 
1212
                {Len,Bytes2} when Len > Fix ->
 
1213
                    Bytes3 = align(Bytes2),
 
1214
                    bit_list_or_named(Bytes3,Len,NamedNumberList);
 
1215
                {Len,Bytes2} when Len > 16 ->
 
1216
                    Bytes3 = align(Bytes2),
 
1217
                    bit_list_or_named(Bytes3,Len,NamedNumberList);
 
1218
                {Len,Bytes2} ->
 
1219
                    bit_list_or_named(Bytes2,Len,NamedNumberList)
 
1220
            end;
1156
1221
        Sc -> % extension marker
1157
1222
            {Len,Bytes2} = decode_length(Buffer,Sc),
1158
1223
            Bytes3 = align(Bytes2),
1204
1269
%%%%%%%%%%%%%%%
1205
1270
%% 
1206
1271
 
1207
 
int_to_bitlist(Int) when integer(Int), Int > 0 ->
 
1272
int_to_bitlist(Int) when is_integer(Int), Int > 0 ->
1208
1273
    [Int band 1 | int_to_bitlist(Int bsr 1)];
1209
1274
int_to_bitlist(0) ->
1210
1275
    [].
1260
1325
    Len = length(Val),
1261
1326
    [encode_length(SZ,Len),2,
1262
1327
     octets_to_complete(Len,Val)];
1263
 
encode_octet_string(SZ,false,Val) when list(SZ) ->
 
1328
encode_octet_string(SZ,false,Val) when is_list(SZ) ->
1264
1329
    Len = length(Val),
1265
1330
    [encode_length({hd(SZ),lists:max(SZ)},Len),2,
1266
1331
     octets_to_complete(Len,Val)];
1282
1347
%%    {Bs,Bytes2}= getbits(Bytes,16),
1283
1348
%%    {binary_to_list(<<Bs:16>>),Bytes2};
1284
1349
    {[B1,B2],Bytes};
1285
 
decode_octet_string(Bytes,Sv,false) when integer(Sv),Sv=<65535 ->
 
1350
decode_octet_string(Bytes,Sv,false) when is_integer(Sv),Sv=<65535 ->
1286
1351
    %%    Bytes2 = align(Bytes),
1287
1352
    %% getoctets_as_list aligns buffer before it picks octets
1288
1353
    getoctets_as_list(Bytes,Sv);
1289
 
decode_octet_string(Bytes,Sv,false) when integer(Sv) ->
 
1354
decode_octet_string(Bytes,Sv,false) when is_integer(Sv) ->
1290
1355
    Bytes2 = align(Bytes),
1291
1356
    decode_fragmented_octets(Bytes2,Sv);
1292
1357
decode_octet_string(Bytes,{Lb,Ub},false) ->
1293
1358
    {Len,Bytes2} = decode_length(Bytes,{Lb,Ub}),
1294
1359
%%    Bytes3 = align(Bytes2),
1295
1360
    getoctets_as_list(Bytes2,Len);
1296
 
decode_octet_string(Bytes,Sv,false) when list(Sv) ->
 
1361
decode_octet_string(Bytes,Sv,false) when is_list(Sv) ->
1297
1362
    {Len,Bytes2} = decode_length(Bytes,{hd(Sv),lists:max(Sv)}),
1298
1363
%%    Bytes3 = align(Bytes2),
1299
1364
    getoctets_as_list(Bytes2,Len);
1310
1375
%%encode_restricted_string(aligned,'BMPString',Constraints,Extension,Val)
1311
1376
 
1312
1377
 
1313
 
encode_restricted_string(aligned,{Name,Val}) when atom(Name) ->
 
1378
encode_restricted_string(aligned,{Name,Val}) when is_atom(Name) ->
1314
1379
    encode_restricted_string(aligned,Val);
1315
1380
 
1316
 
encode_restricted_string(aligned,Val) when list(Val)->
 
1381
encode_restricted_string(aligned,Val) when is_list(Val)->
1317
1382
    Len = length(Val),
1318
1383
    [encode_length(undefined,Len),octets_to_complete(Len,Val)].
1319
1384
 
1320
1385
 
1321
 
encode_known_multiplier_string(StringType,SizeC,NumBits,CharOutTab,{Name,Val}) when atom(Name) ->
 
1386
encode_known_multiplier_string(StringType,SizeC,NumBits,CharOutTab,{Name,Val}) when is_atom(Name) ->
1322
1387
    encode_known_multiplier_string(StringType,SizeC,NumBits,CharOutTab,Val);
1323
1388
encode_known_multiplier_string(_StringType,SizeC,NumBits,CharOutTab,Val) ->
1324
1389
    Result = chars_encode2(Val,NumBits,CharOutTab),
1325
1390
    case SizeC of
1326
 
        Ub when integer(Ub), Ub*NumBits =< 16  ->
 
1391
        Ub when is_integer(Ub), Ub*NumBits =< 16  ->
1327
1392
            Result;
1328
 
        Ub when integer(Ub),Ub =<65535 -> % fixed length
 
1393
        Ub when is_integer(Ub),Ub =<65535 -> % fixed length
1329
1394
            [2,Result];
1330
1395
        {Ub,Lb} ->
1331
1396
            [encode_length({Ub,Lb},length(Val)),2,Result];
1339
1404
 
1340
1405
decode_known_multiplier_string(StringType,SizeC,NumBits,CharInTab,Bytes) ->
1341
1406
    case SizeC of
1342
 
        Ub when integer(Ub), Ub*NumBits =< 16  ->
 
1407
        Ub when is_integer(Ub), Ub*NumBits =< 16  ->
1343
1408
            chars_decode(Bytes,NumBits,StringType,CharInTab,Ub);
1344
 
        Ub when integer(Ub),Ub =<65535 -> % fixed length
 
1409
        Ub when is_integer(Ub),Ub =<65535 -> % fixed length
1345
1410
            Bytes1 = align(Bytes),
1346
1411
            chars_decode(Bytes1,NumBits,StringType,CharInTab,Ub);
1347
 
        Vl when list(Vl) ->
 
1412
        Vl when is_list(Vl) ->
1348
1413
            {Len,Bytes1} = decode_length(Bytes,{hd(Vl),lists:max(Vl)}),
1349
1414
            Bytes2 = align(Bytes1),
1350
1415
            chars_decode(Bytes2,NumBits,StringType,CharInTab,Len);
1490
1555
 
1491
1556
                                                % X.691:17 
1492
1557
encode_null(_Val) -> []. % encodes to nothing
1493
 
%encode_null({Name,Val}) when atom(Name) ->
 
1558
%encode_null({Name,Val}) when is_atom(Name) ->
1494
1559
%    encode_null(Val).
1495
1560
 
1496
1561
decode_null(Bytes) ->
1503
1568
%% Val -> <<utf8encoded binary>>
1504
1569
%% CompleteList -> [apropriate codes and values for driver complete]
1505
1570
%%
1506
 
encode_UTF8String(Val) when binary(Val) ->
 
1571
encode_UTF8String(Val) when is_binary(Val) ->
1507
1572
    [encode_length(undefined,size(Val)),
1508
1573
     octets_to_complete(size(Val),Val)];
1509
1574
encode_UTF8String(Val) ->
1531
1596
%% Int3-N -> integer()
1532
1597
%% CompleteList -> [{bits,8,Val}|{octets,Ol}|align|...]
1533
1598
%%
1534
 
encode_object_identifier({Name,Val}) when atom(Name) ->
 
1599
encode_object_identifier({Name,Val}) when is_atom(Name) ->
1535
1600
    encode_object_identifier(Val);
1536
1601
encode_object_identifier(Val) ->
1537
1602
    OctetList = e_object_identifier(Val),
1541
1606
 
1542
1607
e_object_identifier({'OBJECT IDENTIFIER',V}) ->
1543
1608
    e_object_identifier(V);
1544
 
e_object_identifier({Cname,V}) when atom(Cname),tuple(V) ->
 
1609
e_object_identifier({Cname,V}) when is_atom(Cname),is_tuple(V) ->
1545
1610
    e_object_identifier(tuple_to_list(V));
1546
 
e_object_identifier({Cname,V}) when atom(Cname),list(V) ->
 
1611
e_object_identifier({Cname,V}) when is_atom(Cname),is_list(V) ->
1547
1612
    e_object_identifier(V);
1548
 
e_object_identifier(V) when tuple(V) ->
 
1613
e_object_identifier(V) when is_tuple(V) ->
1549
1614
    e_object_identifier(tuple_to_list(V));
1550
1615
 
1551
1616
%% E1 = 0|1|2 and (E2 < 40 when E1 = 0|1) 
1672
1737
% this function builds the ugly form of lists [E1|E2] to avoid having to reverse it at the end.
1673
1738
% this is done because it is efficient and that the result always will be sent on a port or
1674
1739
% converted by means of list_to_binary/1
1675
 
 complete1(InList) when list(InList) ->
 
1740
 complete1(InList) when is_list(InList) ->
1676
1741
     complete1(InList,[],[]);
1677
1742
 complete1(InList) ->
1678
1743
     complete1([InList],[],[]).
1679
1744
 
1680
1745
 complete1([],Acc,Bacc) ->
1681
1746
     {Acc,Bacc};
1682
 
 complete1([H|T],Acc,Bacc) when list(H) ->
 
1747
 complete1([H|T],Acc,Bacc) when is_list(H) ->
1683
1748
     {NewH,NewBacc} = complete1(H,Acc,Bacc),
1684
1749
     complete1(T,NewH,NewBacc);
1685
1750
 
1702
1767
     complete1(T,Acc,[]);
1703
1768
 complete1([align|T],Acc,Bacc) ->
1704
1769
     complete1(T,[Acc|complete_bytes(Bacc)],[]);
1705
 
 complete1([{0,Bin}|T],Acc,[]) when binary(Bin) ->
 
1770
 complete1([{0,Bin}|T],Acc,[]) when is_binary(Bin) ->
1706
1771
     complete1(T,[Acc|Bin],[]);
1707
 
 complete1([{Unused,Bin}|T],Acc,[]) when integer(Unused),binary(Bin) ->
 
1772
 complete1([{Unused,Bin}|T],Acc,[]) when is_integer(Unused),is_binary(Bin) ->
1708
1773
     Size = size(Bin)-1,
1709
1774
     <<Bs:Size/binary,B>> = Bin,
1710
1775
     NumBits = 8-Unused,
1711
1776
     complete1(T,[Acc|Bs],[[B bsr Unused]|NumBits]);
1712
 
 complete1([{Unused,Bin}|T],Acc,Bacc) when integer(Unused),binary(Bin) ->
 
1777
 complete1([{Unused,Bin}|T],Acc,Bacc) when is_integer(Unused),is_binary(Bin) ->
1713
1778
     Size = size(Bin)-1,
1714
1779
     <<Bs:Size/binary,B>> = Bin,
1715
1780
     NumBits = 8 - Unused,
1738
1803
 
1739
1804
-else.
1740
1805
 
 
1806
%% asn1-1.6.8.1_dev
 
1807
%% complete(L) ->
 
1808
%%     case catch port_control(asn1_driver_port,1,L) of
 
1809
%%      Bin when is_binary(Bin) ->
 
1810
%%          Bin;
 
1811
%%      List when is_list(List) -> handle_error(List,L);
 
1812
%%      {'EXIT',{badarg,Reason}} ->
 
1813
%%          asn1rt_driver_handler:load_driver(),
 
1814
%%          receive
 
1815
%%              driver_ready ->
 
1816
%%                  case catch port_control(asn1_driver_port,1,L) of
 
1817
%%                      Bin2 when is_binary(Bin2) -> Bin2;
 
1818
%%                      List when is_list(List) -> handle_error(List,L);
 
1819
%%                      {'EXIT',Reason2={badarg,_R}} -> 
 
1820
%%                          exit({"failed to call driver probably due to bad asn1 value",Reason2});
 
1821
%%                      Reason2 -> exit(Reason2)
 
1822
%%                  end;
 
1823
%%              {error,Error} -> % error when loading driver
 
1824
%%                  %% the driver could not be loaded
 
1825
%%                  exit(Error);
 
1826
%%              Error={port_error,Reason} ->
 
1827
%%                  exit(Error)
 
1828
%%          end;
 
1829
%%      {'EXIT',Reason} ->
 
1830
%%          exit(Reason)
 
1831
%%     end.
 
1832
 
 
1833
%% asn1-1.6.9
1741
1834
complete(L) ->
1742
 
    case catch port_control(asn1_driver_port,1,L) of
1743
 
        Bin when binary(Bin) ->
1744
 
            Bin;
1745
 
        List when list(List) -> handle_error(List,L);
1746
 
        {'EXIT',{badarg,Reason}} ->
1747
 
            asn1rt_driver_handler:load_driver(),
1748
 
            receive
1749
 
                driver_ready ->
1750
 
                    case catch port_control(asn1_driver_port,1,L) of
1751
 
                        Bin2 when binary(Bin2) -> Bin2;
1752
 
                        List when list(List) -> handle_error(List,L);
1753
 
                        {'EXIT',Reason2={badarg,_R}} -> 
1754
 
                            exit({"failed to call driver probably due to bad asn1 value",Reason2});
1755
 
                        Reason2 -> exit(Reason2)
1756
 
                    end;
1757
 
                {error,Error} -> % error when loading driver
1758
 
                    %% the driver could not be loaded
1759
 
                    exit(Error);
1760
 
                Error={port_error,Reason} ->
1761
 
                    exit(Error)
1762
 
            end;
1763
 
        {'EXIT',Reason} ->
1764
 
            exit(Reason)
 
1835
    case catch control(?COMPLETE_ENCODE,L) of
 
1836
        Bin when is_binary(Bin) ->
 
1837
            Bin;
 
1838
        List when is_list(List) -> handle_error(List,L);
 
1839
        {'EXIT',{badarg,_Reason}} ->
 
1840
            case asn1rt:load_driver() of
 
1841
                ok ->
 
1842
                    case control(?COMPLETE_ENCODE,L) of
 
1843
                        Bin when is_binary(Bin) ->Bin;
 
1844
                        List when is_list(List) -> handle_error(List,L)
 
1845
                    end;
 
1846
                Err ->
 
1847
                    Err
 
1848
            end
1765
1849
    end.
1766
1850
 
1767
1851
 
1772
1856
handle_error(ErrL,L) ->
1773
1857
    exit({error,{asn1,ErrL,L}}).
1774
1858
 
 
1859
%% asn1-1.6.9
 
1860
control(Cmd, Data) ->
 
1861
    Port = asn1rt_driver_handler:client_port(),
 
1862
    erlang:port_control(Port, Cmd, Data).
 
1863
 
1775
1864
-endif.
1776
1865
 
1777
1866