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

« back to all changes in this revision

Viewing changes to lib/asn1/src/asn1rt_ber_bin.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>2000-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(asn1rt_ber_bin).
19
 
 
20
 
%% encoding / decoding of BER  
21
 
 
22
 
-export([decode/1]). 
 
21
 
 
22
%% encoding / decoding of BER
 
23
 
 
24
-export([decode/1]).
23
25
-export([fixoptionals/2,split_list/2,cindex/3,restbytes2/3,
24
26
         list_to_record/2,
25
27
         encode_tag_val/1,decode_tag/1,peek_tag/1,
28
30
         encode_integer/3,encode_integer/4,
29
31
         decode_integer/4,decode_integer/5,encode_enumerated/2,
30
32
         encode_enumerated/4,decode_enumerated/5,
31
 
         encode_real/2,decode_real/4,
 
33
         encode_real/2, encode_real/3,
 
34
         decode_real/2, decode_real/4,
32
35
         encode_bit_string/4,decode_bit_string/6,
33
36
         decode_compact_bit_string/6,
34
37
         encode_octet_string/3,decode_octet_string/5,
35
38
         encode_null/2,decode_null/3,
36
39
         encode_object_identifier/2,decode_object_identifier/3,
 
40
         encode_relative_oid/2,decode_relative_oid/3,
37
41
         encode_restricted_string/4,decode_restricted_string/6,
38
42
         encode_universal_string/3,decode_universal_string/5,
39
43
         encode_UTF8_string/3, decode_UTF8_string/3,
42
46
         encode_utc_time/3,decode_utc_time/5,
43
47
         encode_length/1,decode_length/1,
44
48
         check_if_valid_tag/3,
45
 
         decode_tag_and_length/1, decode_components/6, 
 
49
         decode_tag_and_length/1, decode_components/6,
46
50
         decode_components/7, decode_set/6]).
47
51
 
48
52
-export([encode_open_type/1,encode_open_type/2,decode_open_type/1,decode_open_type/2,decode_open_type/3]).
49
53
-export([skipvalue/1, skipvalue/2,skip_ExtensionAdditions/2]).
50
 
 
51
 
-include("asn1_records.hrl"). 
52
 
 
53
 
% the encoding of class of tag bits 8 and 7 
54
 
-define(UNIVERSAL,   0). 
55
 
-define(APPLICATION, 16#40). 
56
 
-define(CONTEXT,     16#80). 
57
 
-define(PRIVATE,     16#C0). 
58
 
 
59
 
%%% primitive or constructed encoding % bit 6 
60
 
-define(PRIMITIVE,   0). 
61
 
-define(CONSTRUCTED, 2#00100000). 
 
54
 
 
55
-include("asn1_records.hrl").
 
56
 
 
57
% the encoding of class of tag bits 8 and 7
 
58
-define(UNIVERSAL,   0).
 
59
-define(APPLICATION, 16#40).
 
60
-define(CONTEXT,     16#80).
 
61
-define(PRIVATE,     16#C0).
 
62
 
 
63
%%% primitive or constructed encoding % bit 6
 
64
-define(PRIMITIVE,   0).
 
65
-define(CONSTRUCTED, 2#00100000).
62
66
 
63
67
%%% The tag-number for universal types
64
 
-define(N_BOOLEAN, 1). 
65
 
-define(N_INTEGER, 2). 
 
68
-define(N_BOOLEAN, 1).
 
69
-define(N_INTEGER, 2).
66
70
-define(N_BIT_STRING, 3).
67
71
-define(N_OCTET_STRING, 4).
68
 
-define(N_NULL, 5). 
69
 
-define(N_OBJECT_IDENTIFIER, 6). 
70
 
-define(N_OBJECT_DESCRIPTOR, 7). 
71
 
-define(N_EXTERNAL, 8). 
72
 
-define(N_REAL, 9). 
73
 
-define(N_ENUMERATED, 10). 
74
 
-define(N_EMBEDDED_PDV, 11). 
 
72
-define(N_NULL, 5).
 
73
-define(N_OBJECT_IDENTIFIER, 6).
 
74
-define(N_OBJECT_DESCRIPTOR, 7).
 
75
-define(N_EXTERNAL, 8).
 
76
-define(N_REAL, 9).
 
77
-define(N_ENUMERATED, 10).
 
78
-define(N_EMBEDDED_PDV, 11).
75
79
-define(N_UTF8String, 12).
76
 
-define(N_SEQUENCE, 16). 
77
 
-define(N_SET, 17). 
 
80
-define('N_RELATIVE-OID',13).
 
81
-define(N_SEQUENCE, 16).
 
82
-define(N_SET, 17).
78
83
-define(N_NumericString, 18).
79
84
-define(N_PrintableString, 19).
80
85
-define(N_TeletexString, 20).
81
86
-define(N_VideotexString, 21).
82
87
-define(N_IA5String, 22).
83
 
-define(N_UTCTime, 23). 
84
 
-define(N_GeneralizedTime, 24). 
 
88
-define(N_UTCTime, 23).
 
89
-define(N_GeneralizedTime, 24).
85
90
-define(N_GraphicString, 25).
86
91
-define(N_VisibleString, 26).
87
92
-define(N_GeneralString, 27).
88
93
-define(N_UniversalString, 28).
89
94
-define(N_BMPString, 30).
90
95
 
91
 
 
92
 
% the complete tag-word of built-in types 
93
 
-define(T_BOOLEAN,          ?UNIVERSAL bor ?PRIMITIVE bor 1). 
94
 
-define(T_INTEGER,          ?UNIVERSAL bor ?PRIMITIVE bor 2). 
95
 
-define(T_BIT_STRING,       ?UNIVERSAL bor ?PRIMITIVE bor 3). % can be CONSTRUCTED 
96
 
-define(T_OCTET_STRING,     ?UNIVERSAL bor ?PRIMITIVE bor 4). % can be CONSTRUCTED 
97
 
-define(T_NULL,             ?UNIVERSAL bor ?PRIMITIVE bor 5). 
98
 
-define(T_OBJECT_IDENTIFIER,?UNIVERSAL bor ?PRIMITIVE bor 6). 
99
 
-define(T_OBJECT_DESCRIPTOR,?UNIVERSAL bor ?PRIMITIVE bor 7). 
100
 
-define(T_EXTERNAL,         ?UNIVERSAL bor ?PRIMITIVE bor 8). 
101
 
-define(T_REAL,             ?UNIVERSAL bor ?PRIMITIVE bor 9). 
102
 
-define(T_ENUMERATED,       ?UNIVERSAL bor ?PRIMITIVE bor 10). 
103
 
-define(T_EMBEDDED_PDV,     ?UNIVERSAL bor ?PRIMITIVE bor 11). 
104
 
-define(T_SEQUENCE,         ?UNIVERSAL bor ?CONSTRUCTED bor 16). 
105
 
-define(T_SET,              ?UNIVERSAL bor ?CONSTRUCTED bor 17). 
106
 
-define(T_NumericString,    ?UNIVERSAL bor ?PRIMITIVE bor 18). %can be constructed 
107
 
-define(T_PrintableString,  ?UNIVERSAL bor ?PRIMITIVE bor 19). %can be constructed 
108
 
-define(T_TeletexString,    ?UNIVERSAL bor ?PRIMITIVE bor 20). %can be constructed 
109
 
-define(T_VideotexString,   ?UNIVERSAL bor ?PRIMITIVE bor 21). %can be constructed 
110
 
-define(T_IA5String,        ?UNIVERSAL bor ?PRIMITIVE bor 22). %can be constructed 
111
 
-define(T_UTCTime,          ?UNIVERSAL bor ?PRIMITIVE bor 23). 
112
 
-define(T_GeneralizedTime,  ?UNIVERSAL bor ?PRIMITIVE bor 24). 
113
 
-define(T_GraphicString,    ?UNIVERSAL bor ?PRIMITIVE bor 25). %can be constructed 
114
 
-define(T_VisibleString,    ?UNIVERSAL bor ?PRIMITIVE bor 26). %can be constructed 
115
 
-define(T_GeneralString,    ?UNIVERSAL bor ?PRIMITIVE bor 27). %can be constructed 
116
 
-define(T_UniversalString,  ?UNIVERSAL bor ?PRIMITIVE bor 28). %can be constructed 
117
 
-define(T_BMPString,        ?UNIVERSAL bor ?PRIMITIVE bor 30). %can be constructed 
118
 
 
 
96
 
 
97
% the complete tag-word of built-in types
 
98
-define(T_BOOLEAN,          ?UNIVERSAL bor ?PRIMITIVE bor 1).
 
99
-define(T_INTEGER,          ?UNIVERSAL bor ?PRIMITIVE bor 2).
 
100
-define(T_BIT_STRING,       ?UNIVERSAL bor ?PRIMITIVE bor 3). % can be CONSTRUCTED
 
101
-define(T_OCTET_STRING,     ?UNIVERSAL bor ?PRIMITIVE bor 4). % can be CONSTRUCTED
 
102
-define(T_NULL,             ?UNIVERSAL bor ?PRIMITIVE bor 5).
 
103
-define(T_OBJECT_IDENTIFIER,?UNIVERSAL bor ?PRIMITIVE bor 6).
 
104
-define(T_OBJECT_DESCRIPTOR,?UNIVERSAL bor ?PRIMITIVE bor 7).
 
105
-define(T_EXTERNAL,         ?UNIVERSAL bor ?PRIMITIVE bor 8).
 
106
-define(T_REAL,             ?UNIVERSAL bor ?PRIMITIVE bor 9).
 
107
-define(T_ENUMERATED,       ?UNIVERSAL bor ?PRIMITIVE bor 10).
 
108
-define(T_EMBEDDED_PDV,     ?UNIVERSAL bor ?PRIMITIVE bor 11).
 
109
-define(T_SEQUENCE,         ?UNIVERSAL bor ?CONSTRUCTED bor 16).
 
110
-define(T_SET,              ?UNIVERSAL bor ?CONSTRUCTED bor 17).
 
111
-define(T_NumericString,    ?UNIVERSAL bor ?PRIMITIVE bor 18). %can be constructed
 
112
-define(T_PrintableString,  ?UNIVERSAL bor ?PRIMITIVE bor 19). %can be constructed
 
113
-define(T_TeletexString,    ?UNIVERSAL bor ?PRIMITIVE bor 20). %can be constructed
 
114
-define(T_VideotexString,   ?UNIVERSAL bor ?PRIMITIVE bor 21). %can be constructed
 
115
-define(T_IA5String,        ?UNIVERSAL bor ?PRIMITIVE bor 22). %can be constructed
 
116
-define(T_UTCTime,          ?UNIVERSAL bor ?PRIMITIVE bor 23).
 
117
-define(T_GeneralizedTime,  ?UNIVERSAL bor ?PRIMITIVE bor 24).
 
118
-define(T_GraphicString,    ?UNIVERSAL bor ?PRIMITIVE bor 25). %can be constructed
 
119
-define(T_VisibleString,    ?UNIVERSAL bor ?PRIMITIVE bor 26). %can be constructed
 
120
-define(T_GeneralString,    ?UNIVERSAL bor ?PRIMITIVE bor 27). %can be constructed
 
121
-define(T_UniversalString,  ?UNIVERSAL bor ?PRIMITIVE bor 28). %can be constructed
 
122
-define(T_BMPString,        ?UNIVERSAL bor ?PRIMITIVE bor 30). %can be constructed
 
123
 
119
124
 
120
125
decode(Bin) ->
121
126
    decode_primitive(Bin).
122
127
 
123
128
decode_primitive(Bin) ->
124
129
    {Tlv = {Tag,Len,V},<<>>} = decode_tlv(Bin),
125
 
    case element(2,Tag) of 
 
130
    case element(2,Tag) of
126
131
        ?CONSTRUCTED ->
127
132
            {Tag,Len,decode_constructed(V)};
128
133
        _ ->
134
139
decode_constructed(Bin) ->
135
140
    {Tlv = {Tag,Len,V},Rest} = decode_tlv(Bin),
136
141
    NewTlv =
137
 
        case element(2,Tag) of 
 
142
        case element(2,Tag) of
138
143
            ?CONSTRUCTED ->
139
144
                {Tag,Len,decode_constructed(V)};
140
145
            _ ->
141
146
                Tlv
142
147
        end,
143
148
    [NewTlv|decode_constructed(Rest)].
144
 
    
 
149
 
145
150
decode_tlv(Bin) ->
146
151
    {Tag,Bin1,_Rb1} = decode_tag(Bin),
147
152
    {{Len,Bin2},_Rb2} = decode_length(Bin1),
148
153
    <<V:Len/binary,Bin3/binary>> = Bin2,
149
154
    {{Tag,Len,V},Bin3}.
150
 
    
151
 
 
152
 
 
 
155
 
 
156
 
 
157
 
153
158
%%%%%%%%%%%%%
154
159
% split_list(List,HeadLen) -> {HeadList,TailList}
155
160
%
224
229
%%    end;
225
230
%%skipvalue(L, Bytes, Rb) ->
226
231
%%    {lists:nthtail(L,Bytes),Rb+L}.
227
 
    
 
232
 
228
233
skipvalue(Bytes) ->
229
234
    {_T,Bytes2,R2} = decode_tag(Bytes),
230
235
    {{L,Bytes3},R3} = decode_length(Bytes2),
231
236
    skipvalue(L,Bytes3,R2+R3).
232
 
        
233
 
 
234
 
cindex(Ix,Val,Cname) -> 
235
 
    case element(Ix,Val) of 
236
 
        {Cname,Val2} -> Val2; 
237
 
        X -> X 
238
 
    end. 
239
 
 
 
237
 
 
238
 
 
239
cindex(Ix,Val,Cname) ->
 
240
    case element(Ix,Val) of
 
241
        {Cname,Val2} -> Val2;
 
242
        X -> X
 
243
    end.
 
244
 
240
245
%%%
241
246
%% skips byte sequence of Bytes that do not match a tag in Tags
242
247
skip_ExtensionAdditions(Bytes,Tags) ->
257
262
                    {Bytes,RmB}
258
263
            end
259
264
    end.
260
 
                    
261
 
    
262
 
 
263
 
%%=============================================================================== 
264
 
%%=============================================================================== 
265
 
%%=============================================================================== 
266
 
%% Optionals, preset not filled optionals with asn1_NOVALUE 
267
 
%%=============================================================================== 
268
 
%%=============================================================================== 
269
 
%%=============================================================================== 
270
 
 
271
 
% converts a list to a record if necessary 
272
 
list_to_record(Name,List) when list(List) -> 
273
 
    list_to_tuple([Name|List]); 
274
 
list_to_record(_Name,Tuple) when tuple(Tuple) -> 
275
 
    Tuple. 
276
 
 
277
 
 
278
 
fixoptionals(OptList,Val) when list(Val) -> 
279
 
    fixoptionals(OptList,Val,1,[],[]). 
280
 
 
281
 
fixoptionals([{Name,Pos}|Ot],[{Name,Val}|Vt],_Opt,Acc1,Acc2) -> 
282
 
    fixoptionals(Ot,Vt,Pos+1,[1|Acc1],[{Name,Val}|Acc2]); 
283
 
fixoptionals([{_Name,Pos}|Ot],V,Pos,Acc1,Acc2) -> 
284
 
    fixoptionals(Ot,V,Pos+1,[0|Acc1],[asn1_NOVALUE|Acc2]); 
285
 
fixoptionals(O,[Vh|Vt],Pos,Acc1,Acc2) -> 
286
 
    fixoptionals(O,Vt,Pos+1,Acc1,[Vh|Acc2]); 
287
 
fixoptionals([],[Vh|Vt],Pos,Acc1,Acc2) -> 
288
 
    fixoptionals([],Vt,Pos+1,Acc1,[Vh|Acc2]); 
289
 
fixoptionals([],[],_,_Acc1,Acc2) -> 
290
 
    % return Val as a record 
 
265
 
 
266
 
 
267
 
 
268
%%===============================================================================
 
269
%%===============================================================================
 
270
%%===============================================================================
 
271
%% Optionals, preset not filled optionals with asn1_NOVALUE
 
272
%%===============================================================================
 
273
%%===============================================================================
 
274
%%===============================================================================
 
275
 
 
276
% converts a list to a record if necessary
 
277
list_to_record(Name,List) when list(List) ->
 
278
    list_to_tuple([Name|List]);
 
279
list_to_record(_Name,Tuple) when tuple(Tuple) ->
 
280
    Tuple.
 
281
 
 
282
 
 
283
fixoptionals(OptList,Val) when list(Val) ->
 
284
    fixoptionals(OptList,Val,1,[],[]).
 
285
 
 
286
fixoptionals([{Name,Pos}|Ot],[{Name,Val}|Vt],_Opt,Acc1,Acc2) ->
 
287
    fixoptionals(Ot,Vt,Pos+1,[1|Acc1],[{Name,Val}|Acc2]);
 
288
fixoptionals([{_Name,Pos}|Ot],V,Pos,Acc1,Acc2) ->
 
289
    fixoptionals(Ot,V,Pos+1,[0|Acc1],[asn1_NOVALUE|Acc2]);
 
290
fixoptionals(O,[Vh|Vt],Pos,Acc1,Acc2) ->
 
291
    fixoptionals(O,Vt,Pos+1,Acc1,[Vh|Acc2]);
 
292
fixoptionals([],[Vh|Vt],Pos,Acc1,Acc2) ->
 
293
    fixoptionals([],Vt,Pos+1,Acc1,[Vh|Acc2]);
 
294
fixoptionals([],[],_,_Acc1,Acc2) ->
 
295
    % return Val as a record
291
296
    list_to_tuple([asn1_RECORDNAME|lists:reverse(Acc2)]).
292
 
 
293
 
 
294
 
%%encode_tag(TagClass(?UNI, APP etc), Form (?PRIM etx), TagInteger) ->  
295
 
%%     8bit Int | binary 
296
 
encode_tag_val({Class, Form, TagNo}) when (TagNo =< 30) -> 
 
297
 
 
298
 
 
299
%%encode_tag(TagClass(?UNI, APP etc), Form (?PRIM etx), TagInteger) ->
 
300
%%     8bit Int | binary
 
301
encode_tag_val({Class, Form, TagNo}) when (TagNo =< 30) ->
297
302
    <<(Class bsr 6):2,(Form bsr 5):1,TagNo:5>>;
298
303
 
299
 
encode_tag_val({Class, Form, TagNo}) -> 
 
304
encode_tag_val({Class, Form, TagNo}) ->
300
305
    {Octets,_Len} = mk_object_val(TagNo),
301
306
    BinOct = list_to_binary(Octets),
302
 
    <<(Class bsr 6):2, (Form bsr 5):1, 31:5,BinOct/binary>>; 
303
 
 
304
 
%% asumes whole correct tag bitpattern, multiple of 8 
 
307
    <<(Class bsr 6):2, (Form bsr 5):1, 31:5,BinOct/binary>>;
 
308
 
 
309
%% asumes whole correct tag bitpattern, multiple of 8
305
310
encode_tag_val(Tag) when (Tag =< 255) -> Tag;  %% anv�nds denna funktion??!!
306
 
%% asumes correct bitpattern of 0-5 
307
 
encode_tag_val(Tag) -> encode_tag_val2(Tag,[]). 
308
 
 
309
 
encode_tag_val2(Tag, OctAck) when (Tag =< 255) -> 
310
 
    [Tag | OctAck]; 
311
 
encode_tag_val2(Tag, OctAck) -> 
312
 
    encode_tag_val2(Tag bsr 8, [255 band Tag | OctAck]). 
313
 
 
314
 
 
315
 
%%%encode_tag(TagClass(?UNI, APP etc), Form (?PRIM etx), TagInteger) ->  
316
 
%%%     8bit Int | [list of octets] 
317
 
%encode_tag_val({Class, Form, TagNo}) when (TagNo =< 30) -> 
 
311
%% asumes correct bitpattern of 0-5
 
312
encode_tag_val(Tag) -> encode_tag_val2(Tag,[]).
 
313
 
 
314
encode_tag_val2(Tag, OctAck) when (Tag =< 255) ->
 
315
    [Tag | OctAck];
 
316
encode_tag_val2(Tag, OctAck) ->
 
317
    encode_tag_val2(Tag bsr 8, [255 band Tag | OctAck]).
 
318
 
 
319
 
 
320
%%%encode_tag(TagClass(?UNI, APP etc), Form (?PRIM etx), TagInteger) ->
 
321
%%%     8bit Int | [list of octets]
 
322
%encode_tag_val({Class, Form, TagNo}) when (TagNo =< 30) ->
318
323
%%%    <<Class:2,Form:1,TagNo:5>>;
319
 
%    [Class bor Form bor TagNo]; 
320
 
%encode_tag_val({Class, Form, TagNo}) -> 
 
324
%    [Class bor Form bor TagNo];
 
325
%encode_tag_val({Class, Form, TagNo}) ->
321
326
%    {Octets,L} = mk_object_val(TagNo),
322
 
%    [Class bor Form bor 31 | Octets]; 
 
327
%    [Class bor Form bor 31 | Octets];
323
328
 
324
329
 
325
330
%%============================================================================\%% Peek on the initial tag
340
345
peek_tag(<<PartialTag,Buffer/binary>>, TagAck) ->
341
346
    peek_tag(Buffer,<<TagAck/binary,PartialTag>>);
342
347
peek_tag(_,TagAck) ->
343
 
    exit({error,{asn1, {invalid_tag,TagAck}}}). 
344
 
%%peek_tag([Tag|Buffer]) when (Tag band 31) == 31 -> 
 
348
    exit({error,{asn1, {invalid_tag,TagAck}}}).
 
349
%%peek_tag([Tag|Buffer]) when (Tag band 31) == 31 ->
345
350
%%    [Tag band 2#11011111 | peek_tag(Buffer,[])];
346
351
%%%% single tag (tagno < 31)
347
352
%%peek_tag([Tag|Buffer]) ->
352
357
%%peek_tag([PartialTag|Buffer], TagAck) ->
353
358
%%    peek_tag(Buffer,[PartialTag|TagAck]);
354
359
%%peek_tag(Buffer,TagAck) ->
355
 
%%    exit({error,{asn1, {invalid_tag,lists:reverse(TagAck)}}}). 
356
 
  
357
 
 
358
 
%%=============================================================================== 
359
 
%% Decode a tag 
360
 
%% 
361
 
%% decode_tag(OctetListBuffer) -> {{Class, Form, TagNo}, RestOfBuffer, RemovedBytes} 
362
 
%%=============================================================================== 
363
 
 
364
 
%% multiple octet tag 
 
360
%%    exit({error,{asn1, {invalid_tag,lists:reverse(TagAck)}}}).
 
361
 
 
362
 
 
363
%%===============================================================================
 
364
%% Decode a tag
 
365
%%
 
366
%% decode_tag(OctetListBuffer) -> {{Class, Form, TagNo}, RestOfBuffer, RemovedBytes}
 
367
%%===============================================================================
 
368
 
 
369
%% multiple octet tag
365
370
decode_tag(<<Class:2, Form:1, 31:5, Buffer/binary>>) ->
366
371
    {TagNo, Buffer1, RemovedBytes} = decode_tag(Buffer, 0, 1),
367
372
    {{(Class bsl 6), (Form bsl 5), TagNo}, Buffer1, RemovedBytes};
368
373
 
369
374
%% single tag (< 31 tags)
370
 
decode_tag(<<Class:2,Form:1,TagNo:5, Buffer/binary>>) -> 
 
375
decode_tag(<<Class:2,Form:1,TagNo:5, Buffer/binary>>) ->
371
376
    {{(Class bsl 6), (Form bsl 5), TagNo}, Buffer, 1}.
372
 
     
373
 
%% last partial tag 
 
377
 
 
378
%% last partial tag
374
379
decode_tag(<<0:1,PartialTag:7, Buffer/binary>>, TagAck, RemovedBytes) ->
375
380
    TagNo = (TagAck bsl 7) bor PartialTag,
376
381
    %%<<TagNo>> = <<TagAck:1, PartialTag:7>>,
377
 
    {TagNo, Buffer, RemovedBytes+1}; 
378
 
% more tags 
379
 
decode_tag(<<_:1,PartialTag:7, Buffer/binary>>, TagAck, RemovedBytes) -> 
380
 
    TagAck1 = (TagAck bsl 7) bor PartialTag, 
 
382
    {TagNo, Buffer, RemovedBytes+1};
 
383
% more tags
 
384
decode_tag(<<_:1,PartialTag:7, Buffer/binary>>, TagAck, RemovedBytes) ->
 
385
    TagAck1 = (TagAck bsl 7) bor PartialTag,
381
386
    %%<<TagAck1:16>> = <<TagAck:1, PartialTag:7,0:8>>,
382
 
    decode_tag(Buffer, TagAck1, RemovedBytes+1). 
383
 
 
 
387
    decode_tag(Buffer, TagAck1, RemovedBytes+1).
 
388
 
384
389
%%------------------------------------------------------------------
385
390
%% check_tags_i is the same as check_tags except that it stops and
386
391
%% returns the remaining tags not checked when it encounters an
387
 
%% indefinite length field 
 
392
%% indefinite length field
388
393
%% only called internally within this module
389
394
 
390
395
check_tags_i([Tag], Buffer, OptOrMand) -> % optimized very usual case
392
397
check_tags_i(Tags, Buffer, OptOrMand) ->
393
398
    check_tags_i(Tags, Buffer, 0, OptOrMand).
394
399
 
395
 
check_tags_i([Tag1,Tag2|TagRest], Buffer, Rb, OptOrMand) 
 
400
check_tags_i([Tag1,Tag2|TagRest], Buffer, Rb, OptOrMand)
396
401
  when Tag1#tag.type == 'IMPLICIT' ->
397
402
    check_tags_i([Tag1#tag{type=Tag2#tag.type}|TagRest], Buffer, Rb, OptOrMand);
398
403
 
400
405
    {Form_Length,Buffer2,Rb1} = check_one_tag(Tag1, Buffer, OptOrMand),
401
406
    case TagRest of
402
407
        [] -> {TagRest, {Form_Length, Buffer2, Rb + Rb1}};
403
 
        _ -> 
 
408
        _ ->
404
409
            case Form_Length of
405
410
                {?CONSTRUCTED,_} ->
406
411
                    {TagRest, {Form_Length, Buffer2, Rb + Rb1}};
407
 
                _ -> 
 
412
                _ ->
408
413
                    check_tags_i(TagRest, Buffer2, Rb + Rb1, mandatory)
409
414
            end
410
415
    end;
420
425
check_tags(Tags, Buffer, OptOrMand) ->
421
426
    check_tags(Tags, Buffer, 0, OptOrMand).
422
427
 
423
 
check_tags([Tag1,Tag2|TagRest], Buffer, Rb, OptOrMand) 
 
428
check_tags([Tag1,Tag2|TagRest], Buffer, Rb, OptOrMand)
424
429
  when Tag1#tag.type == 'IMPLICIT' ->
425
430
    check_tags([Tag1#tag{type=Tag2#tag.type}|TagRest], Buffer, Rb, OptOrMand);
426
431
 
436
441
 
437
442
check_one_tag(Tag=#tag{class=ExpectedClass,number=ExpectedNumber}, Buffer, OptOrMand) ->
438
443
    case catch decode_tag(Buffer) of
439
 
        {'EXIT',_Reason} -> 
 
444
        {'EXIT',_Reason} ->
440
445
            tag_error(no_data,Tag,Buffer,OptOrMand);
441
446
        {{ExpectedClass,Form,ExpectedNumber},Buffer2,Rb} ->
442
447
            {{L,Buffer3},RemBytes2} = decode_length(Buffer2),
444
449
        {ErrorTag,_,_} ->
445
450
            tag_error(ErrorTag, Tag, Buffer, OptOrMand)
446
451
    end.
447
 
            
 
452
 
448
453
tag_error(ErrorTag, Tag, Buffer, OptOrMand) ->
449
454
    case OptOrMand of
450
455
        mandatory ->
451
 
            exit({error,{asn1, {invalid_tag, 
 
456
            exit({error,{asn1, {invalid_tag,
452
457
                                {ErrorTag, Tag, Buffer}}}});
453
458
        _ ->
454
 
            exit({error,{asn1, {no_optional_tag, 
 
459
            exit({error,{asn1, {no_optional_tag,
455
460
                                {ErrorTag, Tag, Buffer}}}})
456
 
    end.    
 
461
    end.
457
462
%%=======================================================================
458
463
%%
459
464
%% Encode all tags in the list Tags and return a possibly deep list of
461
466
%%
462
467
%% prepend_tags(Tags, BytesSoFar, LenSoFar) -> {Bytes, Len}
463
468
encode_tags(Tags, BytesSoFar, LenSoFar) ->
464
 
    NewTags = encode_tags1(Tags, []), 
 
469
    NewTags = encode_tags1(Tags, []),
465
470
    %% NewTags contains the resulting tags in reverse order
466
471
    encode_tags2(NewTags, BytesSoFar, LenSoFar).
467
472
 
471
476
encode_tags2([Tag|Trest], BytesSoFar, LenSoFar) ->
472
477
    {Bytes1,L1} = encode_one_tag(Tag),
473
478
    {Bytes2,L2} = encode_length(LenSoFar),
474
 
    encode_tags2(Trest, [Bytes1,Bytes2|BytesSoFar], 
 
479
    encode_tags2(Trest, [Bytes1,Bytes2|BytesSoFar],
475
480
                 LenSoFar + L1 + L2);
476
481
encode_tags2([], BytesSoFar, LenSoFar) ->
477
482
    {BytesSoFar,LenSoFar}.
478
483
 
479
 
encode_tags1([Tag1, Tag2| Trest], Acc) 
 
484
encode_tags1([Tag1, Tag2| Trest], Acc)
480
485
  when Tag1#tag.type == 'IMPLICIT' ->
481
486
    encode_tags1([Tag1#tag{type=Tag2#tag.type,form=Tag2#tag.form}|Trest],Acc);
482
 
encode_tags1([Tag1 | Trest], Acc) -> 
 
487
encode_tags1([Tag1 | Trest], Acc) ->
483
488
    encode_tags1(Trest, [Tag1|Acc]);
484
489
encode_tags1([], Acc) ->
485
490
    Acc. % the resulting tags are returned in reverse order
486
491
 
487
492
encode_one_tag(Bin) when binary(Bin) ->
488
493
    {Bin,size(Bin)};
489
 
encode_one_tag(#tag{class=Class,number=No,type=Type, form = Form}) ->                     
 
494
encode_one_tag(#tag{class=Class,number=No,type=Type, form = Form}) ->
490
495
    NewForm = case Type of
491
496
               'EXPLICIT' ->
492
497
                   ?CONSTRUCTED;
495
500
           end,
496
501
    Bytes = encode_tag_val({Class,NewForm,No}),
497
502
    {Bytes,size(Bytes)}.
498
 
   
499
 
%%=============================================================================== 
500
 
%% Change the tag (used when an implicit tagged type has a reference to something else) 
 
503
 
 
504
%%===============================================================================
 
505
%% Change the tag (used when an implicit tagged type has a reference to something else)
501
506
%% The constructed bit in the tag is taken from the tag to be replaced.
502
 
%% 
503
 
%% change_tag(NewTag,[Tag,Buffer]) -> [NewTag,Buffer] 
504
 
%%=============================================================================== 
505
 
 
 
507
%%
 
508
%% change_tag(NewTag,[Tag,Buffer]) -> [NewTag,Buffer]
 
509
%%===============================================================================
 
510
 
506
511
%change_tag({NewClass,NewTagNr}, Buffer) ->
507
512
%    {{OldClass, OldForm, OldTagNo}, Buffer1, RemovedBytes} = decode_tag(lists:flatten(Buffer)),
508
513
%    [encode_tag_val({NewClass, OldForm, NewTagNr}) | Buffer1].
509
 
    
510
 
  
511
 
 
512
 
 
513
 
 
514
 
 
515
 
 
516
 
%%=============================================================================== 
517
 
%% 
518
 
%% This comment is valid for all the encode/decode functions 
519
 
%% 
520
 
%% C = Constraint -> typically {'ValueRange',LowerBound,UpperBound} 
521
 
%%     used for PER-coding but not for BER-coding. 
522
 
%% 
523
 
%% Val = Value.  If Val is an atom then it is a symbolic integer value  
524
 
%%       (i.e the atom must be one of the names in the NamedNumberList). 
525
 
%%       The NamedNumberList is used to translate the atom to an integer value 
526
 
%%       before encoding. 
527
 
%% 
528
 
%%=============================================================================== 
529
 
 
 
514
 
 
515
 
 
516
 
 
517
 
 
518
 
 
519
 
 
520
 
 
521
%%===============================================================================
 
522
%%
 
523
%% This comment is valid for all the encode/decode functions
 
524
%%
 
525
%% C = Constraint -> typically {'ValueRange',LowerBound,UpperBound}
 
526
%%     used for PER-coding but not for BER-coding.
 
527
%%
 
528
%% Val = Value.  If Val is an atom then it is a symbolic integer value
 
529
%%       (i.e the atom must be one of the names in the NamedNumberList).
 
530
%%       The NamedNumberList is used to translate the atom to an integer value
 
531
%%       before encoding.
 
532
%%
 
533
%%===============================================================================
 
534
 
530
535
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
531
536
%% encode_open_type(Value) -> CompleteList
532
537
%% Value = list of bytes of an already encoded value (the list must be flat)
533
538
%%         | binary
534
539
 
535
 
%% This version does not consider Explicit tagging of the open type. It 
 
540
%% This version does not consider Explicit tagging of the open type. It
536
541
%% is only left because of backward compatibility.
537
 
encode_open_type(Val) when list(Val) -> 
 
542
encode_open_type(Val) when list(Val) ->
538
543
    {Val,size(list_to_binary(Val))};
539
544
encode_open_type(Val) ->
540
 
    {Val, size(Val)}. 
 
545
    {Val, size(Val)}.
541
546
 
542
 
%% 
543
 
encode_open_type(Val, []) when list(Val) -> 
 
547
%%
 
548
encode_open_type(Val, []) when list(Val) ->
544
549
    {Val,size(list_to_binary(Val))};
545
550
encode_open_type(Val,[]) ->
546
551
    {Val, size(Val)};
547
 
encode_open_type(Val, Tag) when list(Val) -> 
 
552
encode_open_type(Val, Tag) when list(Val) ->
548
553
    encode_tags(Tag,Val,size(list_to_binary(Val)));
549
554
encode_open_type(Val,Tag) ->
550
 
    encode_tags(Tag,Val, size(Val)). 
 
555
    encode_tags(Tag,Val, size(Val)).
551
556
 
552
557
 
553
558
 
554
559
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
555
560
%% decode_open_type(Buffer) -> Value
556
 
%% Bytes = [byte] with BER encoded data 
 
561
%% Bytes = [byte] with BER encoded data
557
562
%% Value = [byte] with decoded data (which must be decoded again as some type)
558
563
%%
559
564
decode_open_type(Bytes) ->
560
565
%    {_Tag, Len, _RemainingBuffer, RemovedBytes} = decode_tag_and_length(Bytes),
561
566
%    N = Len + RemovedBytes,
562
567
    {_Tag, Len, RemainingBuffer, RemovedBytes} = decode_tag_and_length(Bytes),
563
 
    {_RemainingBuffer2, RemovedBytes2} = skipvalue(Len, RemainingBuffer, RemovedBytes), 
 
568
    {_RemainingBuffer2, RemovedBytes2} = skipvalue(Len, RemainingBuffer, RemovedBytes),
564
569
    N = RemovedBytes2,
565
570
    <<Val:N/binary, RemainingBytes/binary>> = Bytes,
566
571
%    {Val, RemainingBytes, Len + RemovedBytes}.
578
583
%           <<_:RemovedBytes/unit:8,Val:N/binary,RemainingBytes/binary>> = Bytes,
579
584
%           {Val, RemainingBytes, N + RemovedBytes};
580
585
        {{Class,Form,No},[#tag{class=Class,number=No,form=Form}]} ->
581
 
            {_RemainingBuffer2, RemovedBytes2} = 
 
586
            {_RemainingBuffer2, RemovedBytes2} =
582
587
                skipvalue(Len, RemainingBuffer),
583
588
            N = RemovedBytes2,
584
589
            <<_:RemovedBytes/unit:8,Val:N/binary,RemainingBytes/binary>> = Bytes,
585
590
            {Val, RemainingBytes, N + RemovedBytes};
586
591
        _ ->
587
 
            {_RemainingBuffer2, RemovedBytes2} = 
 
592
            {_RemainingBuffer2, RemovedBytes2} =
588
593
                skipvalue(Len, RemainingBuffer, RemovedBytes),
589
594
            N = RemovedBytes2,
590
595
            <<Val:N/binary, RemainingBytes/binary>> = Bytes,
591
596
            {Val, RemainingBytes, N}
592
597
    end.
593
 
 
 
598
 
594
599
decode_open_type(ber_bin,Bytes,ExplTag) ->
595
600
    decode_open_type(Bytes,ExplTag);
596
601
decode_open_type(ber,Bytes,ExplTag) ->
597
602
    {Val,RemBytes,Len}=decode_open_type(Bytes,ExplTag),
598
603
    {binary_to_list(Val),RemBytes,Len}.
599
 
 
600
 
%%=============================================================================== 
601
 
%%=============================================================================== 
602
 
%%=============================================================================== 
603
 
%% Boolean, ITU_T X.690 Chapter 8.2 
604
 
%%=============================================================================== 
605
 
%%=============================================================================== 
606
 
%%=============================================================================== 
607
 
 
608
 
%%=============================================================================== 
609
 
%% encode_boolean(Integer, tag | notag) -> [octet list] 
610
 
%%=============================================================================== 
611
 
 
612
 
encode_boolean({Name, Val}, DoTag) when atom(Name) -> 
613
 
    dotag(DoTag, ?N_BOOLEAN, encode_boolean(Val)); 
 
604
 
 
605
%%===============================================================================
 
606
%%===============================================================================
 
607
%%===============================================================================
 
608
%% Boolean, ITU_T X.690 Chapter 8.2
 
609
%%===============================================================================
 
610
%%===============================================================================
 
611
%%===============================================================================
 
612
 
 
613
%%===============================================================================
 
614
%% encode_boolean(Integer, tag | notag) -> [octet list]
 
615
%%===============================================================================
 
616
 
 
617
encode_boolean({Name, Val}, DoTag) when atom(Name) ->
 
618
    dotag(DoTag, ?N_BOOLEAN, encode_boolean(Val));
614
619
encode_boolean(true,[]) ->
615
620
    {[1,1,16#FF],3};
616
621
encode_boolean(false,[]) ->
617
622
    {[1,1,0],3};
618
 
encode_boolean(Val, DoTag) -> 
619
 
    dotag(DoTag, ?N_BOOLEAN, encode_boolean(Val)). 
620
 
 
621
 
%% encode_boolean(Boolean) -> [Len, Boolean] = [1, $FF | 0] 
622
 
encode_boolean(true)   ->    {[16#FF],1}; 
623
 
encode_boolean(false)  ->    {[0],1}; 
624
 
encode_boolean(X) -> exit({error,{asn1, {encode_boolean, X}}}). 
625
 
 
626
 
 
627
 
%%=============================================================================== 
628
 
%% decode_boolean(BuffList, HasTag, TotalLen) -> {true, Remain, RemovedBytes} |  
629
 
%%                                               {false, Remain, RemovedBytes} 
630
 
%%=============================================================================== 
631
 
 
 
623
encode_boolean(Val, DoTag) ->
 
624
    dotag(DoTag, ?N_BOOLEAN, encode_boolean(Val)).
 
625
 
 
626
%% encode_boolean(Boolean) -> [Len, Boolean] = [1, $FF | 0]
 
627
encode_boolean(true)   ->    {[16#FF],1};
 
628
encode_boolean(false)  ->    {[0],1};
 
629
encode_boolean(X) -> exit({error,{asn1, {encode_boolean, X}}}).
 
630
 
 
631
 
 
632
%%===============================================================================
 
633
%% decode_boolean(BuffList, HasTag, TotalLen) -> {true, Remain, RemovedBytes} |
 
634
%%                                               {false, Remain, RemovedBytes}
 
635
%%===============================================================================
 
636
 
632
637
decode_boolean(Buffer, Tags, OptOrMand) ->
633
638
    NewTags = new_tags(Tags,#tag{class=?UNIVERSAL,number=?N_BOOLEAN}),
634
639
    decode_boolean_notag(Buffer, NewTags, OptOrMand).
635
640
 
636
 
decode_boolean_notag(Buffer, Tags, OptOrMand) -> 
637
 
    {RestTags, {FormLen,Buffer0,Rb0}} = 
 
641
decode_boolean_notag(Buffer, Tags, OptOrMand) ->
 
642
    {RestTags, {FormLen,Buffer0,Rb0}} =
638
643
        check_tags_i(Tags, Buffer, OptOrMand),
639
644
    case FormLen of
640
645
        {?CONSTRUCTED,Len} ->
645
650
        {_,_} ->
646
651
            decode_boolean2(Buffer0, Rb0)
647
652
    end.
648
 
 
 
653
 
649
654
decode_boolean2(<<0:8, Buffer/binary>>, RemovedBytes) ->
650
655
    {false, Buffer, RemovedBytes + 1};
651
656
decode_boolean2(<<_:8, Buffer/binary>>, RemovedBytes) ->
652
657
    {true, Buffer, RemovedBytes + 1};
653
 
decode_boolean2(Buffer, _) ->  
654
 
    exit({error,{asn1, {decode_boolean, Buffer}}}). 
655
 
 
656
 
  
657
 
 
658
 
 
659
 
%%=========================================================================== 
660
 
%% Integer, ITU_T X.690 Chapter 8.3 
661
 
 
662
 
%% encode_integer(Constraint, Value, Tag) -> [octet list] 
663
 
%% encode_integer(Constraint, Name, NamedNumberList, Tag) -> [octet list] 
664
 
%%    Value = INTEGER | {Name,INTEGER}  
665
 
%%    Tag = tag | notag 
666
 
%%=========================================================================== 
667
 
 
668
 
encode_integer(C, Val, []) when integer(Val) -> 
 
658
decode_boolean2(Buffer, _) ->
 
659
    exit({error,{asn1, {decode_boolean, Buffer}}}).
 
660
 
 
661
 
 
662
 
 
663
 
 
664
%%===========================================================================
 
665
%% Integer, ITU_T X.690 Chapter 8.3
 
666
 
 
667
%% encode_integer(Constraint, Value, Tag) -> [octet list]
 
668
%% encode_integer(Constraint, Name, NamedNumberList, Tag) -> [octet list]
 
669
%%    Value = INTEGER | {Name,INTEGER}
 
670
%%    Tag = tag | notag
 
671
%%===========================================================================
 
672
 
 
673
encode_integer(C, Val, []) when integer(Val) ->
669
674
    {EncVal,Len}=encode_integer(C, Val),
670
675
    dotag_universal(?N_INTEGER,EncVal,Len);
671
 
encode_integer(C, Val, Tag) when integer(Val) -> 
 
676
encode_integer(C, Val, Tag) when integer(Val) ->
672
677
    dotag(Tag, ?N_INTEGER, encode_integer(C, Val));
673
678
encode_integer(C,{Name,Val},Tag) when atom(Name) ->
674
679
    encode_integer(C,Val,Tag);
675
 
encode_integer(_, Val, _) -> 
676
 
    exit({error,{asn1, {encode_integer, Val}}}). 
677
 
 
678
 
 
679
 
 
680
 
encode_integer(C, Val, NamedNumberList, Tag) when atom(Val) -> 
681
 
    case lists:keysearch(Val, 1, NamedNumberList) of 
682
 
        {value,{_, NewVal}} ->  
683
 
            dotag(Tag, ?N_INTEGER, encode_integer(C, NewVal)); 
684
 
        _ ->  
685
 
            exit({error,{asn1, {encode_integer_namednumber, Val}}}) 
686
 
    end; 
 
680
encode_integer(_, Val, _) ->
 
681
    exit({error,{asn1, {encode_integer, Val}}}).
 
682
 
 
683
 
 
684
 
 
685
encode_integer(C, Val, NamedNumberList, Tag) when atom(Val) ->
 
686
    case lists:keysearch(Val, 1, NamedNumberList) of
 
687
        {value,{_, NewVal}} ->
 
688
            dotag(Tag, ?N_INTEGER, encode_integer(C, NewVal));
 
689
        _ ->
 
690
            exit({error,{asn1, {encode_integer_namednumber, Val}}})
 
691
    end;
687
692
encode_integer(C,{_,Val},NamedNumberList,Tag) ->
688
 
    encode_integer(C,Val,NamedNumberList,Tag); 
689
 
encode_integer(C, Val, _NamedNumberList, Tag) -> 
690
 
    dotag(Tag, ?N_INTEGER, encode_integer(C, Val)). 
691
 
 
692
 
 
693
 
 
694
 
 
695
 
encode_integer(_C, Val) -> 
696
 
    Bytes =  
697
 
        if  
698
 
            Val >= 0 -> 
699
 
                encode_integer_pos(Val, []); 
700
 
            true -> 
701
 
                encode_integer_neg(Val, []) 
702
 
        end, 
703
 
    {Bytes,length(Bytes)}. 
704
 
 
 
693
    encode_integer(C,Val,NamedNumberList,Tag);
 
694
encode_integer(C, Val, _NamedNumberList, Tag) ->
 
695
    dotag(Tag, ?N_INTEGER, encode_integer(C, Val)).
 
696
 
 
697
 
 
698
 
 
699
 
 
700
encode_integer(_C, Val) ->
 
701
    Bytes =
 
702
        if
 
703
            Val >= 0 ->
 
704
                encode_integer_pos(Val, []);
 
705
            true ->
 
706
                encode_integer_neg(Val, [])
 
707
        end,
 
708
    {Bytes,length(Bytes)}.
 
709
 
705
710
encode_integer_pos(0, L=[B|_Acc]) when B < 128 ->
706
711
    L;
707
712
encode_integer_pos(N, Acc) ->
712
717
encode_integer_neg(N, Acc) ->
713
718
    encode_integer_neg(N bsr 8, [N band 16#ff|Acc]).
714
719
 
715
 
%%=============================================================================== 
716
 
%% decode integer  
717
 
%%    (Buffer, Range, HasTag, TotalLen) -> {Integer, Remain, RemovedBytes}  
718
 
%%    (Buffer, Range, NamedNumberList, HasTag, TotalLen) -> {Integer, Remain, RemovedBytes}  
719
 
%%=============================================================================== 
720
 
 
721
 
 
 
720
%%===============================================================================
 
721
%% decode integer
 
722
%%    (Buffer, Range, HasTag, TotalLen) -> {Integer, Remain, RemovedBytes}
 
723
%%    (Buffer, Range, NamedNumberList, HasTag, TotalLen) -> {Integer, Remain, RemovedBytes}
 
724
%%===============================================================================
 
725
 
 
726
 
722
727
decode_integer(Buffer, Range, Tags, OptOrMand) ->
723
728
    NewTags = new_tags(Tags,#tag{class=?UNIVERSAL,number=?N_INTEGER}),
724
729
    decode_integer_notag(Buffer, Range, [], NewTags, OptOrMand).
725
 
 
726
 
decode_integer(Buffer, Range, NamedNumberList, Tags, OptOrMand) -> 
 
730
 
 
731
decode_integer(Buffer, Range, NamedNumberList, Tags, OptOrMand) ->
727
732
    NewTags = new_tags(Tags,#tag{class=?UNIVERSAL,number=?N_INTEGER}),
728
733
    decode_integer_notag(Buffer, Range, NamedNumberList, NewTags, OptOrMand).
729
734
 
730
735
decode_integer_notag(Buffer, Range, NamedNumberList, NewTags, OptOrMand) ->
731
 
    {RestTags, {FormLen, Buffer0, Rb0}} = 
 
736
    {RestTags, {FormLen, Buffer0, Rb0}} =
732
737
        check_tags_i(NewTags, Buffer, OptOrMand),
733
738
%    Result = {Val, Buffer2, RemovedBytes} =
734
739
        case FormLen of
735
740
            {?CONSTRUCTED,Len} ->
736
741
                {Buffer00, RestBytes} = split_list(Buffer0,Len),
737
 
                {Val01, Buffer01, Rb01} = 
738
 
                    decode_integer_notag(Buffer00, Range, NamedNumberList, 
 
742
                {Val01, Buffer01, Rb01} =
 
743
                    decode_integer_notag(Buffer00, Range, NamedNumberList,
739
744
                                         RestTags, OptOrMand),
740
745
                {Buffer02, Rb02} = restbytes2(RestBytes,Buffer01,noext),
741
746
                {Val01, Buffer02, Rb0+Rb01+Rb02};
745
750
                Result2 = check_integer_constraint(Result,Range),
746
751
                resolve_named_value(Result2,NamedNumberList)
747
752
        end.
748
 
 
 
753
 
749
754
resolve_named_value(Result={Val,Buffer,RemBytes},NamedNumberList) ->
750
755
    case NamedNumberList of
751
756
        [] -> Result;
752
757
        _ ->
753
 
            NewVal = case lists:keysearch(Val, 2, NamedNumberList) of 
754
 
                         {value,{NamedVal, _}} -> 
755
 
                             NamedVal; 
756
 
                         _ -> 
757
 
                             Val 
758
 
                     end, 
 
758
            NewVal = case lists:keysearch(Val, 2, NamedNumberList) of
 
759
                         {value,{NamedVal, _}} ->
 
760
                             NamedVal;
 
761
                         _ ->
 
762
                             Val
 
763
                     end,
759
764
            {NewVal, Buffer, RemBytes}
760
765
    end.
761
 
    
 
766
 
762
767
check_integer_constraint(Result={Val, _Buffer,_},Range) ->
763
768
    case Range of
764
769
        [] -> % No length constraint
767
772
            Result;
768
773
        Val -> % fixed value constraint
769
774
            Result;
770
 
        {_,_} -> 
 
775
        {_,_} ->
771
776
            exit({error,{asn1,{integer_range,Range,Val}}});
772
777
        SingleValue when integer(SingleValue) ->
773
778
            exit({error,{asn1,{integer_range,Range,Val}}});
775
780
            Result
776
781
    end.
777
782
 
778
 
%%============================================================================ 
779
 
%% Enumerated value, ITU_T X.690 Chapter 8.4 
 
783
%%============================================================================
 
784
%% Enumerated value, ITU_T X.690 Chapter 8.4
780
785
 
781
 
%% encode enumerated value 
782
 
%%============================================================================ 
 
786
%% encode enumerated value
 
787
%%============================================================================
783
788
encode_enumerated(Val, []) when integer(Val)->
784
789
    {EncVal,Len} = encode_integer(false,Val),
785
790
    dotag_universal(?N_ENUMERATED,EncVal,Len);
797
802
        {'EXIT',_} -> encode_enumerated(C, Val, ExtList, DoTag);
798
803
        Result -> Result
799
804
    end;
800
 
 
801
 
encode_enumerated(C, Val, NamedNumberList, DoTag) when atom(Val) -> 
802
 
    case lists:keysearch(Val, 1, NamedNumberList) of 
 
805
 
 
806
encode_enumerated(C, Val, NamedNumberList, DoTag) when atom(Val) ->
 
807
    case lists:keysearch(Val, 1, NamedNumberList) of
803
808
        {value, {_, NewVal}} when DoTag == []->
804
809
            {EncVal,Len} = encode_integer(C,NewVal),
805
810
            dotag_universal(?N_ENUMERATED,EncVal,Len);
806
811
        {value, {_, NewVal}} ->
807
 
            dotag(DoTag, ?N_ENUMERATED, encode_integer(C, NewVal)); 
808
 
        _ -> 
809
 
            exit({error,{asn1, {enumerated_not_in_range, Val}}}) 
810
 
    end; 
 
812
            dotag(DoTag, ?N_ENUMERATED, encode_integer(C, NewVal));
 
813
        _ ->
 
814
            exit({error,{asn1, {enumerated_not_in_range, Val}}})
 
815
    end;
811
816
 
812
817
encode_enumerated(C, {asn1_enum, Val}, {_,_}, DoTag) when integer(Val) ->
813
818
    dotag(DoTag, ?N_ENUMERATED, encode_integer(C,Val));
814
819
 
815
 
encode_enumerated(C, {Name,Val}, NamedNumberList, DoTag) when atom(Name) -> 
 
820
encode_enumerated(C, {Name,Val}, NamedNumberList, DoTag) when atom(Name) ->
816
821
    encode_enumerated(C, Val, NamedNumberList, DoTag);
817
822
 
818
 
encode_enumerated(_, Val, _, _) -> 
819
 
    exit({error,{asn1, {enumerated_not_namednumber, Val}}}). 
820
 
 
821
 
 
822
 
 
823
 
%%============================================================================ 
824
 
%% decode enumerated value 
825
 
%%   (Buffer, Range, NamedNumberList, HasTag, TotalLen) ->  
826
 
%%                                    {Value, RemainingBuffer, RemovedBytes} 
 
823
encode_enumerated(_, Val, _, _) ->
 
824
    exit({error,{asn1, {enumerated_not_namednumber, Val}}}).
 
825
 
 
826
 
 
827
 
 
828
%%============================================================================
 
829
%% decode enumerated value
 
830
%%   (Buffer, Range, NamedNumberList, HasTag, TotalLen) ->
 
831
%%                                    {Value, RemainingBuffer, RemovedBytes}
827
832
%%===========================================================================
828
833
decode_enumerated(Buffer, Range, NamedNumberList, Tags, OptOrMand) ->
829
834
    NewTags = new_tags(Tags,#tag{class=?UNIVERSAL,number=?N_ENUMERATED}),
830
 
    decode_enumerated_notag(Buffer, Range, NamedNumberList, 
 
835
    decode_enumerated_notag(Buffer, Range, NamedNumberList,
831
836
                            NewTags, OptOrMand).
832
837
 
833
838
decode_enumerated_notag(Buffer, Range, NNList = {NamedNumberList,ExtList}, Tags, OptOrMand) ->
834
 
    {RestTags, {FormLen, Buffer0, Rb0}} = 
 
839
    {RestTags, {FormLen, Buffer0, Rb0}} =
835
840
        check_tags_i(Tags, Buffer, OptOrMand),
836
841
 
837
842
    case FormLen of
838
843
        {?CONSTRUCTED,Len} ->
839
844
            {Buffer00,RestBytes} = split_list(Buffer0,Len),
840
 
            {Val01, Buffer01, Rb01} = 
 
845
            {Val01, Buffer01, Rb01} =
841
846
                decode_enumerated_notag(Buffer00, Range, NNList, RestTags, OptOrMand),
842
847
            {Buffer02, Rb02} = restbytes2(RestBytes,Buffer01,noext),
843
848
            {Val01, Buffer02, Rb0+Rb01+Rb02};
844
 
        {_,Len} ->                  
845
 
            {Val01, Buffer01, Rb01} = 
 
849
        {_,Len} ->
 
850
            {Val01, Buffer01, Rb01} =
846
851
                decode_integer2(Len, Buffer0, Rb0+Len),
847
852
            case decode_enumerated1(Val01, NamedNumberList) of
848
853
                {asn1_enum,Val01} ->
851
856
                    {Result01, Buffer01, Rb01}
852
857
            end
853
858
    end;
854
 
 
 
859
 
855
860
decode_enumerated_notag(Buffer, Range, NNList, Tags, OptOrMand) ->
856
 
    {RestTags, {FormLen, Buffer0, Rb0}} = 
 
861
    {RestTags, {FormLen, Buffer0, Rb0}} =
857
862
        check_tags_i(Tags, Buffer, OptOrMand),
858
863
 
859
864
    case FormLen of
860
865
        {?CONSTRUCTED,Len} ->
861
866
            {Buffer00,RestBytes} = split_list(Buffer0,Len),
862
 
            {Val01, Buffer01, Rb01} = 
 
867
            {Val01, Buffer01, Rb01} =
863
868
                decode_enumerated_notag(Buffer00, Range, NNList, RestTags, OptOrMand),
864
869
            {Buffer02, Rb02} = restbytes2(RestBytes,Buffer01,noext),
865
870
            {Val01, Buffer02, Rb0+Rb01+Rb02};
866
 
        {_,Len} ->                  
867
 
            {Val01, Buffer02, Rb02} = 
868
 
                decode_integer2(Len, Buffer0, Rb0+Len), 
 
871
        {_,Len} ->
 
872
            {Val01, Buffer02, Rb02} =
 
873
                decode_integer2(Len, Buffer0, Rb0+Len),
869
874
            case decode_enumerated1(Val01, NNList) of
870
875
                {asn1_enum,_} ->
871
876
                    exit({error,{asn1, {illegal_enumerated, Val01}}});
874
879
            end
875
880
    end.
876
881
 
877
 
decode_enumerated1(Val, NamedNumberList) ->     
878
 
    %% it must be a named integer 
879
 
    case lists:keysearch(Val, 2, NamedNumberList) of 
880
 
        {value,{NamedVal, _}} -> 
881
 
            NamedVal; 
882
 
        _ -> 
 
882
decode_enumerated1(Val, NamedNumberList) ->
 
883
    %% it must be a named integer
 
884
    case lists:keysearch(Val, 2, NamedNumberList) of
 
885
        {value,{NamedVal, _}} ->
 
886
            NamedVal;
 
887
        _ ->
883
888
            {asn1_enum,Val}
884
889
    end.
885
 
 
886
 
 
887
 
%%============================================================================ 
888
 
%%
889
 
%% Real value, ITU_T X.690 Chapter 8.5 
890
 
%%============================================================================ 
891
 
%%
892
 
%% encode real value 
893
 
%%============================================================================ 
894
 
 
895
 
%% only base 2 internally so far!! 
896
 
encode_real(0, DoTag) ->
897
 
    dotag(DoTag, ?N_REAL, {[],0}); 
898
 
encode_real('PLUS-INFINITY', DoTag) ->
899
 
    dotag(DoTag, ?N_REAL, {[64],1}); 
900
 
encode_real('MINUS-INFINITY', DoTag) -> 
901
 
    dotag(DoTag, ?N_REAL, {[65],1}); 
902
 
encode_real(Val, DoTag) when tuple(Val)-> 
903
 
    dotag(DoTag, ?N_REAL, encode_real(Val)). 
904
 
 
905
 
%%%%%%%%%%%%%% 
906
 
%% not optimal efficient..  
907
 
%% only base 2 of Mantissa encoding! 
908
 
%% only base 2 of ExpBase encoding! 
909
 
encode_real({Man, Base, Exp}) -> 
910
 
%%    io:format("Mantissa: ~w Base: ~w, Exp: ~w~n",[Man, Base, Exp]), 
911
 
     
912
 
    OctExp = if Exp >= 0 -> list_to_binary(encode_integer_pos(Exp, [])); 
 
890
 
 
891
 
 
892
%%============================================================================
 
893
%%
 
894
%% Real value, ITU_T X.690 Chapter 8.5
 
895
%%============================================================================
 
896
%%
 
897
%% encode real value
 
898
%%============================================================================
 
899
 
 
900
%% only base 2 internally so far!!
 
901
encode_real(_C,0, DoTag) ->
 
902
    dotag(DoTag, ?N_REAL, {[],0});
 
903
encode_real(_C,'PLUS-INFINITY', DoTag) ->
 
904
    dotag(DoTag, ?N_REAL, {[64],1});
 
905
encode_real(_C,'MINUS-INFINITY', DoTag) ->
 
906
    dotag(DoTag, ?N_REAL, {[65],1});
 
907
encode_real(C,Val, DoTag) when is_tuple(Val); is_list(Val) ->
 
908
    dotag(DoTag, ?N_REAL, encode_real(C,Val)).
 
909
 
 
910
%%%%%%%%%%%%%%
 
911
%% only base 2 encoding!
 
912
%% binary encoding:
 
913
%% +------------+ +------------+  +-+-+-+-+---+---+
 
914
%% | (tag)9     | |  n + p + 1 |  |1|S|BB |FF |EE |
 
915
%% +------------+ +------------+  +-+-+-+-+---+---+
 
916
%%
 
917
%%       +------------+    +------------+
 
918
%%       |            |    |            |
 
919
%%       +------------+ ...+------------+
 
920
%%           n octets for exponent
 
921
%%
 
922
%%       +------------+    +------------+
 
923
%%       |            |    |            |
 
924
%%       +------------+ ...+------------+
 
925
%%           p octets for pos mantissa
 
926
%%
 
927
%% S is 0 for positive sign
 
928
%%      1 for negative sign
 
929
%% BB: encoding base, 00 = 2, (01 = 8, 10 = 16)
 
930
%%                             01 and 10 not used
 
931
%% FF: scale factor 00 = 0 (used in base 2 encoding)
 
932
%% EE: encoding of the exponent:
 
933
%%     00 - on the following octet
 
934
%%     01 - on the 2 following octets
 
935
%%     10 - on the 3 following octets
 
936
%%     11 - encoding of the length of the two's-complement encoding of
 
937
%%          exponent on the following octet, and two's-complement 
 
938
%%          encoding of exponent on the other octets.
 
939
%%
 
940
%% In DER and base 2 encoding the mantissa is encoded as value 0 or
 
941
%% bit shifted until it is an odd number. Thus, do this for BER as
 
942
%% well.
 
943
%% This interface also used by RT_COMMON
 
944
encode_real(_C,{Mantissa, Base, Exponent}) when Base =:= 2 ->
 
945
%%    io:format("Mantissa: ~w Base: ~w, Exp: ~w~n",[Man, Base, Exp]),
 
946
    {Man,ExpAdd} = truncate_zeros(Mantissa), %% DER adjustment
 
947
    Exp = Exponent + ExpAdd,
 
948
    OctExp = if Exp >= 0 -> list_to_binary(encode_integer_pos(Exp, []));
913
949
                true     -> list_to_binary(encode_integer_neg(Exp, []))
914
 
             end, 
915
 
%%    ok = io:format("OctExp: ~w~n",[OctExp]), 
916
 
    SignBit = if  Man > 0 -> 0;  % bit 7 is pos or neg, no Zeroval 
 
950
             end,
 
951
%%    ok = io:format("OctExp: ~w~n",[OctExp]),
 
952
    SignBit = if  Man > 0 -> 0;  % bit 7 is pos or neg, no Zeroval
917
953
                  true -> 1
918
 
              end, 
919
 
%%    ok = io:format("SignBitMask: ~w~n",[SignBitMask]), 
920
 
    InBase = if  Base =:= 2 -> 0;   % bit 6,5: only base 2 this far! 
921
 
                           true -> 
922
 
                               exit({error,{asn1, {encode_real_non_supported_encodeing, Base}}}) 
923
 
                       end, 
924
 
    SFactor = 0,   % bit 4,3: no scaling since only base 2 
925
 
    OctExpLen = size(OctExp), 
926
 
    if OctExpLen > 255 -> 
927
 
            exit({error,{asn1, {to_big_exp_in_encode_real, OctExpLen}}}); 
928
 
       true  -> true %% make real assert later.. 
929
 
    end,  
930
 
    {LenCode, EOctets} = case OctExpLen of   % bit 2,1  
931
 
                             1 -> {0, OctExp}; 
932
 
                             2 -> {1, OctExp}; 
933
 
                             3 -> {2, OctExp}; 
934
 
                             _ -> {3, <<OctExpLen, OctExp/binary>>}  
935
 
                         end, 
936
 
    FirstOctet = <<1:1,SignBit:1,InBase:2,SFactor:2,LenCode:2>>,
937
 
    OctMantissa = if Man > 0 -> list_to_binary(minimum_octets(Man)); 
938
 
                     true    -> list_to_binary(minimum_octets(-(Man))) % signbit keeps track of sign 
939
 
                  end, 
940
 
    %%    ok = io:format("LenMask: ~w EOctets: ~w~nFirstOctet: ~w OctMantissa: ~w OctExpLen: ~w~n", [LenMask, EOctets, FirstOctet, OctMantissa, OctExpLen]), 
 
954
              end,
 
955
%%    ok = io:format("SignBitMask: ~w~n",[SignBitMask]),
 
956
    SFactor = 0,
 
957
    OctExpLen = size(OctExp),
 
958
    if OctExpLen > 255 ->
 
959
            exit({error,{asn1, {to_big_exp_in_encode_real, OctExpLen}}});
 
960
       true  -> true %% make real assert later..
 
961
    end,
 
962
    {LenCode, EOctets} = case OctExpLen of   % bit 2,1
 
963
                             1 -> {0, OctExp};
 
964
                             2 -> {1, OctExp};
 
965
                             3 -> {2, OctExp};
 
966
                             _ -> {3, <<OctExpLen, OctExp/binary>>}
 
967
                         end,
 
968
    BB = 0, %% 00 for base 2
 
969
    FirstOctet = <<1:1,SignBit:1,BB:2,SFactor:2,LenCode:2>>,
 
970
    OctMantissa = if Man > 0 -> list_to_binary(minimum_octets(Man));
 
971
                     true    -> list_to_binary(minimum_octets(-(Man))) % signbit keeps track of sign
 
972
                  end,
 
973
    %%    ok = io:format("LenMask: ~w EOctets: ~w~nFirstOctet: ~w OctMantissa: ~w OctExpLen: ~w~n", [LenMask, EOctets, FirstOctet, OctMantissa, OctExpLen]),
941
974
    Bin = <<FirstOctet/binary, EOctets/binary, OctMantissa/binary>>,
942
 
    {Bin, size(Bin)}. 
943
 
 
944
 
 
945
 
%encode_real({Man, Base, Exp}) -> 
946
 
%%    io:format("Mantissa: ~w Base: ~w, Exp: ~w~n",[Man, Base, Exp]), 
947
 
     
948
 
%    OctExp = if Exp >= 0 -> encode_integer_pos(Exp, []); 
949
 
%               true     -> encode_integer_neg(Exp, []) 
950
 
%            end, 
951
 
%%    ok = io:format("OctExp: ~w~n",[OctExp]), 
952
 
%    SignBitMask = if  Man > 0 -> 2#00000000;  % bit 7 is pos or neg, no Zeroval 
953
 
%                     true    -> 2#01000000 
954
 
%                 end, 
955
 
%%    ok = io:format("SignBitMask: ~w~n",[SignBitMask]), 
956
 
%    InternalBaseMask = if  Base =:= 2 -> 2#00000000;   % bit 6,5: only base 2 this far! 
957
 
%                          true -> 
958
 
%                              exit({error,{asn1, {encode_real_non_supported_encodeing, Base}}}) 
959
 
%                      end, 
960
 
%    ScalingFactorMask =2#00000000,   % bit 4,3: no scaling since only base 2 
961
 
%    OctExpLen = length(OctExp), 
962
 
%    if OctExpLen > 255  -> 
963
 
%           exit({error,{asn1, {to_big_exp_in_encode_real, OctExpLen}}}); 
964
 
%       true  -> true %% make real assert later.. 
965
 
%    end,  
966
 
%    {LenMask, EOctets} = case OctExpLen of   % bit 2,1  
967
 
%                            1 -> {0, OctExp}; 
968
 
%                            2 -> {1, OctExp}; 
969
 
%                            3 -> {2, OctExp}; 
970
 
%                            _ -> {3, [OctExpLen, OctExp]}  
971
 
%                        end, 
972
 
%    FirstOctet = (SignBitMask bor InternalBaseMask bor 
973
 
%                 ScalingFactorMask bor LenMask bor 
974
 
%                 2#10000000), % bit set for binary mantissa encoding! 
975
 
%    OctMantissa = if Man > 0 -> minimum_octets(Man); 
976
 
%                    true    -> minimum_octets(-(Man)) % signbit keeps track of sign 
977
 
%                 end, 
978
 
%%    ok = io:format("LenMask: ~w EOctets: ~w~nFirstOctet: ~w OctMantissa: ~w OctExpLen: ~w~n", [LenMask, EOctets, FirstOctet, OctMantissa, OctExpLen]), 
979
 
%     {[FirstOctet, EOctets, OctMantissa],
980
 
%      length(OctMantissa) + 
981
 
%      (if OctExpLen > 3 -> 
982
 
%              OctExpLen + 2; 
983
 
%         true -> 
984
 
%              OctExpLen + 1 
985
 
%       end) 
986
 
%     }. 
987
 
 
988
 
  
989
 
%%============================================================================ 
990
 
%% decode real value 
991
 
%% 
992
 
%% decode_real([OctetBufferList], tuple|value, tag|notag) -> 
993
 
%%  {{Mantissa, Base, Exp} | realval | PLUS-INFINITY | MINUS-INFINITY | 0, 
994
 
%%     RestBuff} 
995
 
%%  
996
 
%% only for base 2 decoding sofar!! 
997
 
%%============================================================================ 
998
 
 
999
 
decode_real(Buffer, Form, Tags, OptOrMand) ->
 
975
    {Bin, size(Bin)};
 
976
encode_real(C,{Mantissa,Base,Exponent}) 
 
977
  when Base =:= 10, is_integer(Mantissa), is_integer(Exponent) ->
 
978
    %% always encode as NR3 due to DER on the format
 
979
    %% mmmm.Eseeee where
 
980
    %% m := digit
 
981
    %% s := '-' | '+' | []
 
982
    %% '+' only allowed in +0
 
983
    %% e := digit
 
984
    %% ex: 1234.E-5679
 
985
%%    {Man,AddExp} = truncate_zeros(Mantissa,0),
 
986
%%    ManNum = trunc(Mantissa),
 
987
%%    {TruncatedMan,NumZeros} = truncate_zeros10(Mantissa),
 
988
    ManStr = integer_to_list(Mantissa),
 
989
    
 
990
    encode_real_as_string(C,ManStr,Exponent);
 
991
encode_real(_C,{_,Base,_}) ->
 
992
    exit({error,{asn1, {encode_real_non_supported_encodeing, Base}}});
 
993
%% base 10
 
994
encode_real(C,Real) when is_list(Real) ->
 
995
    %% The Real string may come in as a NR1, NR2 or NR3 string.
 
996
    {Mantissa, Exponent} =
 
997
        case string:tokens(Real,"Ee") of
 
998
            [NR2] ->
 
999
                {NR2,0};
 
1000
            [NR3MB,NR3E] ->
 
1001
                %% remove beginning zeros
 
1002
                {NR3MB,list_to_integer(NR3E)}
 
1003
        end,
 
1004
    
 
1005
    %% .Decimal | Number | Number.Decimal
 
1006
    ZeroDecimal =
 
1007
        fun("0") -> "";
 
1008
           (L) -> L
 
1009
        end,
 
1010
    {NewMantissa,LenDecimal} =
 
1011
        case Mantissa of
 
1012
            [$.|Dec] ->
 
1013
                NewMan = remove_trailing_zeros(Dec),
 
1014
                {NewMan,length(ZeroDecimal(NewMan))};
 
1015
            _ ->
 
1016
                case string:tokens(Mantissa,",.") of
 
1017
                    [Num] -> %% No decimal-mark
 
1018
                        {integer_to_list(list_to_integer(Num)),0};
 
1019
                    [Num,Dec] ->
 
1020
                        NewDec = ZeroDecimal(remove_trailing_zeros(Dec)),
 
1021
                        NewMan = integer_to_list(list_to_integer(Num)) ++ NewDec,
 
1022
                        {integer_to_list(list_to_integer(NewMan)),
 
1023
                         length(NewDec)}
 
1024
                end
 
1025
        end,
 
1026
    
 
1027
%    DER_Exponent = integer_to_list(Exponent - ExpReduce),
 
1028
    encode_real_as_string(C,NewMantissa,Exponent - LenDecimal).
 
1029
        
 
1030
encode_real_as_string(_C,Mantissa,Exponent)
 
1031
  when is_list(Mantissa), is_integer(Exponent) ->
 
1032
    %% Remove trailing zeros in Mantissa and add this to Exponent
 
1033
    TruncMant = remove_trailing_zeros(Mantissa),
 
1034
 
 
1035
    ExpIncr = length(Mantissa) - length(TruncMant),
 
1036
 
 
1037
    ExpStr = integer_to_list(Exponent + ExpIncr),
 
1038
 
 
1039
    ExpBin =
 
1040
        case ExpStr of
 
1041
            "0" ->
 
1042
                <<"E+0">>;
 
1043
            _ -> 
 
1044
                ExpB = list_to_binary(ExpStr),
 
1045
                <<$E,ExpB/binary>>
 
1046
        end,
 
1047
    ManBin = list_to_binary(TruncMant),
 
1048
    NR3 = 3,
 
1049
    {<<NR3,ManBin/binary,$.,ExpBin/binary>>,2 + size(ManBin) + size(ExpBin)}.
 
1050
    
 
1051
remove_trailing_zeros(IntStr) ->
 
1052
    case lists:dropwhile(fun($0)-> true;
 
1053
                            (_) -> false
 
1054
                         end, lists:reverse(IntStr)) of
 
1055
        [] ->
 
1056
            "0";
 
1057
        ReversedIntStr ->
 
1058
            lists:reverse(ReversedIntStr)
 
1059
    end.
 
1060
 
 
1061
truncate_zeros(Num) ->
 
1062
    truncate_zeros(Num,0).
 
1063
truncate_zeros(0,Sum) ->
 
1064
    {0,Sum};
 
1065
truncate_zeros(M,Sum) ->
 
1066
    case M band 16#f =:= M band 16#e of
 
1067
        true -> truncate_zeros(M bsr 1,Sum+1);
 
1068
        _ -> {M,Sum}
 
1069
    end.
 
1070
 
 
1071
            
 
1072
%%============================================================================
 
1073
%% decode real value
 
1074
%%
 
1075
%% decode_real([OctetBufferList], tuple|value, tag|notag) ->
 
1076
%%  {{Mantissa, Base, Exp} | realval | PLUS-INFINITY | MINUS-INFINITY | 0,
 
1077
%%     RestBuff}
 
1078
%%
 
1079
%% only for base 2 decoding sofar!!
 
1080
%%============================================================================
 
1081
 
 
1082
decode_real(Buffer, C, Tags, OptOrMand) ->
1000
1083
    NewTags = new_tags(Tags,#tag{class=?UNIVERSAL,number=?N_REAL}),
1001
 
    decode_real_notag(Buffer, Form, NewTags, OptOrMand).
1002
 
 
1003
 
decode_real_notag(Buffer, Form, Tags, OptOrMand) ->
1004
 
    {RestTags, {FormLen, Buffer0, Rb0}} = 
 
1084
    decode_real_notag(Buffer, C, NewTags, OptOrMand).
 
1085
 
 
1086
%% This interface used by RT_COMMON
 
1087
decode_real(Buffer,Len) ->
 
1088
    decode_real2(Buffer,[],Len,0).
 
1089
 
 
1090
decode_real_notag(Buffer, C, Tags, OptOrMand) ->
 
1091
    {_RestTags, {{_,Len}, Buffer0, Rb0}} =
1005
1092
        check_tags_i(Tags, Buffer, OptOrMand),
1006
 
 
1007
 
    case FormLen of
1008
 
        {?CONSTRUCTED,Len} ->
1009
 
            {Buffer00,RestBytes} = split_list(Buffer0,Len),
1010
 
            {Val01, Buffer01, Rb01} =
1011
 
                decode_real_notag(Buffer00, Form, RestTags, OptOrMand),
1012
 
            {Buffer02, Rb02} = restbytes2(RestBytes,Buffer01,noext),
1013
 
            {Val01, Buffer02, Rb0+Rb01+Rb02};
1014
 
        {_,Len} ->
1015
 
            decode_real2(Buffer0, Form, Len, Rb0)
1016
 
    end.
1017
 
 
1018
 
decode_real2(Buffer0, Form, Len, RemBytes1) ->
 
1093
    decode_real2(Buffer0, C, Len, Rb0).
 
1094
 
 
1095
decode_real2(Buffer, _C, 0, _RemBytes) ->
 
1096
    {0,Buffer};
 
1097
decode_real2(Buffer0, _C, Len, RemBytes1) ->
1019
1098
    <<First, Buffer2/binary>> = Buffer0,
1020
1099
    if
1021
 
        First =:= 2#01000000 -> {'PLUS-INFINITY', Buffer2}; 
1022
 
        First =:= 2#01000001 -> {'MINUS-INFINITY', Buffer2}; 
1023
 
        First =:= 2#00000000 -> {0, Buffer2}; 
1024
 
        true -> 
1025
 
            %% have some check here to verify only supported bases (2) 
1026
 
            <<_B7:1,B6:1,B5_4:2,_B3_2:2,B1_0:2>> = <<First>>,
1027
 
                Sign = B6,
1028
 
            Base = 
1029
 
                case B5_4 of
1030
 
                    0 -> 2;  % base 2, only one so far 
1031
 
                    _ -> exit({error,{asn1, {non_supported_base, First}}}) 
1032
 
                end, 
1033
 
%           ScalingFactor = 
1034
 
%%              case B3_2 of
1035
 
%%                  0 -> 0;  % no scaling so far  
1036
 
%%                  _ -> exit({error,{asn1, {non_supported_scaling, First}}}) 
1037
 
%%              end, 
1038
 
                                                %           ok = io:format("Buffer2: ~w~n",[Buffer2]), 
1039
 
            {FirstLen, {Exp, Buffer3,_Rb2}, RemBytes2} = 
1040
 
                case B1_0 of
1041
 
                    0 -> {2, decode_integer2(1, Buffer2, RemBytes1), RemBytes1+1}; 
1042
 
                    1 -> {3, decode_integer2(2, Buffer2, RemBytes1), RemBytes1+2}; 
1043
 
                    2 -> {4, decode_integer2(3, Buffer2, RemBytes1), RemBytes1+3}; 
1044
 
                    3 -> 
 
1100
        First =:= 2#01000000 -> {'PLUS-INFINITY', Buffer2};
 
1101
        First =:= 2#01000001 -> {'MINUS-INFINITY', Buffer2};
 
1102
%%      First =:= 2#00000000 -> {0, Buffer2};
 
1103
        First =:= 1 orelse First =:= 2 orelse First =:= 3 ->
 
1104
            %% charcter string encoding of base 10
 
1105
            {NRx,Rest} = split_binary(Buffer2,Len-1),
 
1106
            {binary_to_list(NRx),Rest,Len};
 
1107
        true ->
 
1108
            %% have some check here to verify only supported bases (2)
 
1109
            %% not base 8 or 16
 
1110
            <<_B7:1,Sign:1,BB:2,_FF:2,EE:2>> = <<First>>,
 
1111
            Base =
 
1112
                case BB of
 
1113
                    0 -> 2;  % base 2, only one so far
 
1114
                    _ -> exit({error,{asn1, {non_supported_base, BB}}})
 
1115
                end,
 
1116
            {FirstLen, {Exp, Buffer3,_Rb2}, RemBytes2} =
 
1117
                case EE of
 
1118
                    0 -> {2, decode_integer2(1, Buffer2, RemBytes1), RemBytes1+1};
 
1119
                    1 -> {3, decode_integer2(2, Buffer2, RemBytes1), RemBytes1+2};
 
1120
                    2 -> {4, decode_integer2(3, Buffer2, RemBytes1), RemBytes1+3};
 
1121
                    3 ->
1045
1122
                        <<ExpLen1,RestBuffer/binary>> = Buffer2,
1046
 
                        { ExpLen1 + 2, 
1047
 
                          decode_integer2(ExpLen1, RestBuffer, RemBytes1), 
1048
 
                          RemBytes1+ExpLen1} 
1049
 
                end, 
1050
 
                                                %           io:format("FirstLen: ~w, Exp: ~w, Buffer3: ~w ~n",
1051
 
                                                %           [FirstLen, Exp, Buffer3]), 
 
1123
                        { ExpLen1 + 2,
 
1124
                          decode_integer2(ExpLen1, RestBuffer, RemBytes1),
 
1125
                          RemBytes1+ExpLen1}
 
1126
                end,
 
1127
            %%      io:format("FirstLen: ~w, Exp: ~w, Buffer3: ~w ~n",
 
1128
 
1052
1129
            Length = Len - FirstLen,
1053
1130
            <<LongInt:Length/unit:8,RestBuff/binary>> = Buffer3,
1054
 
            {{Mantissa, Buffer4}, RemBytes3} = 
1055
 
                if Sign =:= 0 -> 
1056
 
                                                %                       io:format("sign plus~n"), 
 
1131
            {{Mantissa, Buffer4}, RemBytes3} =
 
1132
                if Sign =:= 0 ->
 
1133
                        %%                      io:format("sign plus~n"),
1057
1134
                        {{LongInt, RestBuff}, 1 + Length};
1058
 
                   true -> 
1059
 
                                                %                       io:format("sign minus~n"), 
 
1135
                   true ->
 
1136
                        %%                      io:format("sign minus~n"),
1060
1137
                        {{-LongInt, RestBuff}, 1 + Length}
1061
 
                end, 
1062
 
                                                %           io:format("Form: ~w~n",[Form]), 
1063
 
            case Form of 
1064
 
                tuple -> 
1065
 
%%                  {Val,Buf,_RemB} = Exp, 
1066
 
%%                  {{Mantissa, Base, {Val,Buf}}, Buffer4, RemBytes2+RemBytes3};  
1067
 
                    %% This change was only to remove dialyzer warning. Code should be removed or redisigned.
1068
 
                    {{Mantissa, Base, {Exp,Buffer3}}, Buffer4, RemBytes2+RemBytes3};  
1069
 
                _value -> 
1070
 
                    comming 
1071
 
            end 
1072
 
    end. 
1073
 
 
1074
 
 
1075
 
%%============================================================================ 
1076
 
%% Bitstring value, ITU_T X.690 Chapter 8.6 
1077
 
%%
1078
 
%% encode bitstring value 
1079
 
%% 
1080
 
%% bitstring NamedBitList 
1081
 
%% Val can be  of: 
1082
 
%% - [identifiers] where only named identifers are set to one,  
1083
 
%%   the Constraint must then have some information of the  
1084
 
%%   bitlength. 
1085
 
%% - [list of ones and zeroes] all bits  
1086
 
%% - integer value representing the bitlist 
1087
 
%% C is constrint Len, only valid when identifiers 
1088
 
%%============================================================================ 
1089
 
 
 
1138
                end,
 
1139
            {{Mantissa, Base, Exp}, Buffer4, RemBytes2+RemBytes3}
 
1140
    end.
 
1141
 
 
1142
 
 
1143
%%============================================================================
 
1144
%% Bitstring value, ITU_T X.690 Chapter 8.6
 
1145
%%
 
1146
%% encode bitstring value
 
1147
%%
 
1148
%% bitstring NamedBitList
 
1149
%% Val can be  of:
 
1150
%% - [identifiers] where only named identifers are set to one,
 
1151
%%   the Constraint must then have some information of the
 
1152
%%   bitlength.
 
1153
%% - [list of ones and zeroes] all bits
 
1154
%% - integer value representing the bitlist
 
1155
%% C is constrint Len, only valid when identifiers
 
1156
%%============================================================================
 
1157
 
1090
1158
encode_bit_string(C,Bin={Unused,BinBits},NamedBitList,DoTag) when integer(Unused), binary(BinBits) ->
1091
1159
    encode_bin_bit_string(C,Bin,NamedBitList,DoTag);
1092
 
encode_bit_string(C, [FirstVal | RestVal], NamedBitList, DoTag) when atom(FirstVal) -> 
1093
 
    encode_bit_string_named(C, [FirstVal | RestVal], NamedBitList, DoTag); 
1094
 
 
1095
 
encode_bit_string(C, [{bit,X} | RestVal], NamedBitList, DoTag) -> 
1096
 
    encode_bit_string_named(C, [{bit,X} | RestVal], NamedBitList, DoTag); 
1097
 
 
1098
 
encode_bit_string(C, [FirstVal| RestVal], NamedBitList, DoTag) when integer(FirstVal) -> 
1099
 
    encode_bit_string_bits(C, [FirstVal | RestVal], NamedBitList, DoTag); 
1100
 
 
1101
 
encode_bit_string(_, 0, _, []) -> 
1102
 
    {[?N_BIT_STRING,1,0],3};
1103
 
 
1104
 
encode_bit_string(_, 0, _, DoTag) -> 
1105
 
    dotag(DoTag, ?N_BIT_STRING, {<<0>>,1}); 
1106
 
 
1107
 
encode_bit_string(_, [], _, []) -> 
1108
 
    {[?N_BIT_STRING,1,0],3};
1109
 
 
1110
 
encode_bit_string(_, [], _, DoTag) -> 
1111
 
    dotag(DoTag, ?N_BIT_STRING, {<<0>>,1}); 
1112
 
 
1113
 
encode_bit_string(C, IntegerVal, NamedBitList, DoTag) when integer(IntegerVal) -> 
 
1160
encode_bit_string(C, [FirstVal | RestVal], NamedBitList, DoTag) when atom(FirstVal) ->
 
1161
    encode_bit_string_named(C, [FirstVal | RestVal], NamedBitList, DoTag);
 
1162
 
 
1163
encode_bit_string(C, [{bit,X} | RestVal], NamedBitList, DoTag) ->
 
1164
    encode_bit_string_named(C, [{bit,X} | RestVal], NamedBitList, DoTag);
 
1165
 
 
1166
encode_bit_string(C, [FirstVal| RestVal], NamedBitList, DoTag) when integer(FirstVal) ->
 
1167
    encode_bit_string_bits(C, [FirstVal | RestVal], NamedBitList, DoTag);
 
1168
 
 
1169
encode_bit_string(_, 0, _, []) ->
 
1170
    {[?N_BIT_STRING,1,0],3};
 
1171
 
 
1172
encode_bit_string(_, 0, _, DoTag) ->
 
1173
    dotag(DoTag, ?N_BIT_STRING, {<<0>>,1});
 
1174
 
 
1175
encode_bit_string(_, [], _, []) ->
 
1176
    {[?N_BIT_STRING,1,0],3};
 
1177
 
 
1178
encode_bit_string(_, [], _, DoTag) ->
 
1179
    dotag(DoTag, ?N_BIT_STRING, {<<0>>,1});
 
1180
 
 
1181
encode_bit_string(C, IntegerVal, NamedBitList, DoTag) when integer(IntegerVal) ->
1114
1182
    BitListVal = int_to_bitlist(IntegerVal),
1115
1183
    encode_bit_string_bits(C, BitListVal, NamedBitList, DoTag);
1116
1184
 
1117
1185
encode_bit_string(C, {Name,BitList}, NamedBitList, DoTag) when atom(Name) ->
1118
1186
    encode_bit_string(C, BitList, NamedBitList, DoTag).
1119
 
  
1120
 
 
1121
 
 
 
1187
 
 
1188
 
 
1189
 
1122
1190
int_to_bitlist(0) ->
1123
1191
    [];
1124
1192
int_to_bitlist(Int) when integer(Int), Int >= 0 ->
1125
1193
    [Int band 1 | int_to_bitlist(Int bsr 1)].
1126
1194
 
1127
1195
 
1128
 
%%================================================================= 
1129
 
%% Encode BIT STRING of the form {Unused,BinBits}. 
1130
 
%% Unused is the number of unused bits in the last byte in BinBits 
 
1196
%%=================================================================
 
1197
%% Encode BIT STRING of the form {Unused,BinBits}.
 
1198
%% Unused is the number of unused bits in the last byte in BinBits
1131
1199
%% and BinBits is a binary representing the BIT STRING.
1132
 
%%================================================================= 
 
1200
%%=================================================================
1133
1201
encode_bin_bit_string(C,{Unused,BinBits},_NamedBitList,DoTag)->
1134
1202
    case get_constraint(C,'SizeConstraint') of
1135
1203
        no ->
1138
1206
            BBLen = (size(BinBits)*8)-Unused,
1139
1207
            if
1140
1208
                BBLen > Max ->
1141
 
                    exit({error,{asn1, 
1142
 
                                 {bitstring_length, 
1143
 
                                  {{was,BBLen},{maximum,Max}}}}}); 
 
1209
                    exit({error,{asn1,
 
1210
                                 {bitstring_length,
 
1211
                                  {{was,BBLen},{maximum,Max}}}}});
1144
1212
                true ->
1145
1213
                    remove_unused_then_dotag(DoTag,?N_BIT_STRING,
1146
1214
                                             Unused,BinBits)
1151
1219
                    remove_unused_then_dotag(DoTag,?N_BIT_STRING,
1152
1220
                                             Unused,BinBits);
1153
1221
                BBSize  ->
1154
 
                    exit({error,{asn1,  
1155
 
                                 {bitstring_length, 
 
1222
                    exit({error,{asn1,
 
1223
                                 {bitstring_length,
1156
1224
                                  {{was,BBSize},{should_be,Size}}}}})
1157
1225
            end
1158
1226
    end.
1188
1256
    end.
1189
1257
 
1190
1258
 
1191
 
%%================================================================= 
1192
 
%% Encode named bits 
1193
 
%%================================================================= 
1194
 
 
1195
 
encode_bit_string_named(C, [FirstVal | RestVal], NamedBitList, DoTag) -> 
 
1259
%%=================================================================
 
1260
%% Encode named bits
 
1261
%%=================================================================
 
1262
 
 
1263
encode_bit_string_named(C, [FirstVal | RestVal], NamedBitList, DoTag) ->
1196
1264
    {Len,Unused,OctetList} =
1197
 
        case get_constraint(C,'SizeConstraint') of 
1198
 
            no -> 
1199
 
                ToSetPos = get_all_bitposes([FirstVal | RestVal],
1200
 
                                            NamedBitList, []), 
1201
 
                BitList = make_and_set_list(lists:max(ToSetPos)+1, 
1202
 
                                            ToSetPos, 0), 
1203
 
                encode_bitstring(BitList);  
1204
 
            {_Min,Max} -> 
1205
 
                ToSetPos = get_all_bitposes([FirstVal | RestVal],
1206
 
                                            NamedBitList, []), 
1207
 
                BitList = make_and_set_list(Max, ToSetPos, 0), 
1208
 
                encode_bitstring(BitList);
1209
 
            Size -> 
1210
 
                ToSetPos = get_all_bitposes([FirstVal | RestVal],
1211
 
                                            NamedBitList, []), 
1212
 
                BitList = make_and_set_list(Size, ToSetPos, 0), 
 
1265
        case get_constraint(C,'SizeConstraint') of
 
1266
            no ->
 
1267
                ToSetPos = get_all_bitposes([FirstVal | RestVal],
 
1268
                                            NamedBitList, []),
 
1269
                BitList = make_and_set_list(lists:max(ToSetPos)+1,
 
1270
                                            ToSetPos, 0),
 
1271
                encode_bitstring(BitList);
 
1272
            {_Min,Max} ->
 
1273
                ToSetPos = get_all_bitposes([FirstVal | RestVal],
 
1274
                                            NamedBitList, []),
 
1275
                BitList = make_and_set_list(Max, ToSetPos, 0),
 
1276
                encode_bitstring(BitList);
 
1277
            Size ->
 
1278
                ToSetPos = get_all_bitposes([FirstVal | RestVal],
 
1279
                                            NamedBitList, []),
 
1280
                BitList = make_and_set_list(Size, ToSetPos, 0),
1213
1281
                encode_bitstring(BitList)
1214
1282
        end,
1215
1283
    case DoTag of
1221
1289
            dotag(DoTag, ?N_BIT_STRING, {[Unused|OctetList],Len+1})
1222
1290
    end.
1223
1291
 
1224
 
         
1225
 
%%---------------------------------------- 
1226
 
%% get_all_bitposes([list of named bits to set], named_bit_db, []) -> 
1227
 
%%   [sorted_list_of_bitpositions_to_set] 
1228
 
%%---------------------------------------- 
 
1292
 
 
1293
%%----------------------------------------
 
1294
%% get_all_bitposes([list of named bits to set], named_bit_db, []) ->
 
1295
%%   [sorted_list_of_bitpositions_to_set]
 
1296
%%----------------------------------------
1229
1297
 
1230
1298
get_all_bitposes([{bit,ValPos}|Rest], NamedBitList, Ack) ->
1231
1299
    get_all_bitposes(Rest, NamedBitList, [ValPos | Ack ]);
1232
 
get_all_bitposes([Val | Rest], NamedBitList, Ack) when atom(Val) -> 
1233
 
    case lists:keysearch(Val, 1, NamedBitList) of 
1234
 
        {value, {_ValName, ValPos}} -> 
1235
 
            get_all_bitposes(Rest, NamedBitList, [ValPos | Ack]); 
1236
 
        _ -> 
1237
 
            exit({error,{asn1, {bitstring_namedbit, Val}}}) 
1238
 
    end; 
1239
 
get_all_bitposes([], _NamedBitList, Ack) -> 
1240
 
    lists:sort(Ack). 
1241
 
 
1242
 
 
1243
 
%%---------------------------------------- 
1244
 
%% make_and_set_list(Len of list to return, [list of positions to set to 1])-> 
1245
 
%% returns list of Len length, with all in SetPos set. 
1246
 
%% in positioning in list the first element is 0, the second 1 etc.., but 
1247
 
%% Len will make a list of length Len, not Len + 1. 
1248
 
%%    BitList = make_and_set_list(C, ToSetPos, 0), 
1249
 
%%---------------------------------------- 
1250
 
 
1251
 
make_and_set_list(0, [], _) -> []; 
1252
 
make_and_set_list(0, _, _) ->  
1253
 
    exit({error,{asn1,bitstring_sizeconstraint}}); 
1254
 
make_and_set_list(Len, [XPos|SetPos], XPos) -> 
1255
 
    [1 | make_and_set_list(Len - 1, SetPos, XPos + 1)]; 
1256
 
make_and_set_list(Len, [Pos|SetPos], XPos) -> 
1257
 
    [0 | make_and_set_list(Len - 1, [Pos | SetPos], XPos + 1)]; 
1258
 
make_and_set_list(Len, [], XPos) -> 
1259
 
    [0 | make_and_set_list(Len - 1, [], XPos + 1)]. 
1260
 
 
1261
 
 
1262
 
 
1263
 
 
1264
 
 
1265
 
 
1266
 
%%================================================================= 
1267
 
%% Encode bit string for lists of ones and zeroes 
1268
 
%%================================================================= 
1269
 
encode_bit_string_bits(C, BitListVal, _NamedBitList, DoTag) when list(BitListVal) -> 
 
1300
get_all_bitposes([Val | Rest], NamedBitList, Ack) when atom(Val) ->
 
1301
    case lists:keysearch(Val, 1, NamedBitList) of
 
1302
        {value, {_ValName, ValPos}} ->
 
1303
            get_all_bitposes(Rest, NamedBitList, [ValPos | Ack]);
 
1304
        _ ->
 
1305
            exit({error,{asn1, {bitstring_namedbit, Val}}})
 
1306
    end;
 
1307
get_all_bitposes([], _NamedBitList, Ack) ->
 
1308
    lists:sort(Ack).
 
1309
 
 
1310
 
 
1311
%%----------------------------------------
 
1312
%% make_and_set_list(Len of list to return, [list of positions to set to 1])->
 
1313
%% returns list of Len length, with all in SetPos set.
 
1314
%% in positioning in list the first element is 0, the second 1 etc.., but
 
1315
%% Len will make a list of length Len, not Len + 1.
 
1316
%%    BitList = make_and_set_list(C, ToSetPos, 0),
 
1317
%%----------------------------------------
 
1318
 
 
1319
make_and_set_list(0, [], _) -> [];
 
1320
make_and_set_list(0, _, _) ->
 
1321
    exit({error,{asn1,bitstring_sizeconstraint}});
 
1322
make_and_set_list(Len, [XPos|SetPos], XPos) ->
 
1323
    [1 | make_and_set_list(Len - 1, SetPos, XPos + 1)];
 
1324
make_and_set_list(Len, [Pos|SetPos], XPos) ->
 
1325
    [0 | make_and_set_list(Len - 1, [Pos | SetPos], XPos + 1)];
 
1326
make_and_set_list(Len, [], XPos) ->
 
1327
    [0 | make_and_set_list(Len - 1, [], XPos + 1)].
 
1328
 
 
1329
 
 
1330
 
 
1331
 
 
1332
 
 
1333
 
 
1334
%%=================================================================
 
1335
%% Encode bit string for lists of ones and zeroes
 
1336
%%=================================================================
 
1337
encode_bit_string_bits(C, BitListVal, _NamedBitList, DoTag) when list(BitListVal) ->
1270
1338
    {Len,Unused,OctetList} =
1271
 
        case get_constraint(C,'SizeConstraint') of 
1272
 
            no -> 
1273
 
                encode_bitstring(BitListVal);  
1274
 
            Constr={Min,_Max} when integer(Min) -> 
 
1339
        case get_constraint(C,'SizeConstraint') of
 
1340
            no ->
 
1341
                encode_bitstring(BitListVal);
 
1342
            Constr={Min,_Max} when integer(Min) ->
1275
1343
                encode_constr_bit_str_bits(Constr,BitListVal,DoTag);
1276
1344
            {Constr={_,_},[]} ->
1277
1345
                %% constraint with extension mark
1282
1350
            Size ->
1283
1351
                case length(BitListVal) of
1284
1352
                    BitSize when BitSize == Size ->
1285
 
                        encode_bitstring(BitListVal);  
 
1353
                        encode_bitstring(BitListVal);
1286
1354
                    BitSize when BitSize < Size ->
1287
 
                        PaddedList = 
 
1355
                        PaddedList =
1288
1356
                            pad_bit_list(Size-BitSize,BitListVal),
1289
1357
                        encode_bitstring(PaddedList);
1290
 
                    BitSize -> 
 
1358
                    BitSize ->
1291
1359
                        exit({error,
1292
 
                              {asn1,  
1293
 
                               {bitstring_length, 
 
1360
                              {asn1,
 
1361
                               {bitstring_length,
1294
1362
                                {{was,BitSize},
1295
 
                                 {should_be,Size}}}}}) 
 
1363
                                 {should_be,Size}}}}})
1296
1364
                end
1297
1365
        end,
1298
 
    %%add unused byte to the Len 
 
1366
    %%add unused byte to the Len
1299
1367
    case DoTag of
1300
1368
        [] ->
1301
1369
            dotag_universal(?N_BIT_STRING,[Unused|OctetList],Len+1);
1302
1370
%           {EncLen,LenLen}=encode_length(Len+1),
1303
1371
%           {[?N_BIT_STRING,EncLen,Unused|OctetList],1+LenLen+Len+1};
1304
1372
        _ ->
1305
 
            dotag(DoTag, ?N_BIT_STRING, 
 
1373
            dotag(DoTag, ?N_BIT_STRING,
1306
1374
                  {[Unused | OctetList],Len+1})
1307
1375
    end.
1308
1376
 
1309
 
 
 
1377
 
1310
1378
encode_constr_bit_str_bits({{_Min1,Max1},{Min2,Max2}},BitListVal,_DoTag) ->
1311
1379
    BitLen = length(BitListVal),
1312
1380
    case BitLen of
1313
 
        Len when Len > Max2 -> 
 
1381
        Len when Len > Max2 ->
1314
1382
            exit({error,{asn1,{bitstring_length,{{was,BitLen},
1315
 
                                                 {maximum,Max2}}}}}); 
 
1383
                                                 {maximum,Max2}}}}});
1316
1384
        Len when Len > Max1, Len < Min2  ->
1317
1385
            exit({error,{asn1,{bitstring_length,{{was,BitLen},
1318
1386
                                                 {not_allowed_interval,
1321
1389
            encode_bitstring(BitListVal)
1322
1390
    end;
1323
1391
encode_constr_bit_str_bits({Min,Max},BitListVal,_DoTag) ->
1324
 
    BitLen = length(BitListVal), 
1325
 
    if  
1326
 
        BitLen > Max -> 
 
1392
    BitLen = length(BitListVal),
 
1393
    if
 
1394
        BitLen > Max ->
1327
1395
            exit({error,{asn1,{bitstring_length,{{was,BitLen},
1328
 
                                                 {maximum,Max}}}}}); 
 
1396
                                                 {maximum,Max}}}}});
1329
1397
        BitLen < Min ->
1330
1398
            exit({error,{asn1,{bitstring_length,{{was,BitLen},
1331
1399
                                                 {minimum,Min}}}}});
1332
 
        true -> 
1333
 
            encode_bitstring(BitListVal)  
 
1400
        true ->
 
1401
            encode_bitstring(BitListVal)
1334
1402
    end.
1335
1403
 
1336
1404
 
1337
 
%% returns a list of length Size + length(BitListVal), with BitListVal 
 
1405
%% returns a list of length Size + length(BitListVal), with BitListVal
1338
1406
%% as the most significant elements followed by padded zero elements
1339
1407
pad_bit_list(Size,BitListVal) ->
1340
1408
    Tail = lists:duplicate(Size,0),
1341
1409
    lists:append(BitListVal,Tail).
1342
 
 
1343
 
%%================================================================= 
1344
 
%% Do the actual encoding 
1345
 
%%     ([bitlist]) -> {ListLen, UnusedBits, OctetList} 
1346
 
%%================================================================= 
1347
 
 
1348
 
encode_bitstring([B8, B7, B6, B5, B4, B3, B2, B1 | Rest]) -> 
1349
 
    Val = (B8 bsl 7) bor (B7 bsl 6) bor (B6 bsl 5) bor (B5 bsl 4) bor 
1350
 
        (B4 bsl 3) bor (B3 bsl 2) bor (B2 bsl 1) bor B1, 
1351
 
    encode_bitstring(Rest, [Val], 1); 
1352
 
encode_bitstring(Val) -> 
1353
 
    {Unused, Octet} = unused_bitlist(Val, 7, 0), 
1354
 
    {1, Unused, [Octet]}. 
1355
 
 
1356
 
encode_bitstring([B8, B7, B6, B5, B4, B3, B2, B1 | Rest], Ack, Len) -> 
1357
 
    Val = (B8 bsl 7) bor (B7 bsl 6) bor (B6 bsl 5) bor (B5 bsl 4) bor 
1358
 
        (B4 bsl 3) bor (B3 bsl 2) bor (B2 bsl 1) bor B1, 
1359
 
    encode_bitstring(Rest, [Ack | [Val]], Len + 1); 
1360
 
%%even multiple of 8 bits.. 
1361
 
encode_bitstring([], Ack, Len) -> 
1362
 
    {Len, 0, Ack}; 
1363
 
%% unused bits in last octet 
1364
 
encode_bitstring(Rest, Ack, Len) -> 
1365
 
%    io:format("uneven ~w ~w ~w~n",[Rest, Ack, Len]), 
1366
 
    {Unused, Val} = unused_bitlist(Rest, 7, 0), 
1367
 
    {Len + 1, Unused, [Ack | [Val]]}. 
1368
 
 
1369
 
%%%%%%%%%%%%%%%%%% 
1370
 
%% unused_bitlist([list of ones and zeros <= 7], 7, []) -> 
1371
 
%%  {Unused bits, Last octet with bits moved to right} 
1372
 
unused_bitlist([], Trail, Ack) -> 
1373
 
    {Trail + 1, Ack}; 
1374
 
unused_bitlist([Bit | Rest], Trail, Ack) -> 
1375
 
%%    io:format("trail Bit: ~w Rest: ~w Trail: ~w Ack:~w~n",[Bit, Rest, Trail, Ack]), 
1376
 
    unused_bitlist(Rest, Trail - 1, (Bit bsl Trail) bor Ack). 
1377
 
 
1378
 
 
1379
 
%%============================================================================ 
1380
 
%% decode bitstring value 
1381
 
%%    (Buffer, Range, NamedNumberList, HasTag, TotalLen) -> {Integer, Remain, RemovedBytes}  
1382
 
%%============================================================================ 
 
1410
 
 
1411
%%=================================================================
 
1412
%% Do the actual encoding
 
1413
%%     ([bitlist]) -> {ListLen, UnusedBits, OctetList}
 
1414
%%=================================================================
 
1415
 
 
1416
encode_bitstring([B8, B7, B6, B5, B4, B3, B2, B1 | Rest]) ->
 
1417
    Val = (B8 bsl 7) bor (B7 bsl 6) bor (B6 bsl 5) bor (B5 bsl 4) bor
 
1418
        (B4 bsl 3) bor (B3 bsl 2) bor (B2 bsl 1) bor B1,
 
1419
    encode_bitstring(Rest, [Val], 1);
 
1420
encode_bitstring(Val) ->
 
1421
    {Unused, Octet} = unused_bitlist(Val, 7, 0),
 
1422
    {1, Unused, [Octet]}.
 
1423
 
 
1424
encode_bitstring([B8, B7, B6, B5, B4, B3, B2, B1 | Rest], Ack, Len) ->
 
1425
    Val = (B8 bsl 7) bor (B7 bsl 6) bor (B6 bsl 5) bor (B5 bsl 4) bor
 
1426
        (B4 bsl 3) bor (B3 bsl 2) bor (B2 bsl 1) bor B1,
 
1427
    encode_bitstring(Rest, [Ack | [Val]], Len + 1);
 
1428
%%even multiple of 8 bits..
 
1429
encode_bitstring([], Ack, Len) ->
 
1430
    {Len, 0, Ack};
 
1431
%% unused bits in last octet
 
1432
encode_bitstring(Rest, Ack, Len) ->
 
1433
%    io:format("uneven ~w ~w ~w~n",[Rest, Ack, Len]),
 
1434
    {Unused, Val} = unused_bitlist(Rest, 7, 0),
 
1435
    {Len + 1, Unused, [Ack | [Val]]}.
 
1436
 
 
1437
%%%%%%%%%%%%%%%%%%
 
1438
%% unused_bitlist([list of ones and zeros <= 7], 7, []) ->
 
1439
%%  {Unused bits, Last octet with bits moved to right}
 
1440
unused_bitlist([], Trail, Ack) ->
 
1441
    {Trail + 1, Ack};
 
1442
unused_bitlist([Bit | Rest], Trail, Ack) ->
 
1443
%%    io:format("trail Bit: ~w Rest: ~w Trail: ~w Ack:~w~n",[Bit, Rest, Trail, Ack]),
 
1444
    unused_bitlist(Rest, Trail - 1, (Bit bsl Trail) bor Ack).
 
1445
 
 
1446
 
 
1447
%%============================================================================
 
1448
%% decode bitstring value
 
1449
%%    (Buffer, Range, NamedNumberList, HasTag, TotalLen) -> {Integer, Remain, RemovedBytes}
 
1450
%%============================================================================
1383
1451
 
1384
1452
decode_compact_bit_string(Buffer, Range, NamedNumberList, Tags, LenIn, OptOrMand) ->
1385
1453
%    NewTags = new_tags(HasTag,#tag{class=?UNIVERSAL,number=?N_BIT_STRING}),
1386
 
     decode_restricted_string(Buffer, Range, ?N_BIT_STRING, Tags, LenIn, 
 
1454
     decode_restricted_string(Buffer, Range, ?N_BIT_STRING, Tags, LenIn,
1387
1455
                             NamedNumberList, OptOrMand,bin).
1388
1456
 
1389
 
decode_bit_string(Buffer, Range, NamedNumberList, Tags, LenIn, OptOrMand) -> 
 
1457
decode_bit_string(Buffer, Range, NamedNumberList, Tags, LenIn, OptOrMand) ->
1390
1458
%    NewTags = new_tags(HasTag,#tag{class=?UNIVERSAL,number=?N_BIT_STRING}),
1391
 
    decode_restricted_string(Buffer, Range, ?N_BIT_STRING, Tags, LenIn, 
1392
 
                             NamedNumberList, OptOrMand,old). 
1393
 
 
1394
 
 
1395
 
decode_bit_string2(1,<<0 ,Buffer/binary>>,_NamedNumberList,RemovedBytes,BinOrOld) -> 
 
1459
    decode_restricted_string(Buffer, Range, ?N_BIT_STRING, Tags, LenIn,
 
1460
                             NamedNumberList, OptOrMand,old).
 
1461
 
 
1462
 
 
1463
decode_bit_string2(1,<<0 ,Buffer/binary>>,_NamedNumberList,RemovedBytes,BinOrOld) ->
1396
1464
    case BinOrOld of
1397
1465
        bin ->
1398
1466
            {{0,<<>>},Buffer,RemovedBytes};
1400
1468
            {[], Buffer, RemovedBytes}
1401
1469
    end;
1402
1470
decode_bit_string2(Len,<<Unused,Buffer/binary>>,NamedNumberList,
1403
 
                   RemovedBytes,BinOrOld) -> 
 
1471
                   RemovedBytes,BinOrOld) ->
1404
1472
    L = Len - 1,
1405
1473
    <<Bits:L/binary,BufferTail/binary>> = Buffer,
1406
 
    case NamedNumberList of 
1407
 
        [] -> 
 
1474
    case NamedNumberList of
 
1475
        [] ->
1408
1476
            case BinOrOld of
1409
1477
                bin ->
1410
1478
                    {{Unused,Bits},BufferTail,RemovedBytes};
1412
1480
                    BitString = decode_bitstring2(L, Unused, Buffer),
1413
1481
                    {BitString,BufferTail, RemovedBytes}
1414
1482
            end;
1415
 
        _ -> 
 
1483
        _ ->
1416
1484
            BitString = decode_bitstring2(L, Unused, Buffer),
1417
 
            {decode_bitstring_NNL(BitString,NamedNumberList), 
1418
 
             BufferTail,  
1419
 
             RemovedBytes} 
1420
 
    end. 
1421
 
 
1422
 
%%---------------------------------------- 
1423
 
%% Decode the in buffer to bits 
1424
 
%%---------------------------------------- 
1425
 
decode_bitstring2(1,Unused,<<B7:1,B6:1,B5:1,B4:1,B3:1,B2:1,B1:1,B0:1,_/binary>>) -> 
1426
 
    lists:sublist([B7,B6,B5,B4,B3,B2,B1,B0],8-Unused); 
 
1485
            {decode_bitstring_NNL(BitString,NamedNumberList),
 
1486
             BufferTail,
 
1487
             RemovedBytes}
 
1488
    end.
 
1489
 
 
1490
%%----------------------------------------
 
1491
%% Decode the in buffer to bits
 
1492
%%----------------------------------------
 
1493
decode_bitstring2(1,Unused,<<B7:1,B6:1,B5:1,B4:1,B3:1,B2:1,B1:1,B0:1,_/binary>>) ->
 
1494
    lists:sublist([B7,B6,B5,B4,B3,B2,B1,B0],8-Unused);
1427
1495
decode_bitstring2(Len, Unused,
1428
 
                  <<B7:1,B6:1,B5:1,B4:1,B3:1,B2:1,B1:1,B0:1,Buffer/binary>>) -> 
1429
 
    [B7, B6, B5, B4, B3, B2, B1, B0 | 
1430
 
     decode_bitstring2(Len - 1, Unused, Buffer)]. 
1431
 
 
1432
 
%%decode_bitstring2(1, Unused, Buffer) -> 
1433
 
%%    make_bits_of_int(hd(Buffer), 128, 8-Unused); 
1434
 
%%decode_bitstring2(Len, Unused, [BitVal | Buffer]) -> 
1435
 
%%    [B7, B6, B5, B4, B3, B2, B1, B0] = make_bits_of_int(BitVal, 128, 8), 
1436
 
%%    [B7, B6, B5, B4, B3, B2, B1, B0 | 
1437
 
%%     decode_bitstring2(Len - 1, Unused, Buffer)]. 
1438
 
 
1439
 
 
1440
 
%%make_bits_of_int(_, _, 0) -> 
1441
 
%%    []; 
1442
 
%%make_bits_of_int(BitVal, MaskVal, Unused) when Unused > 0 -> 
1443
 
%%    X = case MaskVal band BitVal of 
1444
 
%%          0 -> 0 ; 
1445
 
%%          _ -> 1 
1446
 
%%      end, 
1447
 
%%    [X | make_bits_of_int(BitVal, MaskVal bsr 1, Unused - 1)]. 
1448
 
 
1449
 
 
1450
 
 
1451
 
%%---------------------------------------- 
1452
 
%% Decode the bitlist to names 
1453
 
%%---------------------------------------- 
1454
 
 
1455
 
 
1456
 
decode_bitstring_NNL(BitList,NamedNumberList) -> 
1457
 
    decode_bitstring_NNL(BitList,NamedNumberList,0,[]). 
1458
 
 
1459
 
 
1460
 
decode_bitstring_NNL([],_,_No,Result) -> 
1461
 
    lists:reverse(Result); 
1462
 
 
1463
 
decode_bitstring_NNL([B|BitList],[{Name,No}|NamedNumberList],No,Result) -> 
1464
 
    if 
1465
 
        B == 0 -> 
1466
 
            decode_bitstring_NNL(BitList,NamedNumberList,No+1,Result); 
1467
 
        true -> 
1468
 
            decode_bitstring_NNL(BitList,NamedNumberList,No+1,[Name|Result]) 
1469
 
    end; 
1470
 
decode_bitstring_NNL([1|BitList],NamedNumberList,No,Result) -> 
1471
 
            decode_bitstring_NNL(BitList,NamedNumberList,No+1,[{bit,No}|Result]); 
 
1496
                  <<B7:1,B6:1,B5:1,B4:1,B3:1,B2:1,B1:1,B0:1,Buffer/binary>>) ->
 
1497
    [B7, B6, B5, B4, B3, B2, B1, B0 |
 
1498
     decode_bitstring2(Len - 1, Unused, Buffer)].
 
1499
 
 
1500
%%decode_bitstring2(1, Unused, Buffer) ->
 
1501
%%    make_bits_of_int(hd(Buffer), 128, 8-Unused);
 
1502
%%decode_bitstring2(Len, Unused, [BitVal | Buffer]) ->
 
1503
%%    [B7, B6, B5, B4, B3, B2, B1, B0] = make_bits_of_int(BitVal, 128, 8),
 
1504
%%    [B7, B6, B5, B4, B3, B2, B1, B0 |
 
1505
%%     decode_bitstring2(Len - 1, Unused, Buffer)].
 
1506
 
 
1507
 
 
1508
%%make_bits_of_int(_, _, 0) ->
 
1509
%%    [];
 
1510
%%make_bits_of_int(BitVal, MaskVal, Unused) when Unused > 0 ->
 
1511
%%    X = case MaskVal band BitVal of
 
1512
%%          0 -> 0 ;
 
1513
%%          _ -> 1
 
1514
%%      end,
 
1515
%%    [X | make_bits_of_int(BitVal, MaskVal bsr 1, Unused - 1)].
 
1516
 
 
1517
 
 
1518
 
 
1519
%%----------------------------------------
 
1520
%% Decode the bitlist to names
 
1521
%%----------------------------------------
 
1522
 
 
1523
 
 
1524
decode_bitstring_NNL(BitList,NamedNumberList) ->
 
1525
    decode_bitstring_NNL(BitList,NamedNumberList,0,[]).
 
1526
 
 
1527
 
 
1528
decode_bitstring_NNL([],_,_No,Result) ->
 
1529
    lists:reverse(Result);
 
1530
 
 
1531
decode_bitstring_NNL([B|BitList],[{Name,No}|NamedNumberList],No,Result) ->
 
1532
    if
 
1533
        B == 0 ->
 
1534
            decode_bitstring_NNL(BitList,NamedNumberList,No+1,Result);
 
1535
        true ->
 
1536
            decode_bitstring_NNL(BitList,NamedNumberList,No+1,[Name|Result])
 
1537
    end;
 
1538
decode_bitstring_NNL([1|BitList],NamedNumberList,No,Result) ->
 
1539
            decode_bitstring_NNL(BitList,NamedNumberList,No+1,[{bit,No}|Result]);
1472
1540
decode_bitstring_NNL([0|BitList],NamedNumberList,No,Result) ->
1473
 
            decode_bitstring_NNL(BitList,NamedNumberList,No+1,Result). 
1474
 
 
1475
 
 
1476
 
%%============================================================================ 
1477
 
%% Octet string, ITU_T X.690 Chapter 8.7 
 
1541
            decode_bitstring_NNL(BitList,NamedNumberList,No+1,Result).
 
1542
 
 
1543
 
 
1544
%%============================================================================
 
1545
%% Octet string, ITU_T X.690 Chapter 8.7
1478
1546
%%
1479
 
%% encode octet string 
 
1547
%% encode octet string
1480
1548
%% The OctetList must be a flat list of integers in the range 0..255
1481
1549
%% the function does not check this because it takes to much time
1482
 
%%============================================================================ 
1483
 
encode_octet_string(_C, OctetList, []) when binary(OctetList) -> 
 
1550
%%============================================================================
 
1551
encode_octet_string(_C, OctetList, []) when binary(OctetList) ->
1484
1552
    dotag_universal(?N_OCTET_STRING,OctetList,size(OctetList));
1485
 
encode_octet_string(_C, OctetList, DoTag) when binary(OctetList) -> 
 
1553
encode_octet_string(_C, OctetList, DoTag) when binary(OctetList) ->
1486
1554
    dotag(DoTag, ?N_OCTET_STRING, {OctetList,size(OctetList)});
1487
 
encode_octet_string(_C, OctetList, DoTag) when list(OctetList) -> 
 
1555
encode_octet_string(_C, OctetList, DoTag) when list(OctetList) ->
1488
1556
    case length(OctetList) of
1489
1557
        Len when DoTag == [] ->
1490
1558
            dotag_universal(?N_OCTET_STRING,OctetList,Len);
1491
1559
        Len ->
1492
1560
            dotag(DoTag, ?N_OCTET_STRING, {OctetList,Len})
1493
1561
    end;
1494
 
% encode_octet_string(C, OctetList, DoTag) when list(OctetList) -> 
 
1562
% encode_octet_string(C, OctetList, DoTag) when list(OctetList) ->
1495
1563
%     dotag(DoTag, ?N_OCTET_STRING, {OctetList,length(OctetList)});
1496
 
encode_octet_string(C, {Name,OctetList}, DoTag) when atom(Name) -> 
 
1564
encode_octet_string(C, {Name,OctetList}, DoTag) when atom(Name) ->
1497
1565
    encode_octet_string(C, OctetList, DoTag).
1498
 
 
1499
 
 
1500
 
%%============================================================================ 
1501
 
%% decode octet string  
1502
 
%%    (Buffer, Range, HasTag, TotalLen) -> {String, Remain, RemovedBytes}  
1503
 
%% 
1504
 
%% Octet string is decoded as a restricted string 
1505
 
%%============================================================================ 
1506
 
decode_octet_string(Buffer, Range, Tags, TotalLen, OptOrMand) -> 
 
1566
 
 
1567
 
 
1568
%%============================================================================
 
1569
%% decode octet string
 
1570
%%    (Buffer, Range, HasTag, TotalLen) -> {String, Remain, RemovedBytes}
 
1571
%%
 
1572
%% Octet string is decoded as a restricted string
 
1573
%%============================================================================
 
1574
decode_octet_string(Buffer, Range, Tags, TotalLen, OptOrMand) ->
1507
1575
%    NewTags = new_tags(HasTag,#tag{class=?UNIVERSAL,number=?N_OCTET_STRING}),
1508
 
    decode_restricted_string(Buffer, Range, ?N_OCTET_STRING, 
1509
 
                             Tags, TotalLen, [], OptOrMand,old). 
 
1576
    decode_restricted_string(Buffer, Range, ?N_OCTET_STRING,
 
1577
                             Tags, TotalLen, [], OptOrMand,old).
1510
1578
 
1511
 
%%============================================================================ 
1512
 
%% Null value, ITU_T X.690 Chapter 8.8 
 
1579
%%============================================================================
 
1580
%% Null value, ITU_T X.690 Chapter 8.8
1513
1581
%%
1514
 
%% encode NULL value 
1515
 
%%============================================================================ 
1516
 
 
1517
 
encode_null(_, []) -> 
 
1582
%% encode NULL value
 
1583
%%============================================================================
 
1584
 
 
1585
encode_null(_, []) ->
1518
1586
    {[?N_NULL,0],2};
1519
 
encode_null(_, DoTag) -> 
1520
 
    dotag(DoTag, ?N_NULL, {[],0}). 
1521
 
 
1522
 
%%============================================================================ 
1523
 
%% decode NULL value 
1524
 
%%    (Buffer, HasTag, TotalLen) -> {NULL, Remain, RemovedBytes}  
1525
 
%%============================================================================ 
 
1587
encode_null(_, DoTag) ->
 
1588
    dotag(DoTag, ?N_NULL, {[],0}).
 
1589
 
 
1590
%%============================================================================
 
1591
%% decode NULL value
 
1592
%%    (Buffer, HasTag, TotalLen) -> {NULL, Remain, RemovedBytes}
 
1593
%%============================================================================
1526
1594
decode_null(Buffer, Tags, OptOrMand) ->
1527
1595
    NewTags = new_tags(Tags,#tag{class=?UNIVERSAL,number=?N_NULL}),
1528
1596
    decode_null_notag(Buffer, NewTags, OptOrMand).
1529
1597
 
1530
1598
decode_null_notag(Buffer, Tags, OptOrMand) ->
1531
 
    {RestTags, {FormLen, Buffer0, Rb0}} = 
 
1599
    {RestTags, {FormLen, Buffer0, Rb0}} =
1532
1600
        check_tags_i(Tags, Buffer, OptOrMand),
1533
1601
 
1534
1602
    case FormLen of
1535
1603
        {?CONSTRUCTED,Len} ->
1536
1604
            {_Buffer00,RestBytes} = split_list(Buffer0,Len),
1537
 
            {Val01, Buffer01, Rb01} = decode_null_notag(Buffer0, RestTags, 
 
1605
            {Val01, Buffer01, Rb01} = decode_null_notag(Buffer0, RestTags,
1538
1606
                                                        OptOrMand),
1539
1607
            {Buffer02, Rb02} = restbytes2(RestBytes,Buffer01,noext),
1540
1608
            {Val01, Buffer02, Rb0+Rb01+Rb02};
1542
1610
            {'NULL', Buffer0, Rb0};
1543
1611
        {_,Len} ->
1544
1612
            exit({error,{asn1,{invalid_length,'NULL',Len}}})
1545
 
    end. 
1546
 
 
1547
 
 
1548
 
%%============================================================================ 
1549
 
%% Object identifier, ITU_T X.690 Chapter 8.19 
 
1613
    end.
 
1614
 
 
1615
 
 
1616
%%============================================================================
 
1617
%% Object identifier, ITU_T X.690 Chapter 8.19
1550
1618
%%
1551
 
%% encode Object Identifier value 
1552
 
%%============================================================================ 
1553
 
 
1554
 
encode_object_identifier({Name,Val}, DoTag) when atom(Name) -> 
 
1619
%% encode Object Identifier value
 
1620
%%============================================================================
 
1621
 
 
1622
encode_object_identifier({Name,Val}, DoTag) when atom(Name) ->
1555
1623
    encode_object_identifier(Val, DoTag);
1556
 
encode_object_identifier(Val, []) -> 
 
1624
encode_object_identifier(Val, []) ->
1557
1625
    {EncVal,Len} = e_object_identifier(Val),
1558
1626
    dotag_universal(?N_OBJECT_IDENTIFIER,EncVal,Len);
1559
 
encode_object_identifier(Val, DoTag) -> 
 
1627
encode_object_identifier(Val, DoTag) ->
1560
1628
    dotag(DoTag, ?N_OBJECT_IDENTIFIER, e_object_identifier(Val)).
1561
 
 
1562
 
e_object_identifier({'OBJECT IDENTIFIER', V}) -> 
1563
 
    e_object_identifier(V); 
1564
 
e_object_identifier({Cname, V}) when atom(Cname), tuple(V) -> 
1565
 
    e_object_identifier(tuple_to_list(V)); 
1566
 
e_object_identifier({Cname, V}) when atom(Cname), list(V) -> 
1567
 
    e_object_identifier(V); 
1568
 
e_object_identifier(V) when tuple(V) -> 
1569
 
    e_object_identifier(tuple_to_list(V)); 
1570
 
 
1571
 
%%%%%%%%%%%%%%% 
1572
 
%% e_object_identifier([List of Obect Identifiers]) -> 
1573
 
%% {[Encoded Octetlist of ObjIds], IntLength} 
1574
 
%% 
1575
 
e_object_identifier([E1, E2 | Tail]) -> 
1576
 
    Head = 40*E1 + E2,  % wow! 
 
1629
 
 
1630
e_object_identifier({'OBJECT IDENTIFIER', V}) ->
 
1631
    e_object_identifier(V);
 
1632
e_object_identifier({Cname, V}) when atom(Cname), tuple(V) ->
 
1633
    e_object_identifier(tuple_to_list(V));
 
1634
e_object_identifier({Cname, V}) when atom(Cname), list(V) ->
 
1635
    e_object_identifier(V);
 
1636
e_object_identifier(V) when tuple(V) ->
 
1637
    e_object_identifier(tuple_to_list(V));
 
1638
 
 
1639
%%%%%%%%%%%%%%%
 
1640
%% e_object_identifier([List of Obect Identifiers]) ->
 
1641
%% {[Encoded Octetlist of ObjIds], IntLength}
 
1642
%%
 
1643
e_object_identifier([E1, E2 | Tail]) ->
 
1644
    Head = 40*E1 + E2,  % wow!
1577
1645
    {H,Lh} = mk_object_val(Head),
1578
1646
    {R,Lr} = enc_obj_id_tail(Tail, [], 0),
1579
1647
    {[H|R], Lh+Lr}.
1584
1652
    {B, L} = mk_object_val(H),
1585
1653
    enc_obj_id_tail(T, [B|Ack], Len+L).
1586
1654
 
1587
 
%% e_object_identifier([List of Obect Identifiers]) -> 
1588
 
%% {[Encoded Octetlist of ObjIds], IntLength} 
1589
 
%% 
1590
 
%%e_object_identifier([E1, E2 | Tail]) -> 
1591
 
%%    Head = 40*E1 + E2,  % wow! 
1592
 
%%    F = fun(Val, AckLen) -> 
1593
 
%%              {L, Ack} = mk_object_val(Val), 
1594
 
%%              {L, Ack + AckLen} 
1595
 
%%      end, 
1596
 
%%    {Octets, Len} = lists:mapfoldl(F, 0, [Head | Tail]).
1597
 
 
1598
 
%%%%%%%%%%% 
1599
 
%% mk_object_val(Value) -> {OctetList, Len} 
1600
 
%% returns a Val as a list of octets, the 8 bit is allways set to one except 
1601
 
%% for the last octet, where its 0 
1602
 
%% 
1603
 
 
1604
 
 
1605
 
mk_object_val(Val) when Val =< 127 -> 
1606
 
    {[255 band Val], 1}; 
1607
 
mk_object_val(Val) -> 
1608
 
    mk_object_val(Val bsr 7, [Val band 127], 1).  
1609
 
mk_object_val(0, Ack, Len) -> 
1610
 
    {Ack, Len}; 
1611
 
mk_object_val(Val, Ack, Len) -> 
1612
 
    mk_object_val(Val bsr 7, [((Val band 127) bor 128) | Ack], Len + 1). 
1613
 
 
1614
 
 
1615
 
 
1616
 
%%============================================================================ 
1617
 
%% decode Object Identifier value   
1618
 
%%    (Buffer, HasTag, TotalLen) -> {{ObjId}, Remain, RemovedBytes}  
1619
 
%%============================================================================ 
1620
 
 
1621
 
decode_object_identifier(Buffer, Tags, OptOrMand) -> 
 
1655
 
 
1656
%%%%%%%%%%%
 
1657
%% mk_object_val(Value) -> {OctetList, Len}
 
1658
%% returns a Val as a list of octets, the 8 bit is allways set to one except
 
1659
%% for the last octet, where its 0
 
1660
%%
 
1661
 
 
1662
 
 
1663
mk_object_val(Val) when Val =< 127 ->
 
1664
    {[255 band Val], 1};
 
1665
mk_object_val(Val) ->
 
1666
    mk_object_val(Val bsr 7, [Val band 127], 1).
 
1667
mk_object_val(0, Ack, Len) ->
 
1668
    {Ack, Len};
 
1669
mk_object_val(Val, Ack, Len) ->
 
1670
    mk_object_val(Val bsr 7, [((Val band 127) bor 128) | Ack], Len + 1).
 
1671
 
 
1672
 
 
1673
 
 
1674
%%============================================================================
 
1675
%% decode Object Identifier value
 
1676
%%    (Buffer, HasTag, TotalLen) -> {{ObjId}, Remain, RemovedBytes}
 
1677
%%============================================================================
 
1678
 
 
1679
decode_object_identifier(Buffer, Tags, OptOrMand) ->
1622
1680
    NewTags = new_tags(Tags,#tag{class=?UNIVERSAL,
1623
1681
                                 number=?N_OBJECT_IDENTIFIER}),
1624
1682
    decode_object_identifier_notag(Buffer, NewTags, OptOrMand).
1625
1683
 
1626
 
decode_object_identifier_notag(Buffer, Tags, OptOrMand) -> 
1627
 
    {RestTags, {FormLen, Buffer0, Rb0}} = 
 
1684
decode_object_identifier_notag(Buffer, Tags, OptOrMand) ->
 
1685
    {RestTags, {FormLen, Buffer0, Rb0}} =
1628
1686
        check_tags_i(Tags, Buffer, OptOrMand),
1629
1687
 
1630
1688
    case FormLen of
1631
1689
        {?CONSTRUCTED,Len} ->
1632
1690
            {Buffer00,RestBytes} = split_list(Buffer0,Len),
1633
 
            {Val01, Buffer01, Rb01} = 
1634
 
                decode_object_identifier_notag(Buffer00, 
 
1691
            {Val01, Buffer01, Rb01} =
 
1692
                decode_object_identifier_notag(Buffer00,
1635
1693
                                               RestTags, OptOrMand),
1636
1694
            {Buffer02, Rb02} = restbytes2(RestBytes,Buffer01,noext),
1637
1695
            {Val01, Buffer02, Rb0+Rb01+Rb02};
1638
1696
        {_,Len} ->
1639
 
            {[AddedObjVal|ObjVals],Buffer01} = 
1640
 
                dec_subidentifiers(Buffer0,0,[],Len), 
1641
 
            {Val1, Val2} = if 
1642
 
                               AddedObjVal < 40 -> 
1643
 
                                   {0, AddedObjVal}; 
1644
 
                               AddedObjVal < 80 -> 
1645
 
                                   {1, AddedObjVal - 40}; 
1646
 
                               true -> 
1647
 
                                   {2, AddedObjVal - 80} 
1648
 
                           end, 
1649
 
            {list_to_tuple([Val1, Val2 | ObjVals]), Buffer01, 
 
1697
            {[AddedObjVal|ObjVals],Buffer01} =
 
1698
                dec_subidentifiers(Buffer0,0,[],Len),
 
1699
            {Val1, Val2} = if
 
1700
                               AddedObjVal < 40 ->
 
1701
                                   {0, AddedObjVal};
 
1702
                               AddedObjVal < 80 ->
 
1703
                                   {1, AddedObjVal - 40};
 
1704
                               true ->
 
1705
                                   {2, AddedObjVal - 80}
 
1706
                           end,
 
1707
            {list_to_tuple([Val1, Val2 | ObjVals]), Buffer01,
1650
1708
             Rb0+Len}
1651
 
    end. 
1652
 
 
1653
 
dec_subidentifiers(Buffer,_Av,Al,0) -> 
1654
 
    {lists:reverse(Al),Buffer}; 
1655
 
dec_subidentifiers(<<1:1,H:7,T/binary>>,Av,Al,Len) -> 
1656
 
    dec_subidentifiers(T,(Av bsl 7) + H,Al,Len-1); 
1657
 
dec_subidentifiers(<<H,T/binary>>,Av,Al,Len) -> 
1658
 
    dec_subidentifiers(T,0,[((Av bsl 7) + H)|Al],Len-1). 
1659
 
 
1660
 
 
1661
 
%%dec_subidentifiers(Buffer,Av,Al,0) -> 
1662
 
%%    {lists:reverse(Al),Buffer}; 
1663
 
%%dec_subidentifiers([H|T],Av,Al,Len) when H >=16#80 -> 
1664
 
%%    dec_subidentifiers(T,(Av bsl 7) + (H band 16#7F),Al,Len-1); 
1665
 
%%dec_subidentifiers([H|T],Av,Al,Len) -> 
1666
 
%%    dec_subidentifiers(T,0,[(Av bsl 7) + H |Al],Len-1). 
1667
 
 
1668
 
 
1669
 
%%============================================================================ 
1670
 
%% Restricted character string types, ITU_T X.690 Chapter 8.20 
1671
 
%%
1672
 
%% encode Numeric Printable Teletex Videotex Visible IA5 Graphic General strings 
1673
 
%%============================================================================ 
1674
 
encode_restricted_string(_C, OctetList, StringType, []) 
1675
 
  when binary(OctetList) -> 
 
1709
    end.
 
1710
 
 
1711
dec_subidentifiers(Buffer,_Av,Al,0) ->
 
1712
    {lists:reverse(Al),Buffer};
 
1713
dec_subidentifiers(<<1:1,H:7,T/binary>>,Av,Al,Len) ->
 
1714
    dec_subidentifiers(T,(Av bsl 7) + H,Al,Len-1);
 
1715
dec_subidentifiers(<<H,T/binary>>,Av,Al,Len) ->
 
1716
    dec_subidentifiers(T,0,[((Av bsl 7) + H)|Al],Len-1).
 
1717
 
 
1718
%%============================================================================
 
1719
%% RELATIVE-OID, ITU_T X.690 Chapter 8.20
 
1720
%%
 
1721
%% encode Relative Object Identifier
 
1722
%%============================================================================
 
1723
encode_relative_oid({Name,Val},TagIn) when is_atom(Name) ->
 
1724
    encode_relative_oid(Val,TagIn);
 
1725
encode_relative_oid(Val,TagIn) when is_tuple(Val) ->
 
1726
    encode_relative_oid(tuple_to_list(Val),TagIn);
 
1727
encode_relative_oid(Val,[]) ->
 
1728
    {EncVal,Len} = enc_relative_oid(Val),
 
1729
    dotag_universal(?'N_RELATIVE-OID',EncVal,Len);
 
1730
encode_relative_oid(Val, DoTag) ->
 
1731
    dotag(DoTag, ?'N_RELATIVE-OID', enc_relative_oid(Val)).
 
1732
 
 
1733
enc_relative_oid(Val) ->
 
1734
    lists:mapfoldl(fun(X,AccIn) ->
 
1735
                           {SO,L}=mk_object_val(X),
 
1736
                           {SO,L+AccIn}
 
1737
                   end
 
1738
                   ,0,Val).
 
1739
 
 
1740
%%============================================================================
 
1741
%% decode Relative Object Identifier value
 
1742
%%    (Buffer, HasTag, TotalLen) -> {{ObjId}, Remain, RemovedBytes}
 
1743
%%============================================================================
 
1744
decode_relative_oid(Buffer, Tags, OptOrMand) ->
 
1745
    NewTags = new_tags(Tags,#tag{class=?UNIVERSAL,
 
1746
                                 number=?'N_RELATIVE-OID'}),
 
1747
    decode_relative_oid_notag(Buffer, NewTags, OptOrMand).
 
1748
 
 
1749
decode_relative_oid_notag(Buffer, Tags, OptOrMand) ->
 
1750
    {_RestTags, {_FormLen={_,Len}, Buffer0, Rb0}} =
 
1751
        check_tags_i(Tags, Buffer, OptOrMand),
 
1752
    {ObjVals,Buffer01} =
 
1753
        dec_subidentifiers(Buffer0,0,[],Len),
 
1754
    {list_to_tuple(ObjVals), Buffer01, Rb0+Len}.
 
1755
 
 
1756
%%============================================================================
 
1757
%% Restricted character string types, ITU_T X.690 Chapter 8.21
 
1758
%%
 
1759
%% encode Numeric Printable Teletex Videotex Visible IA5 Graphic General strings
 
1760
%%============================================================================
 
1761
encode_restricted_string(_C, OctetList, StringType, [])
 
1762
  when binary(OctetList) ->
1676
1763
    dotag_universal(StringType,OctetList,size(OctetList));
1677
 
encode_restricted_string(_C, OctetList, StringType, DoTag) 
1678
 
  when binary(OctetList) -> 
 
1764
encode_restricted_string(_C, OctetList, StringType, DoTag)
 
1765
  when binary(OctetList) ->
1679
1766
    dotag(DoTag, StringType, {OctetList, size(OctetList)});
1680
 
encode_restricted_string(_C, OctetList, StringType, []) 
 
1767
encode_restricted_string(_C, OctetList, StringType, [])
1681
1768
  when list(OctetList) ->
1682
1769
    dotag_universal(StringType,OctetList,length(OctetList));
1683
 
encode_restricted_string(_C, OctetList, StringType, DoTag) 
 
1770
encode_restricted_string(_C, OctetList, StringType, DoTag)
1684
1771
  when list(OctetList) ->
1685
 
    dotag(DoTag, StringType, {OctetList, length(OctetList)}); 
1686
 
encode_restricted_string(C,{Name,OctetL},StringType,DoTag) when atom(Name)-> 
 
1772
    dotag(DoTag, StringType, {OctetList, length(OctetList)});
 
1773
encode_restricted_string(C,{Name,OctetL},StringType,DoTag) when atom(Name)->
1687
1774
    encode_restricted_string(C, OctetL, StringType, DoTag).
1688
1775
 
1689
 
%%============================================================================ 
1690
 
%% decode Numeric Printable Teletex Videotex Visible IA5 Graphic General strings 
1691
 
%%    (Buffer, Range, StringType, HasTag, TotalLen) -> 
1692
 
%%                                  {String, Remain, RemovedBytes}  
1693
 
%%============================================================================ 
 
1776
%%============================================================================
 
1777
%% decode Numeric Printable Teletex Videotex Visible IA5 Graphic General strings
 
1778
%%    (Buffer, Range, StringType, HasTag, TotalLen) ->
 
1779
%%                                  {String, Remain, RemovedBytes}
 
1780
%%============================================================================
1694
1781
 
1695
 
decode_restricted_string(Buffer, Range, StringType, Tags, LenIn, OptOrMand) -> 
1696
 
    {Val,Buffer2,Rb} = 
1697
 
        decode_restricted_string_tag(Buffer, Range, StringType, Tags, 
 
1782
decode_restricted_string(Buffer, Range, StringType, Tags, LenIn, OptOrMand) ->
 
1783
    {Val,Buffer2,Rb} =
 
1784
        decode_restricted_string_tag(Buffer, Range, StringType, Tags,
1698
1785
                                  LenIn, [], OptOrMand,old),
1699
1786
    {check_and_convert_restricted_string(Val,StringType,Range,[],old),
1700
 
     Buffer2,Rb}. 
1701
 
 
1702
 
 
1703
 
decode_restricted_string(Buffer, Range, StringType, Tags, LenIn, NNList, OptOrMand, BinOrOld ) -> 
1704
 
    {Val,Buffer2,Rb} = 
1705
 
        decode_restricted_string_tag(Buffer, Range, StringType, Tags, 
 
1787
     Buffer2,Rb}.
 
1788
 
 
1789
 
 
1790
decode_restricted_string(Buffer, Range, StringType, Tags, LenIn, NNList, OptOrMand, BinOrOld ) ->
 
1791
    {Val,Buffer2,Rb} =
 
1792
        decode_restricted_string_tag(Buffer, Range, StringType, Tags,
1706
1793
                             LenIn, NNList, OptOrMand, BinOrOld),
1707
1794
    {check_and_convert_restricted_string(Val,StringType,Range,NNList,BinOrOld),
1708
 
     Buffer2,Rb}. 
1709
 
 
1710
 
decode_restricted_string_tag(Buffer, Range, StringType, TagsIn, LenIn, NNList, OptOrMand, BinOrOld ) -> 
 
1795
     Buffer2,Rb}.
 
1796
 
 
1797
decode_restricted_string_tag(Buffer, Range, StringType, TagsIn, LenIn, NNList, OptOrMand, BinOrOld ) ->
1711
1798
    NewTags = new_tags(TagsIn, #tag{class=?UNIVERSAL,number=StringType}),
1712
 
    decode_restricted_string_notag(Buffer, Range, StringType, NewTags, 
 
1799
    decode_restricted_string_notag(Buffer, Range, StringType, NewTags,
1713
1800
                                   LenIn, NNList, OptOrMand, BinOrOld).
1714
1801
 
1715
 
 
 
1802
 
1716
1803
 
1717
1804
 
1718
1805
check_and_convert_restricted_string(Val,StringType,Range,NamedNumberList,_BinOrOld) ->
1721
1808
                              {no_check,Val};
1722
1809
                          ?N_BIT_STRING when list(Val) ->
1723
1810
                              {length(Val),Val};
1724
 
                          ?N_BIT_STRING when tuple(Val) -> 
 
1811
                          ?N_BIT_STRING when tuple(Val) ->
1725
1812
                              {(size(element(2,Val))*8) - element(1,Val),Val};
1726
1813
                          _ when binary(Val) ->
1727
1814
                              {size(Val),binary_to_list(Val)};
1739
1826
            NewVal;
1740
1827
        {{Lb,_Ub},_Ext=[MinExt|_]} when StrLen >= Lb; StrLen >= MinExt ->
1741
1828
            NewVal;
1742
 
        {{Lb1,Ub1},{Lb2,Ub2}} when StrLen >= Lb1, StrLen =< Ub1; 
 
1829
        {{Lb1,Ub1},{Lb2,Ub2}} when StrLen >= Lb1, StrLen =< Ub1;
1743
1830
                                   StrLen =< Ub2, StrLen >= Lb2 ->
1744
1831
            NewVal;
1745
1832
        StrLen -> % fixed length constraint
1746
1833
            NewVal;
1747
 
        {_,_} -> 
 
1834
        {_,_} ->
1748
1835
            exit({error,{asn1,{length,Range,Val}}});
1749
1836
        _Len when integer(_Len) ->
1750
1837
            exit({error,{asn1,{length,Range,Val}}});
1755
1842
 
1756
1843
%%=============================================================================
1757
1844
%% Common routines for several string types including bit string
1758
 
%% handles indefinite length 
 
1845
%% handles indefinite length
1759
1846
%%=============================================================================
1760
1847
 
1761
1848
 
1762
 
decode_restricted_string_notag(Buffer, _Range, StringType, TagsIn, 
1763
 
                         _, NamedNumberList, OptOrMand,BinOrOld) -> 
1764
 
    %%----------------------------------------------------------- 
1765
 
    %% Get inner (the implicit tag or no tag) and  
1766
 
    %%     outer (the explicit tag) lengths. 
1767
 
    %%----------------------------------------------------------- 
1768
 
    {RestTags, {FormLength={_,_Len01}, Buffer0, Rb0}} = 
 
1849
decode_restricted_string_notag(Buffer, _Range, StringType, TagsIn,
 
1850
                         _, NamedNumberList, OptOrMand,BinOrOld) ->
 
1851
    %%-----------------------------------------------------------
 
1852
    %% Get inner (the implicit tag or no tag) and
 
1853
    %%     outer (the explicit tag) lengths.
 
1854
    %%-----------------------------------------------------------
 
1855
    {RestTags, {FormLength={_,_Len01}, Buffer0, Rb0}} =
1769
1856
        check_tags_i(TagsIn, Buffer, OptOrMand),
1770
1857
 
1771
1858
    case FormLength of
1772
1859
        {?CONSTRUCTED,Len} ->
1773
1860
            {Buffer00, RestBytes} = split_list(Buffer0,Len),
1774
 
            {Val01, Buffer01, Rb01} = 
1775
 
                decode_restricted_parts(Buffer00, RestBytes, [], StringType, 
 
1861
            {Val01, Buffer01, Rb01} =
 
1862
                decode_restricted_parts(Buffer00, RestBytes, [], StringType,
1776
1863
                                        RestTags,
1777
 
                                        Len, NamedNumberList, 
1778
 
                                        OptOrMand, 
 
1864
                                        Len, NamedNumberList,
 
1865
                                        OptOrMand,
1779
1866
                                        BinOrOld, 0, []),
1780
1867
            {Val01, Buffer01, Rb0+Rb01};
1781
1868
        {_, Len} ->
1782
 
            {Val01, Buffer01, Rb01} = 
1783
 
                decode_restricted(Buffer0, Len, StringType, 
 
1869
            {Val01, Buffer01, Rb01} =
 
1870
                decode_restricted(Buffer0, Len, StringType,
1784
1871
                                  NamedNumberList, BinOrOld),
1785
1872
            {Val01, Buffer01, Rb0+Rb01}
1786
1873
    end.
1787
1874
 
1788
1875
 
1789
 
decode_restricted_parts(Buffer, RestBytes, [], StringType, RestTags, Len, NNList, 
 
1876
decode_restricted_parts(Buffer, RestBytes, [], StringType, RestTags, Len, NNList,
1790
1877
                        OptOrMand, BinOrOld, AccRb, AccVal) ->
1791
1878
    DecodeFun = case RestTags of
1792
1879
                    [] -> fun decode_restricted_string_tag/8;
1793
1880
                    _ -> fun decode_restricted_string_notag/8
1794
1881
                end,
1795
 
    {Val, Buffer1, Rb} = 
1796
 
        DecodeFun(Buffer, [], StringType, RestTags, 
1797
 
                  no_length, NNList, 
 
1882
    {Val, Buffer1, Rb} =
 
1883
        DecodeFun(Buffer, [], StringType, RestTags,
 
1884
                  no_length, NNList,
1798
1885
                  OptOrMand, BinOrOld),
1799
 
    {Buffer2,More} = 
 
1886
    {Buffer2,More} =
1800
1887
        case Buffer1 of
1801
1888
            <<0,0,Buffer10/binary>> when Len == indefinite ->
1802
1889
                {Buffer10,false};
1812
1899
            _ when binary(Val),binary(AccVal) ->
1813
1900
                {<<AccVal/binary,Val/binary>>,AccRb+Rb};
1814
1901
            _ when binary(Val), AccVal==[] ->
1815
 
                {Val,AccRb+Rb};                               
1816
 
            _ ->        
 
1902
                {Val,AccRb+Rb};
 
1903
            _ ->
1817
1904
                {AccVal++Val, AccRb+Rb}
1818
1905
        end,
1819
1906
    case More of
1820
1907
        false ->
1821
1908
            {NewVal, Buffer2, NewRb};
1822
1909
        true ->
1823
 
            decode_restricted_parts(Buffer2, RestBytes, [], StringType, RestTags, Len, NNList, 
 
1910
            decode_restricted_parts(Buffer2, RestBytes, [], StringType, RestTags, Len, NNList,
1824
1911
                                    OptOrMand, BinOrOld, NewRb, NewVal)
1825
1912
    end.
1826
1913
 
1827
 
    
1828
 
 
1829
 
decode_restricted(Buffer, InnerLen, StringType, NamedNumberList,BinOrOld) -> 
1830
 
    
1831
 
    case StringType of 
1832
 
        ?N_BIT_STRING -> 
1833
 
            decode_bit_string2(InnerLen,Buffer,NamedNumberList,InnerLen,BinOrOld); 
1834
 
        
 
1914
 
 
1915
 
 
1916
decode_restricted(Buffer, InnerLen, StringType, NamedNumberList,BinOrOld) ->
 
1917
 
 
1918
    case StringType of
 
1919
        ?N_BIT_STRING ->
 
1920
            decode_bit_string2(InnerLen,Buffer,NamedNumberList,InnerLen,BinOrOld);
 
1921
 
1835
1922
        ?N_UniversalString ->
1836
1923
            <<PreBuff:InnerLen/binary,RestBuff/binary>> = Buffer,%%added for binary
1837
 
            UniString = mk_universal_string(binary_to_list(PreBuff)), 
1838
 
            {UniString,RestBuff,InnerLen}; 
1839
 
        ?N_BMPString ->  
 
1924
            UniString = mk_universal_string(binary_to_list(PreBuff)),
 
1925
            {UniString,RestBuff,InnerLen};
 
1926
        ?N_BMPString ->
1840
1927
            <<PreBuff:InnerLen/binary,RestBuff/binary>> = Buffer,%%added for binary
1841
 
            BMP = mk_BMP_string(binary_to_list(PreBuff)), 
1842
 
            {BMP,RestBuff,InnerLen}; 
1843
 
        _ ->  
 
1928
            BMP = mk_BMP_string(binary_to_list(PreBuff)),
 
1929
            {BMP,RestBuff,InnerLen};
 
1930
        _ ->
1844
1931
            <<PreBuff:InnerLen/binary,RestBuff/binary>> = Buffer,%%added for binary
1845
1932
            {PreBuff, RestBuff, InnerLen}
1846
 
    end. 
1847
 
     
1848
 
 
1849
 
  
1850
 
%%============================================================================ 
1851
 
%% encode Universal string 
1852
 
%%============================================================================ 
1853
 
 
1854
 
encode_universal_string(C, {Name, Universal}, DoTag) when atom(Name) -> 
 
1933
    end.
 
1934
 
 
1935
 
 
1936
 
 
1937
%%============================================================================
 
1938
%% encode Universal string
 
1939
%%============================================================================
 
1940
 
 
1941
encode_universal_string(C, {Name, Universal}, DoTag) when atom(Name) ->
1855
1942
    encode_universal_string(C, Universal, DoTag);
1856
 
encode_universal_string(_C, Universal, []) -> 
 
1943
encode_universal_string(_C, Universal, []) ->
1857
1944
    OctetList = mk_uni_list(Universal),
1858
1945
    dotag_universal(?N_UniversalString,OctetList,length(OctetList));
1859
 
encode_universal_string(_C, Universal, DoTag) -> 
1860
 
    OctetList = mk_uni_list(Universal), 
1861
 
    dotag(DoTag, ?N_UniversalString, {OctetList,length(OctetList)}). 
1862
 
 
1863
 
mk_uni_list(In) ->  
1864
 
    mk_uni_list(In,[]). 
1865
 
 
1866
 
mk_uni_list([],List) ->  
1867
 
    lists:reverse(List); 
1868
 
mk_uni_list([{A,B,C,D}|T],List) ->  
1869
 
    mk_uni_list(T,[D,C,B,A|List]); 
1870
 
mk_uni_list([H|T],List) ->  
1871
 
    mk_uni_list(T,[H,0,0,0|List]). 
1872
 
 
1873
 
%%=========================================================================== 
1874
 
%% decode Universal strings  
1875
 
%%    (Buffer, Range, StringType, HasTag, LenIn) -> 
1876
 
%%                           {String, Remain, RemovedBytes}  
1877
 
%%=========================================================================== 
 
1946
encode_universal_string(_C, Universal, DoTag) ->
 
1947
    OctetList = mk_uni_list(Universal),
 
1948
    dotag(DoTag, ?N_UniversalString, {OctetList,length(OctetList)}).
 
1949
 
 
1950
mk_uni_list(In) ->
 
1951
    mk_uni_list(In,[]).
 
1952
 
 
1953
mk_uni_list([],List) ->
 
1954
    lists:reverse(List);
 
1955
mk_uni_list([{A,B,C,D}|T],List) ->
 
1956
    mk_uni_list(T,[D,C,B,A|List]);
 
1957
mk_uni_list([H|T],List) ->
 
1958
    mk_uni_list(T,[H,0,0,0|List]).
 
1959
 
 
1960
%%===========================================================================
 
1961
%% decode Universal strings
 
1962
%%    (Buffer, Range, StringType, HasTag, LenIn) ->
 
1963
%%                           {String, Remain, RemovedBytes}
 
1964
%%===========================================================================
1878
1965
 
1879
1966
decode_universal_string(Buffer, Range, Tags, LenIn, OptOrMand) ->
1880
1967
%    NewTags = new_tags(HasTag, #tag{class=?UNIVERSAL,number=?N_UniversalString}),
1881
 
    decode_restricted_string(Buffer, Range, ?N_UniversalString, 
 
1968
    decode_restricted_string(Buffer, Range, ?N_UniversalString,
1882
1969
                             Tags, LenIn, [], OptOrMand,old).
1883
 
  
1884
 
 
1885
 
mk_universal_string(In) -> 
1886
 
    mk_universal_string(In,[]). 
1887
 
 
1888
 
mk_universal_string([],Acc) -> 
1889
 
    lists:reverse(Acc); 
1890
 
mk_universal_string([0,0,0,D|T],Acc) -> 
1891
 
    mk_universal_string(T,[D|Acc]); 
1892
 
mk_universal_string([A,B,C,D|T],Acc) -> 
1893
 
    mk_universal_string(T,[{A,B,C,D}|Acc]). 
1894
 
 
1895
 
 
1896
 
%%============================================================================ 
1897
 
%% encode UTF8 string 
1898
 
%%============================================================================ 
 
1970
 
 
1971
 
 
1972
mk_universal_string(In) ->
 
1973
    mk_universal_string(In,[]).
 
1974
 
 
1975
mk_universal_string([],Acc) ->
 
1976
    lists:reverse(Acc);
 
1977
mk_universal_string([0,0,0,D|T],Acc) ->
 
1978
    mk_universal_string(T,[D|Acc]);
 
1979
mk_universal_string([A,B,C,D|T],Acc) ->
 
1980
    mk_universal_string(T,[{A,B,C,D}|Acc]).
 
1981
 
 
1982
 
 
1983
%%============================================================================
 
1984
%% encode UTF8 string
 
1985
%%============================================================================
1899
1986
encode_UTF8_string(_,UTF8String,[]) when binary(UTF8String) ->
1900
1987
    dotag_universal(?N_UTF8String,UTF8String,size(UTF8String));
1901
1988
encode_UTF8_string(_,UTF8String,DoTag) when binary(UTF8String) ->
1908
1995
 
1909
1996
 
1910
1997
%%============================================================================
1911
 
%% decode UTF8 string 
 
1998
%% decode UTF8 string
1912
1999
%%============================================================================
1913
2000
 
1914
2001
decode_UTF8_string(Buffer, Tags, OptOrMand) ->
1916
2003
    decode_UTF8_string_notag(Buffer, NewTags, OptOrMand).
1917
2004
 
1918
2005
decode_UTF8_string_notag(Buffer, Tags, OptOrMand) ->
1919
 
    {RestTags, {FormLen, Buffer0, Rb0}} = 
 
2006
    {RestTags, {FormLen, Buffer0, Rb0}} =
1920
2007
        check_tags_i(Tags, Buffer, OptOrMand),
1921
2008
    case FormLen of
1922
2009
        {?CONSTRUCTED,Len} ->
1923
2010
            %% an UTF8String may be encoded as a constructed type
1924
2011
            {Buffer00,RestBytes} = split_list(Buffer0,Len),
1925
 
            {Val01, Buffer01, Rb01} = 
 
2012
            {Val01, Buffer01, Rb01} =
1926
2013
                decode_UTF8_string_notag(Buffer00,RestTags,OptOrMand),
1927
2014
            {Buffer02, Rb02} = restbytes2(RestBytes,Buffer01,noext),
1928
2015
            {Val01, Buffer02, Rb0+Rb01+Rb02};
1930
2017
            <<Result:Len/binary,RestBuff/binary>> = Buffer0,
1931
2018
            {Result,RestBuff,Rb0 + Len}
1932
2019
    end.
1933
 
            
1934
 
    
1935
 
%%============================================================================
1936
 
%% encode BMP string 
1937
 
%%============================================================================
1938
 
 
1939
 
encode_BMP_string(C, {Name,BMPString}, DoTag) when atom(Name)-> 
 
2020
 
 
2021
 
 
2022
%%============================================================================
 
2023
%% encode BMP string
 
2024
%%============================================================================
 
2025
 
 
2026
encode_BMP_string(C, {Name,BMPString}, DoTag) when atom(Name)->
1940
2027
    encode_BMP_string(C, BMPString, DoTag);
1941
 
encode_BMP_string(_C, BMPString, []) -> 
 
2028
encode_BMP_string(_C, BMPString, []) ->
1942
2029
    OctetList = mk_BMP_list(BMPString),
1943
2030
    dotag_universal(?N_BMPString,OctetList,length(OctetList));
1944
 
encode_BMP_string(_C, BMPString, DoTag) -> 
1945
 
    OctetList = mk_BMP_list(BMPString), 
1946
 
    dotag(DoTag, ?N_BMPString, {OctetList,length(OctetList)}). 
1947
 
 
1948
 
mk_BMP_list(In) ->  
1949
 
    mk_BMP_list(In,[]). 
1950
 
 
1951
 
mk_BMP_list([],List) ->  
1952
 
    lists:reverse(List); 
1953
 
mk_BMP_list([{0,0,C,D}|T],List) ->  
1954
 
    mk_BMP_list(T,[D,C|List]); 
1955
 
mk_BMP_list([H|T],List) ->  
1956
 
    mk_BMP_list(T,[H,0|List]). 
1957
 
 
1958
 
%%============================================================================ 
1959
 
%% decode (OctetList, Range(ignored), tag|notag) -> {ValList, RestList} 
1960
 
%%    (Buffer, Range, StringType, HasTag, TotalLen) -> 
1961
 
%%                               {String, Remain, RemovedBytes}  
1962
 
%%============================================================================ 
1963
 
decode_BMP_string(Buffer, Range, Tags, LenIn, OptOrMand) -> 
 
2031
encode_BMP_string(_C, BMPString, DoTag) ->
 
2032
    OctetList = mk_BMP_list(BMPString),
 
2033
    dotag(DoTag, ?N_BMPString, {OctetList,length(OctetList)}).
 
2034
 
 
2035
mk_BMP_list(In) ->
 
2036
    mk_BMP_list(In,[]).
 
2037
 
 
2038
mk_BMP_list([],List) ->
 
2039
    lists:reverse(List);
 
2040
mk_BMP_list([{0,0,C,D}|T],List) ->
 
2041
    mk_BMP_list(T,[D,C|List]);
 
2042
mk_BMP_list([H|T],List) ->
 
2043
    mk_BMP_list(T,[H,0|List]).
 
2044
 
 
2045
%%============================================================================
 
2046
%% decode (OctetList, Range(ignored), tag|notag) -> {ValList, RestList}
 
2047
%%    (Buffer, Range, StringType, HasTag, TotalLen) ->
 
2048
%%                               {String, Remain, RemovedBytes}
 
2049
%%============================================================================
 
2050
decode_BMP_string(Buffer, Range, Tags, LenIn, OptOrMand) ->
1964
2051
%    NewTags = new_tags(HasTag, #tag{class=?UNIVERSAL,number=?N_BMPString}),
1965
 
    decode_restricted_string(Buffer, Range, ?N_BMPString, 
1966
 
                             Tags, LenIn, [], OptOrMand,old). 
1967
 
 
1968
 
mk_BMP_string(In) -> 
1969
 
    mk_BMP_string(In,[]). 
1970
 
 
1971
 
mk_BMP_string([],US) -> 
1972
 
    lists:reverse(US); 
1973
 
mk_BMP_string([0,B|T],US) -> 
1974
 
    mk_BMP_string(T,[B|US]); 
1975
 
mk_BMP_string([C,D|T],US) -> 
1976
 
    mk_BMP_string(T,[{0,0,C,D}|US]). 
1977
 
 
1978
 
 
1979
 
%%============================================================================ 
1980
 
%% Generalized time, ITU_T X.680 Chapter 39 
 
2052
    decode_restricted_string(Buffer, Range, ?N_BMPString,
 
2053
                             Tags, LenIn, [], OptOrMand,old).
 
2054
 
 
2055
mk_BMP_string(In) ->
 
2056
    mk_BMP_string(In,[]).
 
2057
 
 
2058
mk_BMP_string([],US) ->
 
2059
    lists:reverse(US);
 
2060
mk_BMP_string([0,B|T],US) ->
 
2061
    mk_BMP_string(T,[B|US]);
 
2062
mk_BMP_string([C,D|T],US) ->
 
2063
    mk_BMP_string(T,[{0,0,C,D}|US]).
 
2064
 
 
2065
 
 
2066
%%============================================================================
 
2067
%% Generalized time, ITU_T X.680 Chapter 39
1981
2068
%%
1982
 
%% encode Generalized time 
1983
 
%%============================================================================ 
 
2069
%% encode Generalized time
 
2070
%%============================================================================
1984
2071
 
1985
 
encode_generalized_time(C, {Name,OctetList}, DoTag) when atom(Name) -> 
 
2072
encode_generalized_time(C, {Name,OctetList}, DoTag) when atom(Name) ->
1986
2073
    encode_generalized_time(C, OctetList, DoTag);
1987
 
encode_generalized_time(_C, OctetList, []) -> 
 
2074
encode_generalized_time(_C, OctetList, []) ->
1988
2075
    dotag_universal(?N_GeneralizedTime,OctetList,length(OctetList));
1989
 
encode_generalized_time(_C, OctetList, DoTag) -> 
1990
 
    dotag(DoTag, ?N_GeneralizedTime, {OctetList,length(OctetList)}). 
1991
 
 
1992
 
%%============================================================================ 
1993
 
%% decode Generalized time  
1994
 
%%    (Buffer, Range, HasTag, TotalLen) -> {String, Remain, RemovedBytes}  
1995
 
%%============================================================================ 
1996
 
 
1997
 
decode_generalized_time(Buffer, Range, Tags, TotalLen, OptOrMand) -> 
 
2076
encode_generalized_time(_C, OctetList, DoTag) ->
 
2077
    dotag(DoTag, ?N_GeneralizedTime, {OctetList,length(OctetList)}).
 
2078
 
 
2079
%%============================================================================
 
2080
%% decode Generalized time
 
2081
%%    (Buffer, Range, HasTag, TotalLen) -> {String, Remain, RemovedBytes}
 
2082
%%============================================================================
 
2083
 
 
2084
decode_generalized_time(Buffer, Range, Tags, TotalLen, OptOrMand) ->
1998
2085
    NewTags = new_tags(Tags,#tag{class=?UNIVERSAL,
1999
2086
                         number=?N_GeneralizedTime}),
2000
2087
    decode_generalized_time_notag(Buffer, Range, NewTags, TotalLen, OptOrMand).
2001
2088
 
2002
 
decode_generalized_time_notag(Buffer, Range, Tags, TotalLen, OptOrMand) -> 
2003
 
    {RestTags, {FormLen, Buffer0, Rb0}} =  
 
2089
decode_generalized_time_notag(Buffer, Range, Tags, TotalLen, OptOrMand) ->
 
2090
    {RestTags, {FormLen, Buffer0, Rb0}} =
2004
2091
        check_tags_i(Tags, Buffer, OptOrMand),
2005
2092
 
2006
2093
    case FormLen of
2007
2094
        {?CONSTRUCTED,Len} ->
2008
2095
            {Buffer00,RestBytes} = split_list(Buffer0,Len),
2009
 
            {Val01, Buffer01, Rb01} = 
2010
 
                decode_generalized_time_notag(Buffer00, Range, 
2011
 
                                              RestTags, TotalLen, 
 
2096
            {Val01, Buffer01, Rb01} =
 
2097
                decode_generalized_time_notag(Buffer00, Range,
 
2098
                                              RestTags, TotalLen,
2012
2099
                                              OptOrMand),
2013
2100
            {Buffer02, Rb02} = restbytes2(RestBytes,Buffer01,noext),
2014
2101
            {Val01, Buffer02, Rb0+Rb01+Rb02};
2017
2104
            {binary_to_list(PreBuff), RestBuff, Rb0+Len}
2018
2105
    end.
2019
2106
 
2020
 
%%============================================================================ 
2021
 
%% Universal time, ITU_T X.680 Chapter 40 
 
2107
%%============================================================================
 
2108
%% Universal time, ITU_T X.680 Chapter 40
2022
2109
%%
2023
 
%% encode UTC time 
2024
 
%%============================================================================ 
 
2110
%% encode UTC time
 
2111
%%============================================================================
2025
2112
 
2026
 
encode_utc_time(C, {Name,OctetList}, DoTag) when atom(Name) -> 
 
2113
encode_utc_time(C, {Name,OctetList}, DoTag) when atom(Name) ->
2027
2114
    encode_utc_time(C, OctetList, DoTag);
2028
 
encode_utc_time(_C, OctetList, []) -> 
 
2115
encode_utc_time(_C, OctetList, []) ->
2029
2116
    dotag_universal(?N_UTCTime, OctetList,length(OctetList));
2030
 
encode_utc_time(_C, OctetList, DoTag) -> 
 
2117
encode_utc_time(_C, OctetList, DoTag) ->
2031
2118
    dotag(DoTag, ?N_UTCTime, {OctetList,length(OctetList)}).
2032
 
 
2033
 
%%============================================================================ 
2034
 
%% decode UTC time 
2035
 
%%    (Buffer, Range, HasTag, TotalLen) -> {String, Remain, RemovedBytes}  
2036
 
%%============================================================================ 
2037
 
 
2038
 
decode_utc_time(Buffer, Range, Tags, TotalLen, OptOrMand) -> 
 
2119
 
 
2120
%%============================================================================
 
2121
%% decode UTC time
 
2122
%%    (Buffer, Range, HasTag, TotalLen) -> {String, Remain, RemovedBytes}
 
2123
%%============================================================================
 
2124
 
 
2125
decode_utc_time(Buffer, Range, Tags, TotalLen, OptOrMand) ->
2039
2126
    NewTags = new_tags(Tags,#tag{class=?UNIVERSAL,number=?N_UTCTime}),
2040
2127
    decode_utc_time_notag(Buffer, Range, NewTags, TotalLen, OptOrMand).
2041
 
                                                                  
2042
 
decode_utc_time_notag(Buffer, Range, Tags, TotalLen, OptOrMand) -> 
2043
 
    {RestTags, {FormLen, Buffer0, Rb0}} =  
 
2128
 
 
2129
decode_utc_time_notag(Buffer, Range, Tags, TotalLen, OptOrMand) ->
 
2130
    {RestTags, {FormLen, Buffer0, Rb0}} =
2044
2131
        check_tags_i(Tags, Buffer, OptOrMand),
2045
2132
 
2046
2133
    case FormLen of
2047
2134
        {?CONSTRUCTED,Len} ->
2048
2135
            {Buffer00,RestBytes} = split_list(Buffer0,Len),
2049
 
            {Val01, Buffer01, Rb01} = 
2050
 
                decode_utc_time_notag(Buffer00, Range, 
2051
 
                                      RestTags, TotalLen, 
 
2136
            {Val01, Buffer01, Rb01} =
 
2137
                decode_utc_time_notag(Buffer00, Range,
 
2138
                                      RestTags, TotalLen,
2052
2139
                                      OptOrMand),
2053
2140
            {Buffer02, Rb02} = restbytes2(RestBytes,Buffer01,noext),
2054
2141
            {Val01, Buffer02, Rb0+Rb01+Rb02};
2057
2144
            {binary_to_list(PreBuff), RestBuff, Rb0+Len}
2058
2145
    end.
2059
2146
 
2060
 
 
2061
 
%%============================================================================ 
2062
 
%% Length handling  
2063
 
%%
2064
 
%% Encode length 
2065
 
%% 
2066
 
%% encode_length(Int | indefinite) -> 
2067
 
%%          [<127]| [128 + Int (<127),OctetList] | [16#80] 
2068
 
%%============================================================================ 
2069
 
 
2070
 
encode_length(indefinite) -> 
2071
 
    {[16#80],1}; % 128 
2072
 
encode_length(L) when L =< 16#7F -> 
2073
 
    {[L],1}; 
2074
 
encode_length(L) -> 
2075
 
    Oct = minimum_octets(L), 
2076
 
    Len = length(Oct), 
2077
 
    if 
2078
 
        Len =< 126 -> 
2079
 
            {[ (16#80+Len) | Oct ],Len+1}; 
2080
 
        true -> 
2081
 
            exit({error,{asn1, to_long_length_oct, Len}}) 
2082
 
    end. 
2083
 
 
 
2147
 
 
2148
%%============================================================================
 
2149
%% Length handling
 
2150
%%
 
2151
%% Encode length
 
2152
%%
 
2153
%% encode_length(Int | indefinite) ->
 
2154
%%          [<127]| [128 + Int (<127),OctetList] | [16#80]
 
2155
%%============================================================================
 
2156
 
 
2157
encode_length(indefinite) ->
 
2158
    {[16#80],1}; % 128
 
2159
encode_length(L) when L =< 16#7F ->
 
2160
    {[L],1};
 
2161
encode_length(L) ->
 
2162
    Oct = minimum_octets(L),
 
2163
    Len = length(Oct),
 
2164
    if
 
2165
        Len =< 126 ->
 
2166
            {[ (16#80+Len) | Oct ],Len+1};
 
2167
        true ->
 
2168
            exit({error,{asn1, to_long_length_oct, Len}})
 
2169
    end.
 
2170
 
2084
2171
 
2085
2172
%% Val must be >= 0
2086
 
minimum_octets(Val) -> 
2087
 
    minimum_octets(Val,[]). 
2088
 
 
 
2173
minimum_octets(Val) ->
 
2174
    minimum_octets(Val,[]).
 
2175
 
2089
2176
minimum_octets(0,Acc) ->
2090
2177
    Acc;
2091
2178
minimum_octets(Val, Acc) ->
2092
2179
    minimum_octets((Val bsr 8),[Val band 16#FF | Acc]).
2093
2180
 
2094
 
 
2095
 
%%=========================================================================== 
2096
 
%% Decode length 
2097
 
%% 
2098
 
%% decode_length(OctetList) -> {{indefinite, RestOctetsL}, NoRemovedBytes} |  
2099
 
%%                             {{Length, RestOctetsL}, NoRemovedBytes} 
2100
 
%%=========================================================================== 
2101
 
 
2102
 
decode_length(<<1:1,0:7,T/binary>>) ->     
 
2181
 
 
2182
%%===========================================================================
 
2183
%% Decode length
 
2184
%%
 
2185
%% decode_length(OctetList) -> {{indefinite, RestOctetsL}, NoRemovedBytes} |
 
2186
%%                             {{Length, RestOctetsL}, NoRemovedBytes}
 
2187
%%===========================================================================
 
2188
 
 
2189
decode_length(<<1:1,0:7,T/binary>>) ->
2103
2190
    {{indefinite, T}, 1};
2104
2191
decode_length(<<0:1,Length:7,T/binary>>) ->
2105
2192
    {{Length,T},1};
2107
2194
    <<Length:LL/unit:8,Rest/binary>> = T,
2108
2195
    {{Length,Rest}, LL+1}.
2109
2196
 
2110
 
%decode_length([128 | T]) -> 
2111
 
%    {{indefinite, T},1}; 
2112
 
%decode_length([H | T]) when H =< 127 -> 
2113
 
%    {{H, T},1}; 
2114
 
%decode_length([H | T]) -> 
2115
 
%    dec_long_length(H band 16#7F, T, 0, 1). 
2116
 
 
2117
 
 
2118
 
%%dec_long_length(0, Buffer, Acc, Len) -> 
2119
 
%%    {{Acc, Buffer},Len}; 
2120
 
%%dec_long_length(Bytes, [H | T], Acc, Len) -> 
2121
 
%%    dec_long_length(Bytes - 1, T, (Acc bsl 8) + H, Len+1). 
2122
 
 
 
2197
%decode_length([128 | T]) ->
 
2198
%    {{indefinite, T},1};
 
2199
%decode_length([H | T]) when H =< 127 ->
 
2200
%    {{H, T},1};
 
2201
%decode_length([H | T]) ->
 
2202
%    dec_long_length(H band 16#7F, T, 0, 1).
 
2203
 
 
2204
 
 
2205
%%dec_long_length(0, Buffer, Acc, Len) ->
 
2206
%%    {{Acc, Buffer},Len};
 
2207
%%dec_long_length(Bytes, [H | T], Acc, Len) ->
 
2208
%%    dec_long_length(Bytes - 1, T, (Acc bsl 8) + H, Len+1).
 
2209
 
2123
2210
%%===========================================================================
2124
2211
%% Decode tag and length
2125
2212
%%
2126
2213
%% decode_tag_and_length(Buffer) -> {Tag, Len, RemainingBuffer, RemovedBytes}
2127
 
%% 
 
2214
%%
2128
2215
%%===========================================================================
2129
2216
 
2130
2217
decode_tag_and_length(Buffer) ->
2131
 
    {Tag, Buffer2, RemBytesTag} = decode_tag(Buffer), 
2132
 
    {{Len, Buffer3}, RemBytesLen} = decode_length(Buffer2), 
2133
 
    {Tag, Len, Buffer3, RemBytesTag+RemBytesLen}. 
2134
 
 
2135
 
 
2136
 
%%============================================================================ 
2137
 
%% Check if valid tag 
2138
 
%% 
2139
 
%% check_if_valid_tag(Tag, List_of_valid_tags, OptOrMand) -> name of the tag 
2140
 
%%=============================================================================== 
 
2218
    {Tag, Buffer2, RemBytesTag} = decode_tag(Buffer),
 
2219
    {{Len, Buffer3}, RemBytesLen} = decode_length(Buffer2),
 
2220
    {Tag, Len, Buffer3, RemBytesTag+RemBytesLen}.
 
2221
 
 
2222
 
 
2223
%%============================================================================
 
2224
%% Check if valid tag
 
2225
%%
 
2226
%% check_if_valid_tag(Tag, List_of_valid_tags, OptOrMand) -> name of the tag
 
2227
%%===============================================================================
2141
2228
 
2142
2229
check_if_valid_tag(<<0,0,_/binary>>,_,_) ->
2143
2230
    asn1_EOC;
2144
 
check_if_valid_tag(<<>>, _, OptOrMand) -> 
 
2231
check_if_valid_tag(<<>>, _, OptOrMand) ->
2145
2232
    check_if_valid_tag2(false,[],[],OptOrMand);
2146
2233
check_if_valid_tag(Bytes, ListOfTags, OptOrMand) when binary(Bytes) ->
2147
2234
    {Tag, _, _} = decode_tag(Bytes),
2149
2236
 
2150
2237
%% This alternative should be removed in the near future
2151
2238
%% Bytes as input should be the only necessary call
2152
 
check_if_valid_tag(Tag, ListOfTags, OptOrMand) -> 
2153
 
    {Class, _Form, TagNo} = Tag, 
2154
 
    C = code_class(Class), 
2155
 
    T = case C of 
2156
 
            'UNIVERSAL' -> 
2157
 
                code_type(TagNo); 
2158
 
            _ -> 
2159
 
                TagNo 
2160
 
        end, 
2161
 
    check_if_valid_tag2({C,T}, ListOfTags, Tag, OptOrMand). 
2162
 
 
2163
 
check_if_valid_tag2(_Class_TagNo, [], Tag, mandatory) -> 
2164
 
    exit({error,{asn1,{invalid_tag,Tag}}}); 
2165
 
check_if_valid_tag2(_Class_TagNo, [], Tag, _) -> 
2166
 
    exit({error,{asn1,{no_optional_tag,Tag}}}); 
2167
 
 
2168
 
check_if_valid_tag2(Class_TagNo, [{TagName,TagList}|T], Tag, OptOrMand) -> 
2169
 
    case check_if_valid_tag_loop(Class_TagNo, TagList) of 
2170
 
        true -> 
2171
 
            TagName; 
2172
 
        false -> 
2173
 
            check_if_valid_tag2(Class_TagNo, T, Tag, OptOrMand) 
2174
 
    end. 
2175
 
 
2176
 
check_if_valid_tag_loop(_Class_TagNo,[]) -> 
2177
 
    false; 
2178
 
check_if_valid_tag_loop(Class_TagNo,[H|T]) -> 
 
2239
check_if_valid_tag(Tag, ListOfTags, OptOrMand) ->
 
2240
    {Class, _Form, TagNo} = Tag,
 
2241
    C = code_class(Class),
 
2242
    T = case C of
 
2243
            'UNIVERSAL' ->
 
2244
                code_type(TagNo);
 
2245
            _ ->
 
2246
                TagNo
 
2247
        end,
 
2248
    check_if_valid_tag2({C,T}, ListOfTags, Tag, OptOrMand).
 
2249
 
 
2250
check_if_valid_tag2(_Class_TagNo, [], Tag, mandatory) ->
 
2251
    exit({error,{asn1,{invalid_tag,Tag}}});
 
2252
check_if_valid_tag2(_Class_TagNo, [], Tag, _) ->
 
2253
    exit({error,{asn1,{no_optional_tag,Tag}}});
 
2254
 
 
2255
check_if_valid_tag2(Class_TagNo, [{TagName,TagList}|T], Tag, OptOrMand) ->
 
2256
    case check_if_valid_tag_loop(Class_TagNo, TagList) of
 
2257
        true ->
 
2258
            TagName;
 
2259
        false ->
 
2260
            check_if_valid_tag2(Class_TagNo, T, Tag, OptOrMand)
 
2261
    end.
 
2262
 
 
2263
check_if_valid_tag_loop(_Class_TagNo,[]) ->
 
2264
    false;
 
2265
check_if_valid_tag_loop(Class_TagNo,[H|T]) ->
2179
2266
    %% It is not possible to distinguish between SEQUENCE OF and SEQUENCE, and
2180
2267
    %% between SET OF and SET because both are coded as 16 and 17, respectively.
2181
2268
    H_without_OF = case H of
2187
2274
                           Else
2188
2275
                   end,
2189
2276
 
2190
 
    case H_without_OF of 
2191
 
        Class_TagNo -> 
2192
 
            true; 
2193
 
        {_,_} -> 
2194
 
            check_if_valid_tag_loop(Class_TagNo,T); 
2195
 
        _ -> 
2196
 
            check_if_valid_tag_loop(Class_TagNo,H), 
2197
 
            check_if_valid_tag_loop(Class_TagNo,T) 
2198
 
    end. 
2199
 
 
2200
 
 
2201
 
 
2202
 
code_class(0) -> 'UNIVERSAL'; 
2203
 
code_class(16#40) -> 'APPLICATION'; 
2204
 
code_class(16#80) -> 'CONTEXT'; 
2205
 
code_class(16#C0) -> 'PRIVATE'. 
2206
 
 
2207
 
 
2208
 
code_type(1) -> 'BOOLEAN'; 
2209
 
code_type(2) -> 'INTEGER'; 
2210
 
code_type(3) -> 'BIT STRING';  
2211
 
code_type(4) -> 'OCTET STRING';  
2212
 
code_type(5) -> 'NULL'; 
2213
 
code_type(6) -> 'OBJECT IDENTIFIER'; 
2214
 
code_type(7) -> 'ObjectDescriptor'; 
2215
 
code_type(8) -> 'EXTERNAL'; 
2216
 
code_type(9) -> 'REAL'; 
2217
 
code_type(10) -> 'ENUMERATED'; 
2218
 
code_type(11) -> 'EMBEDDED_PDV'; 
2219
 
code_type(16) -> 'SEQUENCE'; 
2220
 
% code_type(16) -> 'SEQUENCE OF'; 
2221
 
code_type(17) -> 'SET'; 
2222
 
% code_type(17) -> 'SET OF'; 
2223
 
code_type(18) -> 'NumericString';   
2224
 
code_type(19) -> 'PrintableString';   
2225
 
code_type(20) -> 'TeletexString';   
2226
 
code_type(21) -> 'VideotexString';   
2227
 
code_type(22) -> 'IA5String';   
2228
 
code_type(23) -> 'UTCTime';   
2229
 
code_type(24) -> 'GeneralizedTime';   
2230
 
code_type(25) -> 'GraphicString';   
2231
 
code_type(26) -> 'VisibleString';   
2232
 
code_type(27) -> 'GeneralString';   
2233
 
code_type(28) -> 'UniversalString';   
2234
 
code_type(30) -> 'BMPString';   
2235
 
code_type(Else) -> exit({error,{asn1,{unrecognized_type,Else}}}). 
2236
 
 
 
2277
    case H_without_OF of
 
2278
        Class_TagNo ->
 
2279
            true;
 
2280
        {_,_} ->
 
2281
            check_if_valid_tag_loop(Class_TagNo,T);
 
2282
        _ ->
 
2283
            check_if_valid_tag_loop(Class_TagNo,H),
 
2284
            check_if_valid_tag_loop(Class_TagNo,T)
 
2285
    end.
 
2286
 
 
2287
 
 
2288
 
 
2289
code_class(0) -> 'UNIVERSAL';
 
2290
code_class(16#40) -> 'APPLICATION';
 
2291
code_class(16#80) -> 'CONTEXT';
 
2292
code_class(16#C0) -> 'PRIVATE'.
 
2293
 
 
2294
 
 
2295
code_type(1) -> 'BOOLEAN';
 
2296
code_type(2) -> 'INTEGER';
 
2297
code_type(3) -> 'BIT STRING';
 
2298
code_type(4) -> 'OCTET STRING';
 
2299
code_type(5) -> 'NULL';
 
2300
code_type(6) -> 'OBJECT IDENTIFIER';
 
2301
code_type(7) -> 'ObjectDescriptor';
 
2302
code_type(8) -> 'EXTERNAL';
 
2303
code_type(9) -> 'REAL';
 
2304
code_type(10) -> 'ENUMERATED';
 
2305
code_type(11) -> 'EMBEDDED_PDV';
 
2306
code_type(16) -> 'SEQUENCE';
 
2307
% code_type(16) -> 'SEQUENCE OF';
 
2308
code_type(17) -> 'SET';
 
2309
% code_type(17) -> 'SET OF';
 
2310
code_type(18) -> 'NumericString';
 
2311
code_type(19) -> 'PrintableString';
 
2312
code_type(20) -> 'TeletexString';
 
2313
code_type(21) -> 'VideotexString';
 
2314
code_type(22) -> 'IA5String';
 
2315
code_type(23) -> 'UTCTime';
 
2316
code_type(24) -> 'GeneralizedTime';
 
2317
code_type(25) -> 'GraphicString';
 
2318
code_type(26) -> 'VisibleString';
 
2319
code_type(27) -> 'GeneralString';
 
2320
code_type(28) -> 'UniversalString';
 
2321
code_type(30) -> 'BMPString';
 
2322
code_type(Else) -> exit({error,{asn1,{unrecognized_type,Else}}}).
 
2323
 
2237
2324
%%-------------------------------------------------------------------------
2238
2325
%% decoding of the components of a SET
2239
2326
%%-------------------------------------------------------------------------
2242
2329
   {lists:reverse(Acc),Bytes,Rb+2};
2243
2330
 
2244
2331
decode_set(Rb, indefinite, Bytes, OptOrMand, Fun3, Acc) ->
2245
 
   {Term, Remain, Rb1} = Fun3(Bytes, OptOrMand),
2246
 
   decode_set(Rb+Rb1, indefinite, Remain, OptOrMand, Fun3, [Term|Acc]);
 
2332
    case Fun3(Bytes, OptOrMand) of
 
2333
        {_Term, _Remain, 0} ->
 
2334
            {lists:reverse(Acc),Bytes,Rb};
 
2335
        {Term, Remain, Rb1} ->
 
2336
            Fun3(Bytes, OptOrMand),
 
2337
            decode_set(Rb+Rb1, indefinite, Remain, OptOrMand, Fun3, [Term|Acc])
 
2338
    end;
 
2339
%%   {Term, Remain, Rb1} = Fun3(Bytes, OptOrMand),
 
2340
%%   decode_set(Rb+Rb1, indefinite, Remain, OptOrMand, Fun3, [Term|Acc]);
2247
2341
 
2248
2342
decode_set(Rb, Num, Bytes, _OptOrMand, _Fun3, Acc) when Num == 0 ->
2249
2343
   {lists:reverse(Acc), Bytes, Rb};
2252
2346
   exit({error,{asn1,{length_error,'SET'}}});
2253
2347
 
2254
2348
decode_set(Rb, Num, Bytes, OptOrMand, Fun3, Acc) ->
2255
 
   {Term, Remain, Rb1} = Fun3(Bytes, OptOrMand),
2256
 
   decode_set(Rb+Rb1, Num-Rb1, Remain, OptOrMand, Fun3, [Term|Acc]).
 
2349
    case Fun3(Bytes, OptOrMand) of
 
2350
        {_Term, _Remain, 0} ->
 
2351
            {lists:reverse(Acc),Bytes,Rb};
 
2352
        {Term, Remain, Rb1} ->
 
2353
            Fun3(Bytes, OptOrMand),
 
2354
            decode_set(Rb+Rb1, Num-Rb1, Remain, OptOrMand, Fun3, [Term|Acc])
 
2355
    end.
 
2356
%%    {Term, Remain, Rb1} = Fun3(Bytes, OptOrMand),
 
2357
%%    decode_set(Rb+Rb1, Num-Rb1, Remain, OptOrMand, Fun3, [Term|Acc]).
2257
2358
 
2258
2359
 
2259
2360
%%-------------------------------------------------------------------------
2303
2404
%% INTERNAL HELPER FUNCTIONS (not exported)
2304
2405
%%-------------------------------------------------------------------------
2305
2406
 
2306
 
 
2307
 
%%========================================================================== 
2308
 
%% Encode tag 
2309
 
%% 
2310
 
%% dotag(tag | notag, TagValpattern | TagValTuple, [Length, Value]) -> [Tag]  
2311
 
%% TagValPattern is a correct bitpattern for a tag 
2312
 
%% TagValTuple is a tuple of three bitpatterns, Class, Form and TagNo where 
2313
 
%%     Class = UNIVERSAL | APPLICATION | CONTEXT | PRIVATE 
2314
 
%%     Form  = Primitive | Constructed 
2315
 
%%     TagNo = Number of tag 
2316
 
%%========================================================================== 
2317
 
 
 
2407
 
 
2408
%%==========================================================================
 
2409
%% Encode tag
 
2410
%%
 
2411
%% dotag(tag | notag, TagValpattern | TagValTuple, [Length, Value]) -> [Tag]
 
2412
%% TagValPattern is a correct bitpattern for a tag
 
2413
%% TagValTuple is a tuple of three bitpatterns, Class, Form and TagNo where
 
2414
%%     Class = UNIVERSAL | APPLICATION | CONTEXT | PRIVATE
 
2415
%%     Form  = Primitive | Constructed
 
2416
%%     TagNo = Number of tag
 
2417
%%==========================================================================
 
2418
 
2318
2419
 
2319
2420
dotag([], Tag, {Bytes,Len}) ->
2320
2421
    dotag_universal(Tag,Bytes,Len);
2321
2422
dotag(Tags, Tag, {Bytes,Len}) ->
2322
 
    encode_tags(Tags ++ [#tag{class=?UNIVERSAL,number=Tag,form=?PRIMITIVE}], 
 
2423
    encode_tags(Tags ++ [#tag{class=?UNIVERSAL,number=Tag,form=?PRIMITIVE}],
2323
2424
                Bytes, Len);
2324
2425
 
2325
2426
dotag(Tags, Tag, Bytes) ->
2326
 
    encode_tags(Tags ++ [#tag{class=?UNIVERSAL,number=Tag,form=?PRIMITIVE}], 
 
2427
    encode_tags(Tags ++ [#tag{class=?UNIVERSAL,number=Tag,form=?PRIMITIVE}],
2327
2428
                Bytes, size(Bytes)).
2328
2429
 
2329
2430
dotag_universal(UniversalTag,Bytes,Len) when Len =< 16#7F->
2332
2433
    {EncLen,LenLen}=encode_length(Len),
2333
2434
    {[UniversalTag,EncLen,Bytes],1+LenLen+Len}.
2334
2435
 
2335
 
%% decoding postitive integer values. 
 
2436
%% decoding postitive integer values.
2336
2437
decode_integer2(Len,Bin = <<0:1,_:7,_Bs/binary>>,RemovedBytes) ->
2337
2438
    <<Int:Len/unit:8,Buffer2/binary>> = Bin,
2338
2439
    {Int,Buffer2,RemovedBytes};
2342
2443
    Int = N - (1 bsl (8 * Len - 1)),
2343
2444
    {Int,Buffer2,RemovedBytes}.
2344
2445
 
2345
 
%%decode_integer2(Len,Buffer,Acc,RemovedBytes) when (hd(Buffer) band 16#FF) =< 16#7F ->  
 
2446
%%decode_integer2(Len,Buffer,Acc,RemovedBytes) when (hd(Buffer) band 16#FF) =< 16#7F ->
2346
2447
%%    {decode_integer_pos(Buffer, 8 * (Len - 1)),skip(Buffer,Len),RemovedBytes};
2347
 
%%decode_integer2(Len,Buffer,Acc,RemovedBytes)  -> 
2348
 
%%    {decode_integer_neg(Buffer, 8 * (Len - 1)),skip(Buffer,Len),RemovedBytes}. 
2349
 
 
2350
 
%%decode_integer_pos([Byte|Tail], Shift) -> 
2351
 
%%    (Byte bsl Shift) bor decode_integer_pos(Tail, Shift-8); 
 
2448
%%decode_integer2(Len,Buffer,Acc,RemovedBytes)  ->
 
2449
%%    {decode_integer_neg(Buffer, 8 * (Len - 1)),skip(Buffer,Len),RemovedBytes}.
 
2450
 
 
2451
%%decode_integer_pos([Byte|Tail], Shift) ->
 
2452
%%    (Byte bsl Shift) bor decode_integer_pos(Tail, Shift-8);
2352
2453
%%decode_integer_pos([], _) -> 0.
2353
2454
 
2354
 
 
2355
 
%%decode_integer_neg([Byte|Tail], Shift) -> 
2356
 
%%    (-128 + (Byte band 127) bsl Shift) bor decode_integer_pos(Tail, Shift-8). 
 
2455
 
 
2456
%%decode_integer_neg([Byte|Tail], Shift) ->
 
2457
%%    (-128 + (Byte band 127) bsl Shift) bor decode_integer_pos(Tail, Shift-8).
2357
2458
 
2358
2459
 
2359
2460
concat_bit_binaries([],Bin={_,_}) ->
2369
2470
    %% this case occur when decoding with NNL
2370
2471
    L1 ++ L2.
2371
2472
 
2372
 
    
 
2473
 
2373
2474
get_constraint(C,Key) ->
2374
2475
    case lists:keysearch(Key,1,C) of
2375
2476
        false ->
2376
2477
             no;
2377
 
        {value,{_,V}} -> 
 
2478
        {value,{_,V}} ->
2378
2479
            V
2379
2480
    end.
2380
 
 
2381
 
%%skip(Buffer, 0) -> 
2382
 
%%    Buffer; 
2383
 
%%skip([H | T], Len) -> 
2384
 
%%    skip(T, Len-1). 
 
2481
 
 
2482
%%skip(Buffer, 0) ->
 
2483
%%    Buffer;
 
2484
%%skip([H | T], Len) ->
 
2485
%%    skip(T, Len-1).
2385
2486
 
2386
2487
new_tags([],LastTag) ->
2387
2488
    [LastTag];