~clint-fewbar/ubuntu/precise/erlang/merge-15b

« back to all changes in this revision

Viewing changes to lib/dialyzer/test/r9c_SUITE_data/src/asn1/asn1rt_per_bin_rt2ct.erl

  • Committer: Package Import Robot
  • Author(s): Sergei Golovan
  • Date: 2011-12-15 19:20:10 UTC
  • mfrom: (1.1.18) (3.5.15 sid)
  • mto: (3.5.16 sid)
  • mto: This revision was merged to the branch mainline in revision 33.
  • Revision ID: package-import@ubuntu.com-20111215192010-jnxcfe3tbrpp0big
Tags: 1:15.b-dfsg-1
* New upstream release.
* Upload to experimental because this release breaks external drivers
  API along with ABI, so several applications are to be fixed.
* Removed SSL patch because the old SSL implementation is removed from
  the upstream distribution.
* Removed never used patch which added native code to erlang beam files.
* Removed the erlang-docbuilder binary package because the docbuilder
  application was dropped by upstream.
* Documented dropping ${erlang-docbuilder:Depends} substvar in
  erlang-depends(1) manpage.
* Made erlang-base and erlang-base-hipe provide virtual package
  erlang-abi-15.b (the number means the first erlang version, which
  provides current ABI).

Show diffs side-by-side

added added

removed removed

Lines of Context:
 
1
%% ``The contents of this file are subject to the Erlang Public License,
 
2
%% Version 1.1, (the "License"); you may not use this file except in
 
3
%% compliance with the License. You should have received a copy of the
 
4
%% Erlang Public License along with this software. If not, it can be
 
5
%% retrieved via the world wide web at http://www.erlang.org/.
 
6
%%
 
7
%% Software distributed under the License is distributed on an "AS IS"
 
8
%% basis, WITHOUT WARRANTY OF ANY KIND, either express or implied. See
 
9
%% the License for the specific language governing rights and limitations
 
10
%% under the License.
 
11
%%
 
12
%% The Initial Developer of the Original Code is Ericsson Utvecklings AB.
 
13
%% Portions created by Ericsson are Copyright 1999, Ericsson Utvecklings
 
14
%% AB. All Rights Reserved.''
 
15
%%
 
16
%%     $Id: asn1rt_per_bin_rt2ct.erl,v 1.1 2008/12/17 09:53:31 mikpe Exp $
 
17
%%
 
18
-module(asn1rt_per_bin_rt2ct).
 
19
 
 
20
%% encoding / decoding of PER aligned
 
21
 
 
22
-include("asn1_records.hrl").
 
23
 
 
24
-export([dec_fixup/3, cindex/3, list_to_record/2]).
 
25
-export([setchoiceext/1, setext/1, fixoptionals/3, fixextensions/2,
 
26
         getext/1, getextension/2, skipextensions/3, getbit/1, getchoice/3 ]).
 
27
-export([getoptionals/2, getoptionals2/2,
 
28
         set_choice/3, encode_integer/2, encode_integer/3  ]).
 
29
-export([decode_integer/2, decode_integer/3, encode_small_number/1,
 
30
         decode_boolean/1, encode_length/2, decode_length/1, decode_length/2,
 
31
         encode_small_length/1, decode_small_length/1,
 
32
         decode_compact_bit_string/3]).
 
33
-export([decode_enumerated/3,
 
34
         encode_bit_string/3, decode_bit_string/3  ]).
 
35
-export([encode_octet_string/2, decode_octet_string/2,
 
36
         encode_null/1, decode_null/1,
 
37
         encode_object_identifier/1, decode_object_identifier/1,
 
38
         complete/1]).
 
39
 
 
40
 
 
41
-export([encode_open_type/2, decode_open_type/2]).
 
42
 
 
43
-export([%encode_UniversalString/2, decode_UniversalString/2,
 
44
         %encode_PrintableString/2, decode_PrintableString/2,
 
45
         encode_GeneralString/2, decode_GeneralString/2,
 
46
         encode_GraphicString/2, decode_GraphicString/2,
 
47
         encode_TeletexString/2, decode_TeletexString/2,
 
48
         encode_VideotexString/2, decode_VideotexString/2,
 
49
         %encode_VisibleString/2, decode_VisibleString/2,
 
50
         %encode_BMPString/2, decode_BMPString/2,
 
51
         %encode_IA5String/2, decode_IA5String/2,
 
52
         %encode_NumericString/2, decode_NumericString/2,
 
53
         encode_ObjectDescriptor/2, decode_ObjectDescriptor/1
 
54
        ]).
 
55
 
 
56
-export([decode_constrained_number/2,
 
57
         decode_constrained_number/3,
 
58
         decode_unconstrained_number/1,
 
59
         decode_semi_constrained_number/2,
 
60
         encode_unconstrained_number/1,
 
61
         decode_constrained_number/4,
 
62
         encode_octet_string/3,
 
63
         decode_octet_string/3,
 
64
         encode_known_multiplier_string/5,
 
65
         decode_known_multiplier_string/5,
 
66
         getoctets/2, getbits/2
 
67
%        start_drv/1,start_drv2/1,init_drv/1
 
68
        ]).
 
69
 
 
70
 
 
71
-export([eint_positive/1]).
 
72
-export([pre_complete_bits/2]).
 
73
 
 
74
-define('16K',16384).
 
75
-define('32K',32768).
 
76
-define('64K',65536).
 
77
 
 
78
%%-define(nodriver,true).
 
79
 
 
80
dec_fixup(Terms,Cnames,RemBytes) ->
 
81
    dec_fixup(Terms,Cnames,RemBytes,[]).
 
82
 
 
83
dec_fixup([novalue|T],[_Hc|Tc],RemBytes,Acc) ->
 
84
    dec_fixup(T,Tc,RemBytes,Acc);
 
85
dec_fixup([{_Name,novalue}|T],[_Hc|Tc],RemBytes,Acc) ->
 
86
    dec_fixup(T,Tc,RemBytes,Acc);
 
87
dec_fixup([H|T],[Hc|Tc],RemBytes,Acc) ->
 
88
    dec_fixup(T,Tc,RemBytes,[{Hc,H}|Acc]);
 
89
dec_fixup([],_Cnames,RemBytes,Acc) ->
 
90
    {lists:reverse(Acc),RemBytes}.
 
91
 
 
92
cindex(Ix,Val,Cname) ->
 
93
    case element(Ix,Val) of
 
94
        {Cname,Val2} -> Val2;
 
95
        X -> X
 
96
    end.
 
97
 
 
98
%% converts a list to a record if necessary
 
99
list_to_record(_,Tuple) when tuple(Tuple) ->
 
100
    Tuple;
 
101
list_to_record(Name,List) when list(List) ->
 
102
    list_to_tuple([Name|List]).
 
103
 
 
104
%%--------------------------------------------------------
 
105
%% setchoiceext(InRootSet) -> [{bit,X}]
 
106
%% X  is set to  1 when InRootSet==false
 
107
%% X  is set to  0 when InRootSet==true
 
108
%%
 
109
setchoiceext(true) ->
 
110
%    [{debug,choiceext},{bits,1,0}];
 
111
    [0];
 
112
setchoiceext(false) ->
 
113
%    [{debug,choiceext},{bits,1,1}].
 
114
    [1].
 
115
 
 
116
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
117
%% setext(true|false) ->  CompleteList
 
118
%%
 
119
 
 
120
setext(false) ->
 
121
%    [{debug,ext},{bits,1,0}];
 
122
    [0];
 
123
setext(true) ->
 
124
%    [{debug,ext},{bits,1,1}];
 
125
    [1].
 
126
 
 
127
fixoptionals(OptList,_OptLength,Val) when tuple(Val) ->
 
128
%    Bits = fixoptionals(OptList,Val,0),
 
129
%    {Val,{bits,OptLength,Bits}};
 
130
%    {Val,[10,OptLength,Bits]};
 
131
    {Val,fixoptionals(OptList,Val,[])};
 
132
 
 
133
fixoptionals([],_,Acc) ->
 
134
    %% Optbits
 
135
    lists:reverse(Acc);
 
136
fixoptionals([Pos|Ot],Val,Acc) ->
 
137
    case element(Pos,Val) of
 
138
%       asn1_NOVALUE -> fixoptionals(Ot,Val,Acc bsl 1);
 
139
%       asn1_DEFAULT -> fixoptionals(Ot,Val,Acc bsl 1);
 
140
%       _ -> fixoptionals(Ot,Val,(Acc bsl 1) + 1)
 
141
        asn1_NOVALUE -> fixoptionals(Ot,Val,[0|Acc]);
 
142
        asn1_DEFAULT -> fixoptionals(Ot,Val,[0|Acc]);
 
143
        _ -> fixoptionals(Ot,Val,[1|Acc])
 
144
    end.
 
145
 
 
146
 
 
147
getext(Bytes) when tuple(Bytes) ->
 
148
    getbit(Bytes);
 
149
getext(Bytes) when binary(Bytes) ->
 
150
    getbit({0,Bytes});
 
151
getext(Bytes) when list(Bytes) ->
 
152
    getbit({0,Bytes}).
 
153
 
 
154
getextension(0, Bytes) ->
 
155
    {{},Bytes};
 
156
getextension(1, Bytes) ->
 
157
    {Len,Bytes2} = decode_small_length(Bytes),
 
158
    {Blist, Bytes3} = getbits_as_list(Len,Bytes2),
 
159
    {list_to_tuple(Blist),Bytes3}.
 
160
 
 
161
fixextensions({ext,ExtPos,ExtNum},Val) ->
 
162
    case fixextensions(ExtPos,ExtNum+ExtPos,Val,0) of
 
163
        0 -> [];
 
164
        ExtBits ->
 
165
%           [encode_small_length(ExtNum),{bits,ExtNum,ExtBits}]
 
166
%           [encode_small_length(ExtNum),[10,ExtNum,ExtBits]]
 
167
            [encode_small_length(ExtNum),pre_complete_bits(ExtNum,ExtBits)]
 
168
    end.
 
169
 
 
170
fixextensions(Pos,MaxPos,_,Acc) when Pos >= MaxPos ->
 
171
    Acc;
 
172
fixextensions(Pos,ExtPos,Val,Acc) ->
 
173
    Bit = case catch(element(Pos+1,Val)) of
 
174
              asn1_NOVALUE ->
 
175
                  0;
 
176
              asn1_NOEXTVALUE ->
 
177
                  0;
 
178
              {'EXIT',_} ->
 
179
                  0;
 
180
              _ ->
 
181
                  1
 
182
          end,
 
183
    fixextensions(Pos+1,ExtPos,Val,(Acc bsl 1)+Bit).
 
184
 
 
185
skipextensions(Bytes,Nr,ExtensionBitPattern) ->
 
186
    case (catch element(Nr,ExtensionBitPattern)) of
 
187
        1 ->
 
188
            {_,Bytes2} = decode_open_type(Bytes,[]),
 
189
            skipextensions(Bytes2, Nr+1, ExtensionBitPattern);
 
190
        0 ->
 
191
            skipextensions(Bytes, Nr+1, ExtensionBitPattern);
 
192
        {'EXIT',_} -> % badarg, no more extensions
 
193
            Bytes
 
194
    end.
 
195
 
 
196
 
 
197
getchoice(Bytes,1,0) -> % only 1 alternative is not encoded
 
198
    {0,Bytes};
 
199
getchoice(Bytes,_,1) ->
 
200
    decode_small_number(Bytes);
 
201
getchoice(Bytes,NumChoices,0) ->
 
202
    decode_constrained_number(Bytes,{0,NumChoices-1}).
 
203
 
 
204
%% old version kept for backward compatibility with generates from R7B01
 
205
getoptionals(Bytes,NumOpt) ->
 
206
    {Blist,Bytes1} = getbits_as_list(NumOpt,Bytes),
 
207
    {list_to_tuple(Blist),Bytes1}.
 
208
 
 
209
%% new version used in generates from r8b_patch/3 and later
 
210
getoptionals2(Bytes,NumOpt) ->
 
211
    {_,_} = getbits(Bytes,NumOpt).
 
212
 
 
213
 
 
214
%% getbits_as_binary(Num,Bytes) -> {{Unused,BinBits},RestBytes},
 
215
%% Num = integer(),
 
216
%% Bytes = list() | tuple(),
 
217
%% Unused = integer(),
 
218
%% BinBits = binary(),
 
219
%% RestBytes = tuple()
 
220
getbits_as_binary(Num,Bytes) when binary(Bytes) ->
 
221
    getbits_as_binary(Num,{0,Bytes});
 
222
getbits_as_binary(0,Buffer) ->
 
223
    {{0,<<>>},Buffer};
 
224
getbits_as_binary(Num,{0,Bin}) when Num > 16 ->
 
225
    Used = Num rem 8,
 
226
    Pad = (8 - Used) rem 8,
 
227
%%    Nbytes = Num div 8,
 
228
    <<Bits:Num,_:Pad,RestBin/binary>> = Bin,
 
229
    {{Pad,<<Bits:Num,0:Pad>>},RestBin};
 
230
getbits_as_binary(Num,Buffer={_Used,_Bin}) -> % Unaligned buffer
 
231
    %% Num =< 16,
 
232
    {Bits2,Buffer2} = getbits(Buffer,Num),
 
233
    Pad = (8 - (Num rem 8)) rem 8,
 
234
    {{Pad,<<Bits2:Num,0:Pad>>},Buffer2}.
 
235
 
 
236
 
 
237
% integer_from_list(Int,[],BigInt) ->
 
238
%     BigInt;
 
239
% integer_from_list(Int,[H|T],BigInt) when Int < 8 ->
 
240
%     (BigInt bsl Int) bor (H bsr (8-Int));
 
241
% integer_from_list(Int,[H|T],BigInt) ->
 
242
%     integer_from_list(Int-8,T,(BigInt bsl 8) bor H).
 
243
 
 
244
getbits_as_list(Num,Bytes) when binary(Bytes) ->
 
245
    getbits_as_list(Num,{0,Bytes},[]);
 
246
getbits_as_list(Num,Bytes) ->
 
247
    getbits_as_list(Num,Bytes,[]).
 
248
 
 
249
%% If buffer is empty and nothing more will be picked.
 
250
getbits_as_list(0, B, Acc) ->
 
251
    {lists:reverse(Acc),B};
 
252
%% If first byte in buffer is full and at least one byte will be picked,
 
253
%% then pick one byte.
 
254
getbits_as_list(N,{0,Bin},Acc) when N >= 8 ->
 
255
    <<B7:1,B6:1,B5:1,B4:1,B3:1,B2:1,B1:1,B0:1,Rest/binary>> = Bin,
 
256
    getbits_as_list(N-8,{0,Rest},[B0,B1,B2,B3,B4,B5,B6,B7|Acc]);
 
257
getbits_as_list(N,{Used,Bin},Acc) when N >= 4, Used =< 4 ->
 
258
    NewUsed = Used + 4,
 
259
    Rem = 8 - NewUsed,
 
260
    <<_:Used,B3:1,B2:1,B1:1,B0:1,_:Rem, Rest/binary>> = Bin,
 
261
    NewRest = case Rem of 0 -> Rest; _ -> Bin end,
 
262
    getbits_as_list(N-4,{NewUsed rem 8,NewRest},[B0,B1,B2,B3|Acc]);
 
263
getbits_as_list(N,{Used,Bin},Acc) when N >= 2, Used =< 6  ->
 
264
    NewUsed = Used + 2,
 
265
    Rem = 8 - NewUsed,
 
266
    <<_:Used,B1:1,B0:1,_:Rem, Rest/binary>> = Bin,
 
267
    NewRest = case Rem of 0 -> Rest; _ -> Bin end,
 
268
    getbits_as_list(N-2,{NewUsed rem 8,NewRest},[B0,B1|Acc]);
 
269
getbits_as_list(N,{Used,Bin},Acc) when Used =< 7 ->
 
270
    NewUsed = Used + 1,
 
271
    Rem = 8 - NewUsed,
 
272
    <<_:Used,B0:1,_:Rem, Rest/binary>> = Bin,
 
273
    NewRest = case Rem of 0 -> Rest; _ -> Bin end,
 
274
    getbits_as_list(N-1,{NewUsed rem 8,NewRest},[B0|Acc]).
 
275
 
 
276
 
 
277
getbit({7,<<_:7,B:1,Rest/binary>>}) ->
 
278
    {B,{0,Rest}};
 
279
getbit({0,Buffer = <<B:1,_:7,_/binary>>}) ->
 
280
    {B,{1,Buffer}};
 
281
getbit({Used,Buffer}) ->
 
282
    Unused = (8 - Used) - 1,
 
283
    <<_:Used,B:1,_:Unused,_/binary>> = Buffer,
 
284
    {B,{Used+1,Buffer}};
 
285
getbit(Buffer) when binary(Buffer) ->
 
286
    getbit({0,Buffer}).
 
287
 
 
288
 
 
289
getbits({0,Buffer},Num) when (Num rem 8) == 0 ->
 
290
    <<Bits:Num,Rest/binary>> = Buffer,
 
291
    {Bits,{0,Rest}};
 
292
getbits({Used,Bin},Num) ->
 
293
    NumPlusUsed = Num + Used,
 
294
    NewUsed = NumPlusUsed rem 8,
 
295
    Unused = (8-NewUsed) rem 8,
 
296
    case Unused of
 
297
        0 ->
 
298
            <<_:Used,Bits:Num,Rest/binary>> = Bin,
 
299
            {Bits,{0,Rest}};
 
300
        _ ->
 
301
            Bytes = NumPlusUsed div 8,
 
302
            <<_:Used,Bits:Num,_:Unused,_/binary>> = Bin,
 
303
            <<_:Bytes/binary,Rest/binary>> = Bin,
 
304
            {Bits,{NewUsed,Rest}}
 
305
    end;
 
306
getbits(Bin,Num) when binary(Bin) ->
 
307
    getbits({0,Bin},Num).
 
308
 
 
309
 
 
310
 
 
311
% getoctet(Bytes) when list(Bytes) ->
 
312
%     getoctet({0,Bytes});
 
313
% getoctet(Bytes) ->
 
314
%     %%    io:format("getoctet:Buffer = ~p~n",[Bytes]),
 
315
%     getoctet1(Bytes).
 
316
 
 
317
% getoctet1({0,[H|T]}) ->
 
318
%     {H,{0,T}};
 
319
% getoctet1({Pos,[_,H|T]}) ->
 
320
%     {H,{0,T}}.
 
321
 
 
322
align({0,L}) ->
 
323
    {0,L};
 
324
align({_Pos,<<_H,T/binary>>}) ->
 
325
    {0,T};
 
326
align(Bytes) ->
 
327
    {0,Bytes}.
 
328
 
 
329
%% First align buffer, then pick the first Num octets.
 
330
%% Returns octets as an integer with bit significance as in buffer.
 
331
getoctets({0,Buffer},Num) ->
 
332
    <<Val:Num/integer-unit:8,RestBin/binary>> = Buffer,
 
333
    {Val,{0,RestBin}};
 
334
getoctets({U,<<_Padding,Rest/binary>>},Num) when U /= 0 ->
 
335
    getoctets({0,Rest},Num);
 
336
getoctets(Buffer,Num) when binary(Buffer) ->
 
337
    getoctets({0,Buffer},Num).
 
338
% getoctets(Buffer,Num) ->
 
339
%     %%    io:format("getoctets:Buffer = ~p~nNum = ~p~n",[Buffer,Num]),
 
340
%     getoctets(Buffer,Num,0).
 
341
 
 
342
% getoctets(Buffer,0,Acc) ->
 
343
%     {Acc,Buffer};
 
344
% getoctets(Buffer,Num,Acc) ->
 
345
%     {Oct,NewBuffer} = getoctet(Buffer),
 
346
%     getoctets(NewBuffer,Num-1,(Acc bsl 8)+Oct).
 
347
 
 
348
% getoctets_as_list(Buffer,Num) ->
 
349
%     getoctets_as_list(Buffer,Num,[]).
 
350
 
 
351
% getoctets_as_list(Buffer,0,Acc) ->
 
352
%     {lists:reverse(Acc),Buffer};
 
353
% getoctets_as_list(Buffer,Num,Acc) ->
 
354
%     {Oct,NewBuffer} = getoctet(Buffer),
 
355
%     getoctets_as_list(NewBuffer,Num-1,[Oct|Acc]).
 
356
 
 
357
%% First align buffer, then pick the first Num octets.
 
358
%% Returns octets as a binary
 
359
getoctets_as_bin({0,Bin},Num)->
 
360
    <<Octets:Num/binary,RestBin/binary>> = Bin,
 
361
    {Octets,{0,RestBin}};
 
362
getoctets_as_bin({_U,Bin},Num) ->
 
363
    <<_Padding,Octets:Num/binary,RestBin/binary>> = Bin,
 
364
    {Octets,{0,RestBin}};
 
365
getoctets_as_bin(Bin,Num) when binary(Bin) ->
 
366
    getoctets_as_bin({0,Bin},Num).
 
367
 
 
368
%% same as above but returns octets as a List
 
369
getoctets_as_list(Buffer,Num) ->
 
370
    {Bin,Buffer2} = getoctets_as_bin(Buffer,Num),
 
371
    {binary_to_list(Bin),Buffer2}.
 
372
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
373
%% set_choice(Alt,Choices,Altnum) -> ListofBitSettings
 
374
%% Alt = atom()
 
375
%% Altnum = integer() | {integer(),integer()}% number of alternatives
 
376
%% Choices = [atom()] | {[atom()],[atom()]}
 
377
%% When Choices is a tuple the first list is the Rootset and the
 
378
%% second is the Extensions and then Altnum must also be a tuple with the
 
379
%% lengths of the 2 lists
 
380
%%
 
381
set_choice(Alt,{L1,L2},{Len1,_Len2}) ->
 
382
    case set_choice_tag(Alt,L1) of
 
383
        N when integer(N), Len1 > 1 ->
 
384
%           [{bits,1,0}, % the value is in the root set
 
385
%            encode_constrained_number({0,Len1-1},N)];
 
386
            [0, % the value is in the root set
 
387
             encode_constrained_number({0,Len1-1},N)];
 
388
        N when integer(N) ->
 
389
%           [{bits,1,0}]; % no encoding if only 0 or 1 alternative
 
390
            [0]; % no encoding if only 0 or 1 alternative
 
391
        false ->
 
392
%           [{bits,1,1}, % extension value
 
393
            [1, % extension value
 
394
             case set_choice_tag(Alt,L2) of
 
395
                 N2 when integer(N2) ->
 
396
                     encode_small_number(N2);
 
397
                 false ->
 
398
                     unknown_choice_alt
 
399
             end]
 
400
    end;
 
401
set_choice(Alt,L,Len) ->
 
402
    case set_choice_tag(Alt,L) of
 
403
        N when integer(N), Len > 1 ->
 
404
            encode_constrained_number({0,Len-1},N);
 
405
        N when integer(N) ->
 
406
            []; % no encoding if only 0 or 1 alternative
 
407
        false ->
 
408
            [unknown_choice_alt]
 
409
    end.
 
410
 
 
411
set_choice_tag(Alt,Choices) ->
 
412
    set_choice_tag(Alt,Choices,0).
 
413
 
 
414
set_choice_tag(Alt,[Alt|_Rest],Tag) ->
 
415
    Tag;
 
416
set_choice_tag(Alt,[_H|Rest],Tag) ->
 
417
    set_choice_tag(Alt,Rest,Tag+1);
 
418
set_choice_tag(_Alt,[],_Tag) ->
 
419
    false.
 
420
 
 
421
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
422
%% decode_fragmented_XXX; decode of values encoded fragmented according
 
423
%% to ITU-T X.691 clause 10.9.3.8. The unit (XXX) is either bits, octets,
 
424
%% characters or number of components (in a choice,sequence or similar).
 
425
%% Buffer is a buffer {Used, Bin}.
 
426
%% C is the constrained length.
 
427
%% If the buffer is not aligned, this function does that.
 
428
decode_fragmented_bits({0,Buffer},C) ->
 
429
    decode_fragmented_bits(Buffer,C,[]);
 
430
decode_fragmented_bits({_N,<<_B,Bs/binary>>},C) ->
 
431
    decode_fragmented_bits(Bs,C,[]).
 
432
 
 
433
decode_fragmented_bits(<<3:2,Len:6,Bin/binary>>,C,Acc) ->
 
434
    {Value,Bin2} = split_binary(Bin, Len * ?'16K'),
 
435
    decode_fragmented_bits(Bin2,C,[Value,Acc]);
 
436
decode_fragmented_bits(<<0:1,0:7,Bin/binary>>,C,Acc) ->
 
437
    BinBits = list_to_binary(lists:reverse(Acc)),
 
438
    case C of
 
439
        Int when integer(Int),C == size(BinBits) ->
 
440
            {BinBits,{0,Bin}};
 
441
        Int when integer(Int) ->
 
442
            exit({error,{asn1,{illegal_value,C,BinBits}}});
 
443
        _ ->
 
444
            {BinBits,{0,Bin}}
 
445
    end;
 
446
decode_fragmented_bits(<<0:1,Len:7,Bin/binary>>,C,Acc) ->
 
447
    Result = {BinBits,{Used,_Rest}} =
 
448
        case (Len rem 8) of
 
449
            0 ->
 
450
                <<Value:Len/binary-unit:1,Bin2/binary>> = Bin,
 
451
                {list_to_binary(lists:reverse([Value|Acc])),{0,Bin2}};
 
452
            Rem ->
 
453
                Bytes = Len div 8,
 
454
                U = 8 - Rem,
 
455
                <<Value:Bytes/binary-unit:8,Bits1:Rem,Bits2:U,Bin2/binary>> = Bin,
 
456
                {list_to_binary(lists:reverse([Bits1 bsl U,Value|Acc])),
 
457
                 {Rem,<<Bits2,Bin2/binary>>}}
 
458
        end,
 
459
    case C of
 
460
         Int when integer(Int),C == (size(BinBits) - ((8 - Used) rem 8)) ->
 
461
            Result;
 
462
        Int when integer(Int) ->
 
463
            exit({error,{asn1,{illegal_value,C,BinBits}}});
 
464
        _ ->
 
465
            Result
 
466
    end.
 
467
 
 
468
 
 
469
decode_fragmented_octets({0,Bin},C) ->
 
470
    decode_fragmented_octets(Bin,C,[]);
 
471
decode_fragmented_octets({_N,<<_B,Bs/binary>>},C) ->
 
472
    decode_fragmented_octets(Bs,C,[]).
 
473
 
 
474
decode_fragmented_octets(<<3:2,Len:6,Bin/binary>>,C,Acc) ->
 
475
    {Value,Bin2} = split_binary(Bin,Len * ?'16K'),
 
476
    decode_fragmented_octets(Bin2,C,[Value,Acc]);
 
477
decode_fragmented_octets(<<0:1,0:7,Bin/binary>>,C,Acc) ->
 
478
    Octets = list_to_binary(lists:reverse(Acc)),
 
479
    case C of
 
480
        Int when integer(Int), C == size(Octets) ->
 
481
            {Octets,{0,Bin}};
 
482
        Int when integer(Int) ->
 
483
            exit({error,{asn1,{illegal_value,C,Octets}}});
 
484
        _ ->
 
485
            {Octets,{0,Bin}}
 
486
    end;
 
487
decode_fragmented_octets(<<0:1,Len:7,Bin/binary>>,C,Acc) ->
 
488
    <<Value:Len/binary-unit:8,Bin2/binary>> = Bin,
 
489
    BinOctets = list_to_binary(lists:reverse([Value|Acc])),
 
490
    case C of
 
491
        Int when integer(Int),size(BinOctets) == Int ->
 
492
            {BinOctets,Bin2};
 
493
        Int when integer(Int) ->
 
494
            exit({error,{asn1,{illegal_value,C,BinOctets}}});
 
495
        _ ->
 
496
            {BinOctets,Bin2}
 
497
    end.
 
498
 
 
499
 
 
500
 
 
501
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
502
%% encode_open_type(Constraint, Value) -> CompleteList
 
503
%% Value = list of bytes of an already encoded value (the list must be flat)
 
504
%%         | binary
 
505
%% Contraint = not used in this version
 
506
%%
 
507
encode_open_type(_Constraint, Val) when list(Val) ->
 
508
    Bin = list_to_binary(Val),
 
509
    case size(Bin) of
 
510
        Size when Size>255 ->
 
511
            [encode_length(undefined,Size),[21,<<Size:16>>,Bin]];
 
512
        Size ->
 
513
            [encode_length(undefined,Size),[20,Size,Bin]]
 
514
    end;
 
515
%    [encode_length(undefined,size(Bin)),{octets,Bin}]; % octets implies align
 
516
encode_open_type(_Constraint, Val) when binary(Val) ->
 
517
%    [encode_length(undefined,size(Val)),{octets,Val}]. % octets implies align
 
518
    case size(Val) of
 
519
        Size when Size>255 ->
 
520
            [encode_length(undefined,size(Val)),[21,<<Size:16>>,Val]]; % octets implies align
 
521
        Size ->
 
522
            [encode_length(undefined,Size),[20,Size,Val]]
 
523
    end.
 
524
%% the binary_to_list is not optimal but compatible with the current solution
 
525
 
 
526
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
527
%% decode_open_type(Buffer,Constraint) -> Value
 
528
%% Constraint is not used in this version
 
529
%% Buffer = [byte] with PER encoded data
 
530
%% Value = [byte] with decoded data (which must be decoded again as some type)
 
531
%%
 
532
decode_open_type(Bytes, _Constraint) ->
 
533
    {Len,Bytes2} = decode_length(Bytes,undefined),
 
534
    getoctets_as_bin(Bytes2,Len).
 
535
 
 
536
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
537
%% encode_integer(Constraint,Value,NamedNumberList) -> CompleteList
 
538
%% encode_integer(Constraint,Value) -> CompleteList
 
539
%% encode_integer(Constraint,{Name,Value}) -> CompleteList
 
540
%%
 
541
%%
 
542
encode_integer(C,V,NamedNumberList) when atom(V) ->
 
543
    case lists:keysearch(V,1,NamedNumberList) of
 
544
        {value,{_,NewV}} ->
 
545
            encode_integer(C,NewV);
 
546
        _ ->
 
547
            exit({error,{asn1,{namednumber,V}}})
 
548
    end;
 
549
encode_integer(C,V,_NamedNumberList) when integer(V) ->
 
550
    encode_integer(C,V);
 
551
encode_integer(C,{Name,V},NamedNumberList) when atom(Name) ->
 
552
    encode_integer(C,V,NamedNumberList).
 
553
 
 
554
encode_integer(C,{Name,Val}) when atom(Name) ->
 
555
    encode_integer(C,Val);
 
556
 
 
557
encode_integer([{Rc,_Ec}],Val) when tuple(Rc) -> % XXX when is this invoked? First argument most often a list,...Ok this is the extension case...but it doesn't work.
 
558
    case (catch encode_integer([Rc],Val)) of
 
559
        {'EXIT',{error,{asn1,_}}} ->
 
560
%           [{bits,1,1},encode_unconstrained_number(Val)];
 
561
            [1,encode_unconstrained_number(Val)];
 
562
        Encoded ->
 
563
%           [{bits,1,0},Encoded]
 
564
            [0,Encoded]
 
565
    end;
 
566
 
 
567
encode_integer([],Val) ->
 
568
    encode_unconstrained_number(Val);
 
569
%% The constraint is the effective constraint, and in this case is a number
 
570
encode_integer([{'SingleValue',V}],V) ->
 
571
    [];
 
572
encode_integer([{'ValueRange',VR={Lb,Ub},Range,PreEnc}],Val) when Val >= Lb,
 
573
                                                Ub >= Val ->
 
574
    %% this case when NamedNumberList
 
575
    encode_constrained_number(VR,Range,PreEnc,Val);
 
576
encode_integer([{'ValueRange',{Lb,'MAX'}}],Val) ->
 
577
    encode_semi_constrained_number(Lb,Val);
 
578
encode_integer([{'ValueRange',{'MIN',_}}],Val) ->
 
579
    encode_unconstrained_number(Val);
 
580
encode_integer([{'ValueRange',VR={_Lb,_Ub}}],Val) ->
 
581
    encode_constrained_number(VR,Val);
 
582
encode_integer(_,Val) ->
 
583
    exit({error,{asn1,{illegal_value,Val}}}).
 
584
 
 
585
 
 
586
 
 
587
decode_integer(Buffer,Range,NamedNumberList) ->
 
588
    {Val,Buffer2} = decode_integer(Buffer,Range),
 
589
    case lists:keysearch(Val,2,NamedNumberList) of
 
590
        {value,{NewVal,_}} -> {NewVal,Buffer2};
 
591
        _ -> {Val,Buffer2}
 
592
    end.
 
593
 
 
594
decode_integer(Buffer,[{Rc,_Ec}]) when tuple(Rc) ->
 
595
    {Ext,Buffer2} = getext(Buffer),
 
596
    case Ext of
 
597
        0 -> decode_integer(Buffer2,[Rc]);
 
598
        1 -> decode_unconstrained_number(Buffer2)
 
599
    end;
 
600
decode_integer(Buffer,undefined) ->
 
601
    decode_unconstrained_number(Buffer);
 
602
decode_integer(Buffer,C) ->
 
603
    case get_constraint(C,'SingleValue') of
 
604
        V when integer(V) ->
 
605
            {V,Buffer};
 
606
        _ ->
 
607
            decode_integer1(Buffer,C)
 
608
    end.
 
609
 
 
610
decode_integer1(Buffer,C) ->
 
611
    case VR = get_constraint(C,'ValueRange') of
 
612
        no ->
 
613
            decode_unconstrained_number(Buffer);
 
614
        {Lb, 'MAX'} ->
 
615
            decode_semi_constrained_number(Buffer,Lb);
 
616
        {_Lb,_Ub} ->
 
617
            decode_constrained_number(Buffer,VR)
 
618
    end.
 
619
 
 
620
%% X.691:10.6 Encoding of a normally small non-negative whole number
 
621
%% Use this for encoding of CHOICE index if there is an extension marker in
 
622
%% the CHOICE
 
623
encode_small_number({Name,Val}) when atom(Name) ->
 
624
    encode_small_number(Val);
 
625
encode_small_number(Val) when Val =< 63 ->
 
626
%    [{bits,1,0},{bits,6,Val}];
 
627
%    [{bits,7,Val}]; % same as above but more efficient
 
628
    [10,7,Val]; % same as above but more efficient
 
629
encode_small_number(Val) ->
 
630
%    [{bits,1,1},encode_semi_constrained_number(0,Val)].
 
631
    [1,encode_semi_constrained_number(0,Val)].
 
632
 
 
633
decode_small_number(Bytes) ->
 
634
    {Bit,Bytes2} = getbit(Bytes),
 
635
    case Bit of
 
636
        0 ->
 
637
            getbits(Bytes2,6);
 
638
        1 ->
 
639
            decode_semi_constrained_number(Bytes2,0)
 
640
    end.
 
641
 
 
642
%% X.691:10.7 Encoding of a semi-constrained whole number
 
643
%% might be an optimization encode_semi_constrained_number(0,Val) ->
 
644
encode_semi_constrained_number(C,{Name,Val}) when atom(Name) ->
 
645
    encode_semi_constrained_number(C,Val);
 
646
encode_semi_constrained_number({Lb,'MAX'},Val) ->
 
647
    encode_semi_constrained_number(Lb,Val);
 
648
encode_semi_constrained_number(Lb,Val) ->
 
649
    Val2 = Val - Lb,
 
650
    Oct = eint_positive(Val2),
 
651
    Len = length(Oct),
 
652
    if
 
653
        Len < 128 ->
 
654
            %{octets,[Len|Oct]}; % equiv with encode_length(undefined,Len) but faster
 
655
            [20,Len+1,[Len|Oct]];
 
656
        Len < 256 ->
 
657
            [encode_length(undefined,Len),[20,Len,Oct]];
 
658
        true ->
 
659
            [encode_length(undefined,Len),[21,<<Len:16>>,Oct]]
 
660
    end.
 
661
 
 
662
decode_semi_constrained_number(Bytes,{Lb,_}) ->
 
663
    decode_semi_constrained_number(Bytes,Lb);
 
664
decode_semi_constrained_number(Bytes,Lb) ->
 
665
    {Len,Bytes2} = decode_length(Bytes,undefined),
 
666
    {V,Bytes3} = getoctets(Bytes2,Len),
 
667
    {V+Lb,Bytes3}.
 
668
 
 
669
encode_constrained_number({Lb,_Ub},_Range,{bits,N},Val) ->
 
670
    Val2 = Val-Lb,
 
671
%    {bits,N,Val2};
 
672
    [10,N,Val2];
 
673
encode_constrained_number({Lb,_Ub},_Range,{octets,N},Val) when N < 256->
 
674
    %% N is 8 or 16 (1 or 2 octets)
 
675
    Val2 = Val-Lb,
 
676
%    {octets,<<Val2:N/unit:8>>};
 
677
    [20,N,Val2];
 
678
encode_constrained_number({Lb,_Ub},_Range,{octets,N},Val) -> % N>255
 
679
    %% N is 8 or 16 (1 or 2 octets)
 
680
    Val2 = Val-Lb,
 
681
%    {octets,<<Val2:N/unit:8>>};
 
682
    [21,<<N:16>>,Val2];
 
683
encode_constrained_number({Lb,_Ub},Range,_,Val) ->
 
684
    Val2 = Val-Lb,
 
685
    if
 
686
        Range =< 16#1000000  -> % max 3 octets
 
687
            Octs = eint_positive(Val2),
 
688
%           [encode_length({1,3},size(Octs)),{octets,Octs}];
 
689
            L = length(Octs),
 
690
            [encode_length({1,3},L),[20,L,Octs]];
 
691
        Range =< 16#100000000  -> % max 4 octets
 
692
            Octs = eint_positive(Val2),
 
693
%           [encode_length({1,4},size(Octs)),{octets,Octs}];
 
694
            L = length(Octs),
 
695
            [encode_length({1,4},L),[20,L,Octs]];
 
696
        Range =< 16#10000000000  -> % max 5 octets
 
697
            Octs = eint_positive(Val2),
 
698
%           [encode_length({1,5},size(Octs)),{octets,Octs}];
 
699
            L = length(Octs),
 
700
            [encode_length({1,5},L),[20,L,Octs]];
 
701
        true  ->
 
702
            exit({not_supported,{integer_range,Range}})
 
703
    end.
 
704
 
 
705
encode_constrained_number(Range,{Name,Val}) when atom(Name) ->
 
706
    encode_constrained_number(Range,Val);
 
707
encode_constrained_number({Lb,Ub},Val) when Val >= Lb, Ub >= Val ->
 
708
    Range = Ub - Lb + 1,
 
709
    Val2 = Val - Lb,
 
710
    if
 
711
        Range  == 2 ->
 
712
%           Size = {bits,1,Val2};
 
713
            [Val2];
 
714
        Range  =< 4 ->
 
715
%           Size = {bits,2,Val2};
 
716
            [10,2,Val2];
 
717
        Range  =< 8 ->
 
718
            [10,3,Val2];
 
719
        Range  =< 16 ->
 
720
            [10,4,Val2];
 
721
        Range  =< 32 ->
 
722
            [10,5,Val2];
 
723
        Range  =< 64 ->
 
724
            [10,6,Val2];
 
725
        Range  =< 128 ->
 
726
            [10,7,Val2];
 
727
        Range  =< 255 ->
 
728
            [10,8,Val2];
 
729
        Range  =< 256 ->
 
730
%           Size = {octets,[Val2]};
 
731
            [20,1,Val2];
 
732
        Range  =< 65536 ->
 
733
%           Size = {octets,<<Val2:16>>};
 
734
            [20,2,<<Val2:16>>];
 
735
        Range =< 16#1000000  ->
 
736
            Octs = eint_positive(Val2),
 
737
%           [{bits,2,length(Octs)-1},{octets,Octs}];
 
738
            Len = length(Octs),
 
739
            [10,2,Len-1,20,Len,Octs];
 
740
        Range =< 16#100000000  ->
 
741
            Octs = eint_positive(Val2),
 
742
            Len = length(Octs),
 
743
            [10,2,Len-1,20,Len,Octs];
 
744
        Range =< 16#10000000000  ->
 
745
            Octs = eint_positive(Val2),
 
746
            Len = length(Octs),
 
747
            [10,3,Len-1,20,Len,Octs];
 
748
        true  ->
 
749
            exit({not_supported,{integer_range,Range}})
 
750
    end;
 
751
encode_constrained_number({_,_},Val) ->
 
752
    exit({error,{asn1,{illegal_value,Val}}}).
 
753
 
 
754
decode_constrained_number(Buffer,VR={Lb,Ub}) ->
 
755
    Range = Ub - Lb + 1,
 
756
    decode_constrained_number(Buffer,VR,Range).
 
757
 
 
758
decode_constrained_number(Buffer,{Lb,_Ub},_Range,{bits,N}) ->
 
759
    {Val,Remain} = getbits(Buffer,N),
 
760
    {Val+Lb,Remain};
 
761
decode_constrained_number(Buffer,{Lb,_Ub},_Range,{octets,N}) ->
 
762
    {Val,Remain} = getoctets(Buffer,N),
 
763
    {Val+Lb,Remain}.
 
764
 
 
765
decode_constrained_number(Buffer,{Lb,_Ub},Range) ->
 
766
                                                %    Val2 = Val - Lb,
 
767
    {Val,Remain} =
 
768
        if
 
769
            Range  == 2 ->
 
770
                getbits(Buffer,1);
 
771
            Range  =< 4 ->
 
772
                getbits(Buffer,2);
 
773
            Range  =< 8 ->
 
774
                getbits(Buffer,3);
 
775
            Range  =< 16 ->
 
776
                getbits(Buffer,4);
 
777
            Range  =< 32 ->
 
778
                getbits(Buffer,5);
 
779
            Range  =< 64 ->
 
780
                getbits(Buffer,6);
 
781
            Range  =< 128 ->
 
782
                getbits(Buffer,7);
 
783
            Range  =< 255 ->
 
784
                getbits(Buffer,8);
 
785
            Range  =< 256 ->
 
786
                getoctets(Buffer,1);
 
787
            Range  =< 65536 ->
 
788
                getoctets(Buffer,2);
 
789
            Range =< 16#1000000  ->
 
790
                {Len,Bytes2} = decode_length(Buffer,{1,3}),
 
791
                {Octs,Bytes3} = getoctets_as_list(Bytes2,Len),
 
792
                {dec_pos_integer(Octs),Bytes3};
 
793
            Range =< 16#100000000  ->
 
794
                {Len,Bytes2} = decode_length(Buffer,{1,4}),
 
795
                {Octs,Bytes3} = getoctets_as_list(Bytes2,Len),
 
796
                {dec_pos_integer(Octs),Bytes3};
 
797
            Range =< 16#10000000000  ->
 
798
                {Len,Bytes2} = decode_length(Buffer,{1,5}),
 
799
                {Octs,Bytes3} = getoctets_as_list(Bytes2,Len),
 
800
                {dec_pos_integer(Octs),Bytes3};
 
801
            true  ->
 
802
                exit({not_supported,{integer_range,Range}})
 
803
        end,
 
804
    {Val+Lb,Remain}.
 
805
 
 
806
%% X.691:10.8 Encoding of an unconstrained whole number
 
807
 
 
808
encode_unconstrained_number(Val) when Val >= 0 ->
 
809
    Oct = eint(Val,[]),
 
810
    Len = length(Oct),
 
811
    if
 
812
        Len < 128 ->
 
813
            %{octets,[Len|Oct]}; % equiv with encode_length(undefined,Len) but faster
 
814
            [20,Len+1,[Len|Oct]];
 
815
        Len < 256 ->
 
816
%           [encode_length(undefined,Len),20,Len,Oct];
 
817
            [20,Len+2,<<2:2,Len:14>>,Oct];% equiv with encode_length(undefined,Len) but faster
 
818
        true ->
 
819
%           [encode_length(undefined,Len),{octets,Oct}]
 
820
            [encode_length(undefined,Len),[21,<<Len:16>>,Oct]]
 
821
    end;
 
822
encode_unconstrained_number(Val) -> % negative
 
823
    Oct = enint(Val,[]),
 
824
    Len = length(Oct),
 
825
    if
 
826
        Len < 128 ->
 
827
%           {octets,[Len|Oct]}; % equiv with encode_length(undefined,Len) but faster
 
828
            [20,Len+1,[Len|Oct]];% equiv with encode_length(undefined,Len) but faster
 
829
        Len < 256 ->
 
830
%           [encode_length(undefined,Len),20,Len,Oct];
 
831
            [20,Len+2,<<2:2,Len:14>>,Oct];% equiv with encode_length(undefined,Len) but faster
 
832
        true ->
 
833
            %[encode_length(undefined,Len),{octets,Oct}]
 
834
            [encode_length(undefined,Len),[21,<<Len:16>>,Oct]]
 
835
    end.
 
836
 
 
837
 
 
838
%% used for positive Values which don't need a sign bit
 
839
%% returns a list
 
840
eint_positive(Val) ->
 
841
    case eint(Val,[]) of
 
842
        [0,B1|T] ->
 
843
            [B1|T];
 
844
        T ->
 
845
            T
 
846
    end.
 
847
 
 
848
 
 
849
eint(0, [B|Acc]) when B < 128 ->
 
850
    [B|Acc];
 
851
eint(N, Acc) ->
 
852
    eint(N bsr 8, [N band 16#ff| Acc]).
 
853
 
 
854
enint(-1, [B1|T]) when B1 > 127 ->
 
855
    [B1|T];
 
856
enint(N, Acc) ->
 
857
    enint(N bsr 8, [N band 16#ff|Acc]).
 
858
 
 
859
decode_unconstrained_number(Bytes) ->
 
860
    {Len,Bytes2} = decode_length(Bytes,undefined),
 
861
    {Ints,Bytes3} = getoctets_as_list(Bytes2,Len),
 
862
    {dec_integer(Ints),Bytes3}.
 
863
 
 
864
dec_pos_integer(Ints) ->
 
865
    decpint(Ints, 8 * (length(Ints) - 1)).
 
866
dec_integer(Ints) when hd(Ints) band 255 =< 127 -> %% Positive number
 
867
    decpint(Ints, 8 * (length(Ints) - 1));
 
868
dec_integer(Ints) ->                        %% Negative
 
869
    decnint(Ints,  8 * (length(Ints) - 1)).
 
870
 
 
871
decpint([Byte|Tail], Shift) ->
 
872
    (Byte bsl Shift) bor decpint(Tail, Shift-8);
 
873
decpint([], _) -> 0.
 
874
 
 
875
decnint([Byte|Tail], Shift) ->
 
876
    (-128 + (Byte band 127) bsl Shift) bor decpint(Tail, Shift-8).
 
877
 
 
878
% minimum_octets(Val) ->
 
879
%     minimum_octets(Val,[]).
 
880
 
 
881
% minimum_octets(Val,Acc) when Val > 0 ->
 
882
%     minimum_octets((Val bsr 8),[Val band 16#FF|Acc]);
 
883
% minimum_octets(0,Acc) ->
 
884
%     Acc.
 
885
 
 
886
 
 
887
%% X.691:10.9 Encoding of a length determinant
 
888
%%encode_small_length(undefined,Len) -> % null means no UpperBound
 
889
%%    encode_small_number(Len).
 
890
 
 
891
%% X.691:10.9.3.5
 
892
%% X.691:10.9.3.7
 
893
encode_length(undefined,Len) -> % un-constrained
 
894
    if
 
895
        Len < 128 ->
 
896
%           {octets,[Len]};
 
897
            [20,1,Len];
 
898
        Len < 16384 ->
 
899
            %{octets,<<2:2,Len:14>>};
 
900
            [20,2,<<2:2,Len:14>>];
 
901
        true  -> % should be able to endode length >= 16384 i.e. fragmented length
 
902
            exit({error,{asn1,{encode_length,{nyi,above_16k}}}})
 
903
    end;
 
904
 
 
905
encode_length({0,'MAX'},Len) ->
 
906
    encode_length(undefined,Len);
 
907
encode_length(Vr={Lb,Ub},Len) when Ub =< 65535 ,Lb >= 0 -> % constrained
 
908
    encode_constrained_number(Vr,Len);
 
909
encode_length({Lb,_Ub},Len) when integer(Lb), Lb >= 0 -> % Ub > 65535
 
910
    encode_length(undefined,Len);
 
911
encode_length({Vr={Lb,Ub},[]},Len) when Ub =< 65535 ,Lb >= 0,Len=<Ub ->
 
912
    %% constrained extensible
 
913
%    [{bits,1,0},encode_constrained_number(Vr,Len)];
 
914
    [0,encode_constrained_number(Vr,Len)];
 
915
encode_length({{Lb,_},[]},Len) ->
 
916
    [1,encode_semi_constrained_number(Lb,Len)];
 
917
encode_length(SingleValue,_Len) when integer(SingleValue) ->
 
918
    [].
 
919
 
 
920
%% X.691 10.9.3.4 (only used for length of bitmap that prefixes extension
 
921
%% additions in a sequence or set
 
922
encode_small_length(Len) when Len =< 64 ->
 
923
%%    [{bits,1,0},{bits,6,Len-1}];
 
924
%    {bits,7,Len-1}; % the same as above but more efficient
 
925
    [10,7,Len-1];
 
926
encode_small_length(Len) ->
 
927
%    [{bits,1,1},encode_length(undefined,Len)].
 
928
    [1,encode_length(undefined,Len)].
 
929
 
 
930
% decode_small_length({Used,<<_:Used,0:1,Num:6,_:((8-Used+1) rem 8),Rest/binary>>}) ->
 
931
%     case Buffer of
 
932
%       <<_:Used,0:1,Num:6,_:((8-Used+1) rem 8),Rest/binary>> ->
 
933
%           {Num,
 
934
%     case getbit(Buffer) of
 
935
%       {0,Remain} ->
 
936
%           {Bits,Remain2} = getbits(Remain,6),
 
937
%           {Bits+1,Remain2};
 
938
%       {1,Remain} ->
 
939
%           decode_length(Remain,undefined)
 
940
%     end.
 
941
 
 
942
decode_small_length(Buffer) ->
 
943
    case getbit(Buffer) of
 
944
        {0,Remain} ->
 
945
            {Bits,Remain2} = getbits(Remain,6),
 
946
            {Bits+1,Remain2};
 
947
        {1,Remain} ->
 
948
            decode_length(Remain,undefined)
 
949
    end.
 
950
 
 
951
decode_length(Buffer) ->
 
952
    decode_length(Buffer,undefined).
 
953
 
 
954
decode_length(Buffer,undefined)  -> % un-constrained
 
955
    {0,Buffer2} = align(Buffer),
 
956
    case Buffer2 of
 
957
        <<0:1,Oct:7,Rest/binary>> ->
 
958
            {Oct,{0,Rest}};
 
959
        <<2:2,Val:14,Rest/binary>> ->
 
960
            {Val,{0,Rest}};
 
961
        <<3:2,_Val:14,_Rest/binary>> ->
 
962
            %% this case should be fixed
 
963
            exit({error,{asn1,{decode_length,{nyi,above_16k}}}})
 
964
    end;
 
965
%%    {Bits,_} = getbits(Buffer2,2),
 
966
%     case Bits of
 
967
%       2 ->
 
968
%           {Val,Bytes3} = getoctets(Buffer2,2),
 
969
%           {(Val band 16#3FFF),Bytes3};
 
970
%       3 ->
 
971
%           exit({error,{asn1,{decode_length,{nyi,above_16k}}}});
 
972
%       _ ->
 
973
%           {Val,Bytes3} = getoctet(Buffer2),
 
974
%           {Val band 16#7F,Bytes3}
 
975
%     end;
 
976
 
 
977
decode_length(Buffer,{Lb,Ub}) when Ub =< 65535 ,Lb >= 0 -> % constrained
 
978
    decode_constrained_number(Buffer,{Lb,Ub});
 
979
decode_length(_Buffer,{Lb,_Ub}) when integer(Lb), Lb >= 0 -> % Ub > 65535
 
980
    exit({error,{asn1,{decode_length,{nyi,above_64K}}}});
 
981
decode_length(Buffer,{{Lb,Ub},[]}) ->
 
982
    case getbit(Buffer) of
 
983
        {0,Buffer2} ->
 
984
            decode_length(Buffer2, {Lb,Ub})
 
985
    end;
 
986
 
 
987
 
 
988
%When does this case occur with {_,_Lb,Ub} ??
 
989
% X.691:10.9.3.5
 
990
decode_length({Used,Bin},{_,_Lb,_Ub}) -> %when Len =< 127 -> % Unconstrained or large Ub NOTE! this case does not cover case when Ub > 65535
 
991
    Unused = (8-Used) rem 8,
 
992
    case Bin of
 
993
        <<_:Used,0:1,Val:7,R:Unused,Rest/binary>> ->
 
994
            {Val,{Used,<<R,Rest/binary>>}};
 
995
        <<_:Used,_:Unused,2:2,Val:14,Rest/binary>> ->
 
996
            {Val, {0,Rest}};
 
997
        <<_:Used,_:Unused,3:2,_:14,_Rest/binary>> ->
 
998
            exit({error,{asn1,{decode_length,{nyi,length_above_64K}}}})
 
999
    end;
 
1000
% decode_length(Buffer,{_,_Lb,Ub}) -> %when Len =< 127 -> % Unconstrained or large Ub
 
1001
%     case getbit(Buffer) of
 
1002
%       {0,Remain} ->
 
1003
%           getbits(Remain,7);
 
1004
%       {1,Remain} ->
 
1005
%           {Val,Remain2} = getoctets(Buffer,2),
 
1006
%           {Val band 2#0111111111111111, Remain2}
 
1007
%     end;
 
1008
decode_length(Buffer,SingleValue) when integer(SingleValue) ->
 
1009
    {SingleValue,Buffer}.
 
1010
 
 
1011
 
 
1012
                                                % X.691:11
 
1013
decode_boolean(Buffer) -> %when record(Buffer,buffer)
 
1014
    case getbit(Buffer) of
 
1015
        {1,Remain} -> {true,Remain};
 
1016
        {0,Remain} -> {false,Remain}
 
1017
    end.
 
1018
 
 
1019
 
 
1020
%% ENUMERATED with extension marker
 
1021
decode_enumerated(Buffer,C,{Ntup1,Ntup2}) when tuple(Ntup1), tuple(Ntup2) ->
 
1022
    {Ext,Buffer2} = getext(Buffer),
 
1023
    case Ext of
 
1024
        0 -> % not an extension value
 
1025
            {Val,Buffer3} = decode_integer(Buffer2,C),
 
1026
            case catch (element(Val+1,Ntup1)) of
 
1027
                NewVal when atom(NewVal) -> {NewVal,Buffer3};
 
1028
                _Error -> exit({error,{asn1,{decode_enumerated,{Val,[Ntup1,Ntup2]}}}})
 
1029
            end;
 
1030
        1 -> % this an extension value
 
1031
            {Val,Buffer3} = decode_small_number(Buffer2),
 
1032
            case catch (element(Val+1,Ntup2)) of
 
1033
                NewVal when atom(NewVal) -> {NewVal,Buffer3};
 
1034
                _ -> {{asn1_enum,Val},Buffer3}
 
1035
            end
 
1036
    end;
 
1037
 
 
1038
decode_enumerated(Buffer,C,NamedNumberTup) when tuple(NamedNumberTup) ->
 
1039
    {Val,Buffer2} = decode_integer(Buffer,C),
 
1040
    case catch (element(Val+1,NamedNumberTup)) of
 
1041
        NewVal when atom(NewVal) -> {NewVal,Buffer2};
 
1042
        _Error -> exit({error,{asn1,{decode_enumerated,{Val,NamedNumberTup}}}})
 
1043
    end.
 
1044
 
 
1045
%%===============================================================================
 
1046
%%===============================================================================
 
1047
%%===============================================================================
 
1048
%% Bitstring value, ITU_T X.690 Chapter 8.5
 
1049
%%===============================================================================
 
1050
%%===============================================================================
 
1051
%%===============================================================================
 
1052
 
 
1053
%%===============================================================================
 
1054
%% encode bitstring value
 
1055
%%===============================================================================
 
1056
 
 
1057
 
 
1058
 
 
1059
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
1060
%% bitstring NamedBitList
 
1061
%% Val can be  of:
 
1062
%% - [identifiers] where only named identifers are set to one,
 
1063
%%   the Constraint must then have some information of the
 
1064
%%   bitlength.
 
1065
%% - [list of ones and zeroes] all bits
 
1066
%% - integer value representing the bitlist
 
1067
%% C is constraint Len, only valid when identifiers
 
1068
 
 
1069
 
 
1070
%% when the value is a list of {Unused,BinBits}, where
 
1071
%% Unused = integer(),
 
1072
%% BinBits = binary().
 
1073
 
 
1074
encode_bit_string(C,Bin={Unused,BinBits},NamedBitList) when integer(Unused),
 
1075
                                                            binary(BinBits) ->
 
1076
    encode_bin_bit_string(C,Bin,NamedBitList);
 
1077
 
 
1078
%% when the value is a list of named bits
 
1079
 
 
1080
encode_bit_string(C, LoNB=[FirstVal | _RestVal], NamedBitList) when atom(FirstVal) ->
 
1081
    ToSetPos = get_all_bitposes(LoNB, NamedBitList, []),
 
1082
    BitList = make_and_set_list(ToSetPos,0),
 
1083
    encode_bit_string(C,BitList,NamedBitList);% consider the constraint
 
1084
 
 
1085
encode_bit_string(C, BL=[{bit,_} | _RestVal], NamedBitList) ->
 
1086
    ToSetPos = get_all_bitposes(BL, NamedBitList, []),
 
1087
    BitList = make_and_set_list(ToSetPos,0),
 
1088
    encode_bit_string(C,BitList,NamedBitList);
 
1089
 
 
1090
%% when the value is a list of ones and zeroes
 
1091
encode_bit_string(Int, BitListValue, _)
 
1092
  when list(BitListValue),integer(Int) ->
 
1093
    %% The type is constrained by a single value size constraint
 
1094
    [40,Int,length(BitListValue),BitListValue];
 
1095
% encode_bit_string(C, BitListValue,NamedBitList)
 
1096
%   when list(BitListValue) ->
 
1097
%     [encode_bit_str_length(C,BitListValue),
 
1098
%      2,45,BitListValue];
 
1099
encode_bit_string(no, BitListValue,[])
 
1100
  when list(BitListValue) ->
 
1101
    [encode_length(undefined,length(BitListValue)),
 
1102
     2,BitListValue];
 
1103
encode_bit_string(C, BitListValue,[])
 
1104
  when list(BitListValue) ->
 
1105
    [encode_length(C,length(BitListValue)),
 
1106
     2,BitListValue];
 
1107
encode_bit_string(no, BitListValue,_NamedBitList)
 
1108
  when list(BitListValue) ->
 
1109
    %% this case with an unconstrained BIT STRING can be made more efficient
 
1110
    %% if the complete driver can take a special code so the length field
 
1111
    %% is encoded there.
 
1112
    NewBitLVal = lists:reverse(lists:dropwhile(fun(0)->true;(1)->false end,
 
1113
                                            lists:reverse(BitListValue))),
 
1114
    [encode_length(undefined,length(NewBitLVal)),
 
1115
     2,NewBitLVal];
 
1116
encode_bit_string(C,BitListValue,_NamedBitList)
 
1117
  when list(BitListValue) ->% C = {_,'MAX'}
 
1118
%     NewBitLVal = lists:reverse(lists:dropwhile(fun(0)->true;(1)->false end,
 
1119
%                                           lists:reverse(BitListValue))),
 
1120
    NewBitLVal = bit_string_trailing_zeros(BitListValue,C),
 
1121
    [encode_length(C,length(NewBitLVal)),
 
1122
     2,NewBitLVal];
 
1123
 
 
1124
% encode_bit_string(C, BitListValue, NamedBitList) when list(BitListValue) ->
 
1125
%     BitListToBinary =
 
1126
%       %% fun that transforms a list of 1 and 0 to a tuple:
 
1127
%       %% {UnusedBitsInLastByte, Binary}
 
1128
%       fun([H|T],Acc,N,Fun) ->
 
1129
%               Fun(T,(Acc bsl 1)+H,N+1,Fun);
 
1130
%          ([],Acc,N,_) -> % length fits in one byte
 
1131
%               Unused = (8 - (N rem 8)) rem 8,
 
1132
% %             case N/8 of
 
1133
% %                 _Len =< 255 ->
 
1134
% %                     [30,Unused,(Unused+N)/8,<<Acc:N,0:Unused>>];
 
1135
% %                 _Len ->
 
1136
% %                     Len = (Unused+N)/8,
 
1137
% %                     [31,Unused,<<Len:16>>,<<Acc:N,0:Unused>>]
 
1138
% %             end
 
1139
%               {Unused,<<Acc:N,0:Unused>>}
 
1140
%       end,
 
1141
%     UnusedAndBin =
 
1142
%       case NamedBitList of
 
1143
%           [] ->  % dont remove trailing zeroes
 
1144
%               BitListToBinary(BitListValue,0,0,BitListToBinary);
 
1145
%           _ ->
 
1146
%               BitListToBinary(lists:reverse(
 
1147
%                                 lists:dropwhile(fun(0)->true;(1)->false end,
 
1148
%                                                 lists:reverse(BitListValue))),
 
1149
%                               0,0,BitListToBinary)
 
1150
%       end,
 
1151
%     encode_bin_bit_string(C,UnusedAndBin,NamedBitList);
 
1152
 
 
1153
%% when the value is an integer
 
1154
encode_bit_string(C, IntegerVal, NamedBitList) when integer(IntegerVal)->
 
1155
    BitList = int_to_bitlist(IntegerVal),
 
1156
    encode_bit_string(C,BitList,NamedBitList);
 
1157
 
 
1158
%% when the value is a tuple
 
1159
encode_bit_string(C,{Name,Val}, NamedBitList) when atom(Name) ->
 
1160
    encode_bit_string(C,Val,NamedBitList).
 
1161
 
 
1162
bit_string_trailing_zeros(BitList,C) when integer(C) ->
 
1163
    bit_string_trailing_zeros1(BitList,C,C);
 
1164
bit_string_trailing_zeros(BitList,{Lb,Ub}) when integer(Lb) ->
 
1165
    bit_string_trailing_zeros1(BitList,Lb,Ub);
 
1166
bit_string_trailing_zeros(BitList,{{Lb,Ub},_}) when integer(Lb) ->
 
1167
    bit_string_trailing_zeros1(BitList,Lb,Ub);
 
1168
bit_string_trailing_zeros(BitList,_) ->
 
1169
    BitList.
 
1170
 
 
1171
bit_string_trailing_zeros1(BitList,Lb,Ub) ->
 
1172
    case length(BitList) of
 
1173
        Lb -> BitList;
 
1174
        B when B<Lb -> BitList++lists:duplicate(Lb-B,0);
 
1175
        D -> F = fun(L,LB,LB,_,_)->lists:reverse(L);
 
1176
                    ([0|R],L1,LB,UB,Fun)->Fun(R,L1-1,LB,UB,Fun);
 
1177
                    (L,L1,_,UB,_)when L1 =< UB -> lists:reverse(L);
 
1178
                    (_,_L1,_,_,_) ->exit({error,{list_length_BIT_STRING,
 
1179
                                                 BitList}}) end,
 
1180
             F(lists:reverse(BitList),D,Lb,Ub,F)
 
1181
    end.
 
1182
 
 
1183
%% encode_bin_bit_string/3, when value is a tuple of Unused and BinBits.
 
1184
%% Unused = integer(),i.e. number unused bits in least sign. byte of
 
1185
%% BinBits = binary().
 
1186
encode_bin_bit_string(C,{_,BinBits},_NamedBitList)
 
1187
  when integer(C),C=<16 ->
 
1188
    [45,C,size(BinBits),BinBits];
 
1189
encode_bin_bit_string(C,{_Unused,BinBits},_NamedBitList)
 
1190
  when integer(C) ->
 
1191
    [2,45,C,size(BinBits),BinBits];
 
1192
encode_bin_bit_string(C,UnusedAndBin={_,_},NamedBitList) ->
 
1193
%    UnusedAndBin1 = {Unused1,Bin1} =
 
1194
    {Unused1,Bin1} =
 
1195
        %% removes all trailing bits if NamedBitList is not empty
 
1196
        remove_trailing_bin(NamedBitList,UnusedAndBin),
 
1197
    case C of
 
1198
%    case get_constraint(C,'SizeConstraint') of
 
1199
 
 
1200
%       0 ->
 
1201
%           []; % borde avg�ras i compile-time
 
1202
%       V when integer(V),V=<16 ->
 
1203
%           {Unused2,Bin2} = pad_list(V,UnusedAndBin1),
 
1204
%           <<BitVal:V,_:Unused2>> = Bin2,
 
1205
% %         {bits,V,BitVal};
 
1206
%           [10,V,BitVal];
 
1207
%       V when integer(V) ->
 
1208
%           %[align, pad_list(V, UnusedAndBin1)];
 
1209
%           {Unused2,Bin2} = pad_list(V, UnusedAndBin1),
 
1210
%           <<BitVal:V,_:Unused2>> = Bin2,
 
1211
%           [2,octets_unused_to_complete(Unused2,size(Bin2),Bin2)];
 
1212
 
 
1213
        {Lb,Ub} when integer(Lb),integer(Ub) ->
 
1214
%           [encode_length({Lb,Ub},size(Bin1)*8 - Unused1),
 
1215
%            align,UnusedAndBin1];
 
1216
            Size=size(Bin1),
 
1217
            [encode_length({Lb,Ub},Size*8 - Unused1),
 
1218
             2,octets_unused_to_complete(Unused1,Size,Bin1)];
 
1219
        no ->
 
1220
            Size=size(Bin1),
 
1221
            [encode_length(undefined,Size*8 - Unused1),
 
1222
             2,octets_unused_to_complete(Unused1,Size,Bin1)];
 
1223
        Sc ->
 
1224
            Size=size(Bin1),
 
1225
            [encode_length(Sc,Size*8 - Unused1),
 
1226
             2,octets_unused_to_complete(Unused1,Size,Bin1)]
 
1227
    end.
 
1228
 
 
1229
remove_trailing_bin([], {Unused,Bin}) ->
 
1230
    {Unused,Bin};
 
1231
remove_trailing_bin(NamedNumberList, {_Unused,Bin}) ->
 
1232
    Size = size(Bin)-1,
 
1233
    <<Bfront:Size/binary, LastByte:8>> = Bin,
 
1234
    %% clear the Unused bits to be sure
 
1235
%    LastByte1 = LastByte band (((1 bsl Unused) -1) bxor 255),% why this???
 
1236
    Unused1 = trailingZeroesInNibble(LastByte band 15),
 
1237
    Unused2 =
 
1238
        case Unused1 of
 
1239
            4 ->
 
1240
                4 + trailingZeroesInNibble(LastByte bsr 4);
 
1241
            _ -> Unused1
 
1242
        end,
 
1243
    case Unused2 of
 
1244
        8 ->
 
1245
            remove_trailing_bin(NamedNumberList,{0,Bfront});
 
1246
        _ ->
 
1247
            {Unused2,Bin}
 
1248
    end.
 
1249
 
 
1250
 
 
1251
trailingZeroesInNibble(0) ->
 
1252
    4;
 
1253
trailingZeroesInNibble(1) ->
 
1254
    0;
 
1255
trailingZeroesInNibble(2) ->
 
1256
    1;
 
1257
trailingZeroesInNibble(3) ->
 
1258
    0;
 
1259
trailingZeroesInNibble(4) ->
 
1260
    2;
 
1261
trailingZeroesInNibble(5) ->
 
1262
    0;
 
1263
trailingZeroesInNibble(6) ->
 
1264
    1;
 
1265
trailingZeroesInNibble(7) ->
 
1266
    0;
 
1267
trailingZeroesInNibble(8) ->
 
1268
    3;
 
1269
trailingZeroesInNibble(9) ->
 
1270
    0;
 
1271
trailingZeroesInNibble(10) ->
 
1272
    1;
 
1273
trailingZeroesInNibble(11) ->
 
1274
    0;
 
1275
trailingZeroesInNibble(12) -> %#1100
 
1276
    2;
 
1277
trailingZeroesInNibble(13) ->
 
1278
    0;
 
1279
trailingZeroesInNibble(14) ->
 
1280
    1;
 
1281
trailingZeroesInNibble(15) ->
 
1282
    0.
 
1283
 
 
1284
%%%%%%%%%%%%%%%
 
1285
%% The result is presented as a list of named bits (if possible)
 
1286
%% else as a tuple {Unused,Bits}. Unused is the number of unused
 
1287
%% bits, least significant bits in the last byte of Bits. Bits is
 
1288
%% the BIT STRING represented as a binary.
 
1289
%%
 
1290
decode_compact_bit_string(Buffer, C, NamedNumberList) ->
 
1291
    case get_constraint(C,'SizeConstraint') of
 
1292
        0 -> % fixed length
 
1293
            {{8,0},Buffer};
 
1294
        V when integer(V),V=<16 -> %fixed length 16 bits or less
 
1295
            compact_bit_string(Buffer,V,NamedNumberList);
 
1296
        V when integer(V),V=<65536 -> %fixed length > 16 bits
 
1297
            Bytes2 = align(Buffer),
 
1298
            compact_bit_string(Bytes2,V,NamedNumberList);
 
1299
        V when integer(V) -> % V > 65536 => fragmented value
 
1300
            {Bin,Buffer2} = decode_fragmented_bits(Buffer,V),
 
1301
            case Buffer2 of
 
1302
                {0,_} -> {{0,Bin},Buffer2};
 
1303
                {U,_} -> {{8-U,Bin},Buffer2}
 
1304
            end;
 
1305
        {Lb,Ub} when integer(Lb),integer(Ub) ->
 
1306
            %% This case may demand decoding of fragmented length/value
 
1307
            {Len,Bytes2} = decode_length(Buffer,{Lb,Ub}),
 
1308
            Bytes3 = align(Bytes2),
 
1309
            compact_bit_string(Bytes3,Len,NamedNumberList);
 
1310
        no ->
 
1311
            %% This case may demand decoding of fragmented length/value
 
1312
            {Len,Bytes2} = decode_length(Buffer,undefined),
 
1313
            Bytes3 = align(Bytes2),
 
1314
            compact_bit_string(Bytes3,Len,NamedNumberList);
 
1315
        Sc ->
 
1316
            {Len,Bytes2} = decode_length(Buffer,Sc),
 
1317
            Bytes3 = align(Bytes2),
 
1318
            compact_bit_string(Bytes3,Len,NamedNumberList)
 
1319
    end.
 
1320
 
 
1321
 
 
1322
%%%%%%%%%%%%%%%
 
1323
%% The result is presented as a list of named bits (if possible)
 
1324
%% else as a list of 0 and 1.
 
1325
%%
 
1326
decode_bit_string(Buffer, C, NamedNumberList) ->
 
1327
    case get_constraint(C,'SizeConstraint') of
 
1328
        {Lb,Ub} when integer(Lb),integer(Ub) ->
 
1329
            {Len,Bytes2} = decode_length(Buffer,{Lb,Ub}),
 
1330
            Bytes3 = align(Bytes2),
 
1331
            bit_list_or_named(Bytes3,Len,NamedNumberList);
 
1332
        no ->
 
1333
            {Len,Bytes2} = decode_length(Buffer,undefined),
 
1334
            Bytes3 = align(Bytes2),
 
1335
            bit_list_or_named(Bytes3,Len,NamedNumberList);
 
1336
        0 -> % fixed length
 
1337
            {[],Buffer}; % nothing to encode
 
1338
        V when integer(V),V=<16 -> % fixed length 16 bits or less
 
1339
            bit_list_or_named(Buffer,V,NamedNumberList);
 
1340
        V when integer(V),V=<65536 ->
 
1341
            Bytes2 = align(Buffer),
 
1342
            bit_list_or_named(Bytes2,V,NamedNumberList);
 
1343
        V when integer(V) ->
 
1344
            Bytes2 = align(Buffer),
 
1345
            {BinBits,_Bytes3} = decode_fragmented_bits(Bytes2,V),
 
1346
            bit_list_or_named(BinBits,V,NamedNumberList);
 
1347
        Sc -> % extension marker
 
1348
            {Len,Bytes2} = decode_length(Buffer,Sc),
 
1349
            Bytes3 = align(Bytes2),
 
1350
            bit_list_or_named(Bytes3,Len,NamedNumberList)
 
1351
    end.
 
1352
 
 
1353
 
 
1354
%% if no named bits are declared we will return a
 
1355
%% {Unused,Bits}. Unused = integer(),
 
1356
%% Bits = binary().
 
1357
compact_bit_string(Buffer,Len,[]) ->
 
1358
    getbits_as_binary(Len,Buffer); % {{Unused,BinBits},NewBuffer}
 
1359
compact_bit_string(Buffer,Len,NamedNumberList) ->
 
1360
    bit_list_or_named(Buffer,Len,NamedNumberList).
 
1361
 
 
1362
 
 
1363
%% if no named bits are declared we will return a
 
1364
%% BitList = [0 | 1]
 
1365
 
 
1366
bit_list_or_named(Buffer,Len,[]) ->
 
1367
    getbits_as_list(Len,Buffer);
 
1368
 
 
1369
%% if there are named bits declared we will return a named
 
1370
%% BitList where the names are atoms and unnamed bits represented
 
1371
%% as {bit,Pos}
 
1372
%% BitList = [atom() | {bit,Pos}]
 
1373
%% Pos = integer()
 
1374
 
 
1375
bit_list_or_named(Buffer,Len,NamedNumberList) ->
 
1376
    {BitList,Rest} = getbits_as_list(Len,Buffer),
 
1377
    {bit_list_or_named1(0,BitList,NamedNumberList,[]), Rest}.
 
1378
 
 
1379
bit_list_or_named1(Pos,[0|Bt],Names,Acc) ->
 
1380
    bit_list_or_named1(Pos+1,Bt,Names,Acc);
 
1381
bit_list_or_named1(Pos,[1|Bt],Names,Acc) ->
 
1382
    case lists:keysearch(Pos,2,Names) of
 
1383
        {value,{Name,_}} ->
 
1384
            bit_list_or_named1(Pos+1,Bt,Names,[Name|Acc]);
 
1385
        _  ->
 
1386
            bit_list_or_named1(Pos+1,Bt,Names,[{bit,Pos}|Acc])
 
1387
    end;
 
1388
bit_list_or_named1(_Pos,[],_Names,Acc) ->
 
1389
    lists:reverse(Acc).
 
1390
 
 
1391
 
 
1392
 
 
1393
%%%%%%%%%%%%%%%
 
1394
%%
 
1395
 
 
1396
int_to_bitlist(Int) when integer(Int), Int > 0 ->
 
1397
    [Int band 1 | int_to_bitlist(Int bsr 1)];
 
1398
int_to_bitlist(0) ->
 
1399
    [].
 
1400
 
 
1401
 
 
1402
%%%%%%%%%%%%%%%%%%
 
1403
%% get_all_bitposes([list of named bits to set], named_bit_db, []) ->
 
1404
%%   [sorted_list_of_bitpositions_to_set]
 
1405
 
 
1406
get_all_bitposes([{bit,ValPos}|Rest], NamedBitList, Ack) ->
 
1407
    get_all_bitposes(Rest, NamedBitList, [ValPos | Ack ]);
 
1408
 
 
1409
get_all_bitposes([Val | Rest], NamedBitList, Ack) ->
 
1410
    case lists:keysearch(Val, 1, NamedBitList) of
 
1411
        {value, {_ValName, ValPos}} ->
 
1412
            get_all_bitposes(Rest, NamedBitList, [ValPos | Ack]);
 
1413
        _ ->
 
1414
            exit({error,{asn1, {bitstring_namedbit, Val}}})
 
1415
    end;
 
1416
get_all_bitposes([], _NamedBitList, Ack) ->
 
1417
    lists:sort(Ack).
 
1418
 
 
1419
%%%%%%%%%%%%%%%%%%
 
1420
%% make_and_set_list([list of positions to set to 1])->
 
1421
%% returns list with all in SetPos set.
 
1422
%% in positioning in list the first element is 0, the second 1 etc.., but
 
1423
%%
 
1424
 
 
1425
make_and_set_list([XPos|SetPos], XPos) ->
 
1426
    [1 | make_and_set_list(SetPos, XPos + 1)];
 
1427
make_and_set_list([Pos|SetPos], XPos) ->
 
1428
    [0 | make_and_set_list([Pos | SetPos], XPos + 1)];
 
1429
make_and_set_list([], _) ->
 
1430
    [].
 
1431
 
 
1432
%%%%%%%%%%%%%%%%%
 
1433
%% pad_list(N,BitList) -> PaddedList
 
1434
%% returns a padded (with trailing {bit,0} elements) list of length N
 
1435
%% if Bitlist contains more than N significant bits set an exit asn1_error
 
1436
%% is generated
 
1437
 
 
1438
% pad_list(N,In={Unused,Bin}) ->
 
1439
%     pad_list(N, size(Bin)*8 - Unused, In).
 
1440
 
 
1441
% pad_list(N,Size,In={Unused,Bin}) when N < Size ->
 
1442
%     exit({error,{asn1,{range_error,{bit_string,In}}}});
 
1443
% pad_list(N,Size,{Unused,Bin}) when N > Size, Unused > 0 ->
 
1444
%     pad_list(N,Size+1,{Unused-1,Bin});
 
1445
% pad_list(N,Size,{Unused,Bin}) when N > Size ->
 
1446
%     pad_list(N,Size+1,{7,<<Bin/binary,0>>});
 
1447
% pad_list(N,N,In={Unused,Bin}) ->
 
1448
%     In.
 
1449
 
 
1450
 
 
1451
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
1452
%% X.691:16
 
1453
%% encode_octet_string(Constraint,ExtensionMarker,Val)
 
1454
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
1455
 
 
1456
encode_octet_string(C,Val) ->
 
1457
    encode_octet_string(C,false,Val).
 
1458
 
 
1459
encode_octet_string(C,Bool,{_Name,Val}) ->
 
1460
    encode_octet_string(C,Bool,Val);
 
1461
encode_octet_string(_C,true,_Val) ->
 
1462
    exit({error,{asn1,{'not_supported',extensionmarker}}});
 
1463
encode_octet_string(SZ={_,_},false,Val) ->
 
1464
%    [encode_length(SZ,length(Val)),align,
 
1465
%            {octets,Val}];
 
1466
    Len = length(Val),
 
1467
    [encode_length(SZ,Len),2,
 
1468
     octets_to_complete(Len,Val)];
 
1469
encode_octet_string(SZ,false,Val) when list(SZ) ->
 
1470
    Len = length(Val),
 
1471
    [encode_length({hd(SZ),lists:max(SZ)},Len),2,
 
1472
     octets_to_complete(Len,Val)];
 
1473
encode_octet_string(no,false,Val) ->
 
1474
    Len = length(Val),
 
1475
    [encode_length(undefined,Len),2,
 
1476
     octets_to_complete(Len,Val)];
 
1477
encode_octet_string(C,_,_) ->
 
1478
    exit({error,{not_implemented,C}}).
 
1479
 
 
1480
 
 
1481
decode_octet_string(Bytes,Range) ->
 
1482
    decode_octet_string(Bytes,Range,false).
 
1483
 
 
1484
decode_octet_string(Bytes,1,false) ->
 
1485
    {B1,Bytes2} = getbits(Bytes,8),
 
1486
    {[B1],Bytes2};
 
1487
decode_octet_string(Bytes,2,false) ->
 
1488
    {Bs,Bytes2}= getbits(Bytes,16),
 
1489
    {binary_to_list(<<Bs:16>>),Bytes2};
 
1490
decode_octet_string(Bytes,Sv,false) when integer(Sv),Sv=<65535 ->
 
1491
    Bytes2 = align(Bytes),
 
1492
    getoctets_as_list(Bytes2,Sv);
 
1493
decode_octet_string(Bytes,Sv,false) when integer(Sv) ->
 
1494
    Bytes2 = align(Bytes),
 
1495
    decode_fragmented_octets(Bytes2,Sv);
 
1496
decode_octet_string(Bytes,{Lb,Ub},false) ->
 
1497
    {Len,Bytes2} = decode_length(Bytes,{Lb,Ub}),
 
1498
    Bytes3 = align(Bytes2),
 
1499
    getoctets_as_list(Bytes3,Len);
 
1500
decode_octet_string(Bytes,Sv,false) when list(Sv) ->
 
1501
    {Len,Bytes2} = decode_length(Bytes,{hd(Sv),lists:max(Sv)}),
 
1502
    Bytes3 = align(Bytes2),
 
1503
    getoctets_as_list(Bytes3,Len);
 
1504
decode_octet_string(Bytes,no,false) ->
 
1505
    {Len,Bytes2} = decode_length(Bytes,undefined),
 
1506
    Bytes3 = align(Bytes2),
 
1507
    getoctets_as_list(Bytes3,Len).
 
1508
 
 
1509
 
 
1510
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
1511
%% Restricted char string types
 
1512
%% (NumericString, PrintableString,VisibleString,IA5String,BMPString,UniversalString)
 
1513
%% X.691:26 and X.680:34-36
 
1514
%%encode_restricted_string(aligned,'BMPString',Constraints,Extension,Val)
 
1515
 
 
1516
 
 
1517
encode_restricted_string(aligned,{Name,Val}) when atom(Name) ->
 
1518
    encode_restricted_string(aligned,Val);
 
1519
 
 
1520
encode_restricted_string(aligned,Val) when list(Val)->
 
1521
    Len = length(Val),
 
1522
%    [encode_length(undefined,length(Val)),{octets,Val}].
 
1523
    [encode_length(undefined,Len),octets_to_complete(Len,Val)].
 
1524
 
 
1525
 
 
1526
encode_known_multiplier_string(StringType,SizeC,NumBits,CharOutTab,{Name,Val}) when atom(Name) ->
 
1527
    encode_known_multiplier_string(StringType,SizeC,NumBits,CharOutTab,Val);
 
1528
encode_known_multiplier_string(StringType,SizeC,NumBits,CharOutTab,Val) ->
 
1529
    Result = chars_encode2(Val,NumBits,CharOutTab),
 
1530
    case SizeC of
 
1531
        Ub when integer(Ub), Ub*NumBits =< 16  ->
 
1532
            case {StringType,Result} of
 
1533
                {'BMPString',{octets,Ol}} -> %% this case cannot happen !!??
 
1534
                    [{bits,8,Oct}||Oct <- Ol];
 
1535
                _ ->
 
1536
                    Result
 
1537
            end;
 
1538
        Ub when integer(Ub),Ub =<65535 -> % fixed length
 
1539
%%          [align,Result];
 
1540
            [2,Result];
 
1541
        {Ub,Lb} ->
 
1542
%           [encode_length({Ub,Lb},length(Val)),align,Result];
 
1543
            [encode_length({Ub,Lb},length(Val)),2,Result];
 
1544
        no  ->
 
1545
%           [encode_length(undefined,length(Val)),align,Result]
 
1546
            [encode_length(undefined,length(Val)),2,Result]
 
1547
    end.
 
1548
 
 
1549
decode_restricted_string(Bytes,aligned) ->
 
1550
    {Len,Bytes2} = decode_length(Bytes,undefined),
 
1551
    getoctets_as_list(Bytes2,Len).
 
1552
 
 
1553
decode_known_multiplier_string(StringType,SizeC,NumBits,CharInTab,Bytes) ->
 
1554
    case SizeC of
 
1555
        Ub when integer(Ub), Ub*NumBits =< 16  ->
 
1556
            chars_decode(Bytes,NumBits,StringType,CharInTab,Ub);
 
1557
        Ub when integer(Ub),Ub =<65535 -> % fixed length
 
1558
            Bytes1 = align(Bytes),
 
1559
            chars_decode(Bytes1,NumBits,StringType,CharInTab,Ub);
 
1560
        Vl when list(Vl) ->
 
1561
            {Len,Bytes1} = decode_length(Bytes,{hd(Vl),lists:max(Vl)}),
 
1562
            Bytes2 = align(Bytes1),
 
1563
            chars_decode(Bytes2,NumBits,StringType,CharInTab,Len);
 
1564
        no  ->
 
1565
            {Len,Bytes1} = decode_length(Bytes,undefined),
 
1566
            Bytes2 = align(Bytes1),
 
1567
            chars_decode(Bytes2,NumBits,StringType,CharInTab,Len);
 
1568
        {Lb,Ub}->
 
1569
            {Len,Bytes1} = decode_length(Bytes,{Lb,Ub}),
 
1570
            Bytes2 = align(Bytes1),
 
1571
            chars_decode(Bytes2,NumBits,StringType,CharInTab,Len)
 
1572
    end.
 
1573
 
 
1574
encode_GeneralString(_C,Val) ->
 
1575
    encode_restricted_string(aligned,Val).
 
1576
decode_GeneralString(Bytes,_C) ->
 
1577
    decode_restricted_string(Bytes,aligned).
 
1578
 
 
1579
encode_GraphicString(_C,Val) ->
 
1580
    encode_restricted_string(aligned,Val).
 
1581
decode_GraphicString(Bytes,_C) ->
 
1582
    decode_restricted_string(Bytes,aligned).
 
1583
 
 
1584
encode_ObjectDescriptor(_C,Val) ->
 
1585
    encode_restricted_string(aligned,Val).
 
1586
decode_ObjectDescriptor(Bytes) ->
 
1587
    decode_restricted_string(Bytes,aligned).
 
1588
 
 
1589
encode_TeletexString(_C,Val) -> % equivalent with T61String
 
1590
    encode_restricted_string(aligned,Val).
 
1591
decode_TeletexString(Bytes,_C) ->
 
1592
    decode_restricted_string(Bytes,aligned).
 
1593
 
 
1594
encode_VideotexString(_C,Val) ->
 
1595
    encode_restricted_string(aligned,Val).
 
1596
decode_VideotexString(Bytes,_C) ->
 
1597
    decode_restricted_string(Bytes,aligned).
 
1598
 
 
1599
 
 
1600
 
 
1601
 
 
1602
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
1603
%% getBMPChars(Bytes,Len) ->{BMPcharList,RemainingBytes}
 
1604
%%
 
1605
getBMPChars(Bytes,1) ->
 
1606
    {O1,Bytes2} = getbits(Bytes,8),
 
1607
    {O2,Bytes3} = getbits(Bytes2,8),
 
1608
    if
 
1609
        O1 == 0 ->
 
1610
            {[O2],Bytes3};
 
1611
        true ->
 
1612
            {[{0,0,O1,O2}],Bytes3}
 
1613
    end;
 
1614
getBMPChars(Bytes,Len) ->
 
1615
    getBMPChars(Bytes,Len,[]).
 
1616
 
 
1617
getBMPChars(Bytes,0,Acc) ->
 
1618
    {lists:reverse(Acc),Bytes};
 
1619
getBMPChars(Bytes,Len,Acc) ->
 
1620
    {Octs,Bytes1} = getoctets_as_list(Bytes,2),
 
1621
    case Octs of
 
1622
        [0,O2] ->
 
1623
            getBMPChars(Bytes1,Len-1,[O2|Acc]);
 
1624
        [O1,O2]->
 
1625
            getBMPChars(Bytes1,Len-1,[{0,0,O1,O2}|Acc])
 
1626
    end.
 
1627
 
 
1628
 
 
1629
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
1630
%% chars_encode(C,StringType,Value) -> ValueList
 
1631
%%
 
1632
%% encodes chars according to the per rules taking the constraint PermittedAlphabet
 
1633
%% into account.
 
1634
%% This function does only encode the value part and NOT the length
 
1635
 
 
1636
% chars_encode(C,StringType,Value) ->
 
1637
%     case {StringType,get_constraint(C,'PermittedAlphabet')} of
 
1638
%       {'UniversalString',{_,Sv}} ->
 
1639
%           exit({error,{asn1,{'not implemented',"UniversalString with PermittedAlphabet constraint"}}});
 
1640
%       {'BMPString',{_,Sv}} ->
 
1641
%           exit({error,{asn1,{'not implemented',"BMPString with PermittedAlphabet constraint"}}});
 
1642
%       _ ->
 
1643
%           {NumBits,CharOutTab} = {get_NumBits(C,StringType),get_CharOutTab(C,StringType)},
 
1644
%           chars_encode2(Value,NumBits,CharOutTab)
 
1645
%     end.
 
1646
 
 
1647
 
 
1648
chars_encode2([H|T],NumBits,T1={Min,Max,notab}) when  H =< Max, H >= Min ->
 
1649
%    [[10,NumBits,H-Min]|chars_encode2(T,NumBits,T1)];
 
1650
    [pre_complete_bits(NumBits,H-Min)|chars_encode2(T,NumBits,T1)];
 
1651
chars_encode2([H|T],NumBits,T1={Min,Max,Tab}) when H =< Max, H >= Min ->
 
1652
%    [[10,NumBits,element(H-Min+1,Tab)]|chars_encode2(T,NumBits,T1)];
 
1653
    [pre_complete_bits(NumBits,exit_if_false(H,element(H-Min+1,Tab)))|
 
1654
     chars_encode2(T,NumBits,T1)];
 
1655
chars_encode2([{A,B,C,D}|T],NumBits,T1={Min,_Max,notab}) ->
 
1656
    %% no value range check here (ought to be, but very expensive)
 
1657
%    [{bits,NumBits,(A*B*C*D)-Min}|chars_encode2(T,NumBits,{Min,Max,notab})];
 
1658
%    [[10,NumBits,((((((A bsl 8)+B) bsl 8)+C) bsl 8)+D)-Min]|chars_encode2(T,NumBits,T1)];
 
1659
    [pre_complete_bits(NumBits,
 
1660
                               ((((((A bsl 8)+B) bsl 8)+C) bsl 8)+D)-Min)|
 
1661
     chars_encode2(T,NumBits,T1)];
 
1662
chars_encode2([H={A,B,C,D}|T],NumBits,{Min,Max,Tab}) ->
 
1663
    %% no value range check here (ought to be, but very expensive)
 
1664
    [pre_complete_bits(NumBits,exit_if_false(H,element(((((((A bsl 8)+B) bsl 8)+C) bsl 8)+D)-Min,Tab)))|chars_encode2(T,NumBits,{Min,Max,notab})];
 
1665
chars_encode2([H|_T],_NumBits,{_Min,_Max,_Tab}) ->
 
1666
    exit({error,{asn1,{illegal_char_value,H}}});
 
1667
chars_encode2([],_,_) ->
 
1668
    [].
 
1669
 
 
1670
exit_if_false(V,false)->
 
1671
    exit({error,{asn1,{"illegal value according to Permitted alphabet constraint",V}}});
 
1672
exit_if_false(_,V) ->V.
 
1673
 
 
1674
pre_complete_bits(NumBits,Val) when NumBits =< 8 ->
 
1675
    [10,NumBits,Val];
 
1676
pre_complete_bits(NumBits,Val) when NumBits =< 16 ->
 
1677
    [10,NumBits-8,Val bsr 8,10,8,(Val band 255)];
 
1678
pre_complete_bits(NumBits,Val) when NumBits =< 2040 -> % 255 * 8
 
1679
%     LBUsed = NumBits rem 8,
 
1680
%     {Unused,Len} = case (8 - LBUsed) of
 
1681
%                      8 -> {0,NumBits div 8};
 
1682
%                      U -> {U,(NumBits div 8) + 1}
 
1683
%                  end,
 
1684
%     NewVal = Val bsr LBUsed,
 
1685
%     [30,Unused,Len,<<NewVal:Len/unit:8,Val:LBUsed,0:Unused>>].
 
1686
    Unused = (8 - (NumBits rem 8)) rem 8,
 
1687
    Len = NumBits + Unused,
 
1688
    [30,Unused,Len div 8,<<(Val bsl Unused):Len>>].
 
1689
 
 
1690
% get_NumBits(C,StringType) ->
 
1691
%     case get_constraint(C,'PermittedAlphabet') of
 
1692
%       {'SingleValue',Sv} ->
 
1693
%           charbits(length(Sv),aligned);
 
1694
%       no ->
 
1695
%           case StringType of
 
1696
%               'IA5String' ->
 
1697
%                   charbits(128,aligned); % 16#00..16#7F
 
1698
%               'VisibleString' ->
 
1699
%                   charbits(95,aligned); % 16#20..16#7E
 
1700
%               'PrintableString' ->
 
1701
%                   charbits(74,aligned); % [$\s,$',$(,$),$+,$,,$-,$.,$/,"0123456789",$:,$=,$?,$A..$Z,$a..$z
 
1702
%               'NumericString' ->
 
1703
%                   charbits(11,aligned); % $ ,"0123456789"
 
1704
%               'UniversalString' ->
 
1705
%                   32;
 
1706
%               'BMPString' ->
 
1707
%                   16
 
1708
%           end
 
1709
%     end.
 
1710
 
 
1711
%%Maybe used later
 
1712
%%get_MaxChar(C,StringType) ->
 
1713
%%    case get_constraint(C,'PermittedAlphabet') of
 
1714
%%      {'SingleValue',Sv} ->
 
1715
%%          lists:nth(length(Sv),Sv);
 
1716
%%      no ->
 
1717
%%          case StringType of
 
1718
%%              'IA5String' ->
 
1719
%%                  16#7F; % 16#00..16#7F
 
1720
%%              'VisibleString' ->
 
1721
%%                  16#7E; % 16#20..16#7E
 
1722
%%              'PrintableString' ->
 
1723
%%                  $z; % [$\s,$',$(,$),$+,$,,$-,$.,$/,"0123456789",$:,$=,$?,$A..$Z,$a..$z
 
1724
%%              'NumericString' ->
 
1725
%%                  $9; % $ ,"0123456789"
 
1726
%%              'UniversalString' ->
 
1727
%%                  16#ffffffff;
 
1728
%%              'BMPString' ->
 
1729
%%                  16#ffff
 
1730
%%          end
 
1731
%%    end.
 
1732
 
 
1733
%%Maybe used later
 
1734
%%get_MinChar(C,StringType) ->
 
1735
%%    case get_constraint(C,'PermittedAlphabet') of
 
1736
%%      {'SingleValue',Sv} ->
 
1737
%%          hd(Sv);
 
1738
%%      no ->
 
1739
%%          case StringType of
 
1740
%%              'IA5String' ->
 
1741
%%                  16#00; % 16#00..16#7F
 
1742
%%              'VisibleString' ->
 
1743
%%                  16#20; % 16#20..16#7E
 
1744
%%              'PrintableString' ->
 
1745
%%                  $\s; % [$\s,$',$(,$),$+,$,,$-,$.,$/,"0123456789",$:,$=,$?,$A..$Z,$a..$z
 
1746
%%              'NumericString' ->
 
1747
%%                  $\s; % $ ,"0123456789"
 
1748
%%              'UniversalString' ->
 
1749
%%                  16#00;
 
1750
%%              'BMPString' ->
 
1751
%%                  16#00
 
1752
%%          end
 
1753
%%    end.
 
1754
 
 
1755
% get_CharOutTab(C,StringType) ->
 
1756
%     get_CharTab(C,StringType,out).
 
1757
 
 
1758
% get_CharInTab(C,StringType) ->
 
1759
%     get_CharTab(C,StringType,in).
 
1760
 
 
1761
% get_CharTab(C,StringType,InOut) ->
 
1762
%     case get_constraint(C,'PermittedAlphabet') of
 
1763
%       {'SingleValue',Sv} ->
 
1764
%           get_CharTab2(C,StringType,hd(Sv),lists:max(Sv),Sv,InOut);
 
1765
%       no ->
 
1766
%           case StringType of
 
1767
%               'IA5String' ->
 
1768
%                   {0,16#7F,notab};
 
1769
%               'VisibleString' ->
 
1770
%                   get_CharTab2(C,StringType,16#20,16#7F,notab,InOut);
 
1771
%               'PrintableString' ->
 
1772
%                   Chars = lists:sort(
 
1773
%                             " '()+,-./0123456789:=?ABCDEFGHIJKLMNOPQRSTUVWXYZabcdefghijklmnopqrstuvwxyz"),
 
1774
%                   get_CharTab2(C,StringType,hd(Chars),lists:max(Chars),Chars,InOut);
 
1775
%               'NumericString' ->
 
1776
%                   get_CharTab2(C,StringType,16#20,$9," 0123456789",InOut);
 
1777
%               'UniversalString' ->
 
1778
%                   {0,16#FFFFFFFF,notab};
 
1779
%               'BMPString' ->
 
1780
%                   {0,16#FFFF,notab}
 
1781
%           end
 
1782
%     end.
 
1783
 
 
1784
% get_CharTab2(C,StringType,Min,Max,Chars,InOut) ->
 
1785
%     BitValMax = (1 bsl get_NumBits(C,StringType))-1,
 
1786
%     if
 
1787
%       Max =< BitValMax ->
 
1788
%           {0,Max,notab};
 
1789
%       true ->
 
1790
%           case InOut of
 
1791
%               out ->
 
1792
%                   {Min,Max,create_char_tab(Min,Chars)};
 
1793
%               in  ->
 
1794
%                   {Min,Max,list_to_tuple(Chars)}
 
1795
%           end
 
1796
%     end.
 
1797
 
 
1798
% create_char_tab(Min,L) ->
 
1799
%     list_to_tuple(create_char_tab(Min,L,0)).
 
1800
% create_char_tab(Min,[Min|T],V) ->
 
1801
%     [V|create_char_tab(Min+1,T,V+1)];
 
1802
% create_char_tab(_Min,[],_V) ->
 
1803
%     [];
 
1804
% create_char_tab(Min,L,V) ->
 
1805
%     [false|create_char_tab(Min+1,L,V)].
 
1806
 
 
1807
%% This very inefficient and should be moved to compiletime
 
1808
% charbits(NumOfChars,aligned) ->
 
1809
%     case charbits(NumOfChars) of
 
1810
%       1 -> 1;
 
1811
%       2 -> 2;
 
1812
%       B when B =< 4 -> 4;
 
1813
%       B when B =< 8 -> 8;
 
1814
%       B when B =< 16 -> 16;
 
1815
%       B when B =< 32 -> 32
 
1816
%     end.
 
1817
 
 
1818
% charbits(NumOfChars) when NumOfChars =< 2 -> 1;
 
1819
% charbits(NumOfChars) when NumOfChars =< 4 -> 2;
 
1820
% charbits(NumOfChars) when NumOfChars =< 8 -> 3;
 
1821
% charbits(NumOfChars) when NumOfChars =< 16 -> 4;
 
1822
% charbits(NumOfChars) when NumOfChars =< 32 -> 5;
 
1823
% charbits(NumOfChars) when NumOfChars =< 64 -> 6;
 
1824
% charbits(NumOfChars) when NumOfChars =< 128 -> 7;
 
1825
% charbits(NumOfChars) when NumOfChars =< 256 -> 8;
 
1826
% charbits(NumOfChars) when NumOfChars =< 512 -> 9;
 
1827
% charbits(NumOfChars) when NumOfChars =< 1024 -> 10;
 
1828
% charbits(NumOfChars) when NumOfChars =< 2048 -> 11;
 
1829
% charbits(NumOfChars) when NumOfChars =< 4096 -> 12;
 
1830
% charbits(NumOfChars) when NumOfChars =< 8192 -> 13;
 
1831
% charbits(NumOfChars) when NumOfChars =< 16384 -> 14;
 
1832
% charbits(NumOfChars) when NumOfChars =< 32768 -> 15;
 
1833
% charbits(NumOfChars) when NumOfChars =< 65536 -> 16;
 
1834
% charbits(NumOfChars) when integer(NumOfChars) ->
 
1835
%     16 + charbits1(NumOfChars bsr 16).
 
1836
 
 
1837
% charbits1(0) ->
 
1838
%     0;
 
1839
% charbits1(NumOfChars) ->
 
1840
%     1 + charbits1(NumOfChars bsr 1).
 
1841
 
 
1842
 
 
1843
chars_decode(Bytes,_,'BMPString',_,Len) ->
 
1844
    getBMPChars(Bytes,Len);
 
1845
chars_decode(Bytes,NumBits,_StringType,CharInTab,Len) ->
 
1846
    chars_decode2(Bytes,CharInTab,NumBits,Len).
 
1847
 
 
1848
 
 
1849
chars_decode2(Bytes,CharInTab,NumBits,Len) ->
 
1850
    chars_decode2(Bytes,CharInTab,NumBits,Len,[]).
 
1851
 
 
1852
chars_decode2(Bytes,_CharInTab,_NumBits,0,Acc) ->
 
1853
    {lists:reverse(Acc),Bytes};
 
1854
chars_decode2(Bytes,{Min,Max,notab},NumBits,Len,Acc) when NumBits > 8 ->
 
1855
    {Char,Bytes2} = getbits(Bytes,NumBits),
 
1856
    Result =
 
1857
        if
 
1858
            Char < 256 -> Char;
 
1859
            true ->
 
1860
                list_to_tuple(binary_to_list(<<Char:32>>))
 
1861
        end,
 
1862
    chars_decode2(Bytes2,{Min,Max,notab},NumBits,Len -1,[Result|Acc]);
 
1863
chars_decode2(Bytes,{Min,Max,notab},NumBits,Len,Acc) ->
 
1864
    {Char,Bytes2} = getbits(Bytes,NumBits),
 
1865
    chars_decode2(Bytes2,{Min,Max,notab},NumBits,Len -1,[Char+Min|Acc]);
 
1866
 
 
1867
%% BMPString and UniversalString with PermittedAlphabet is currently not supported
 
1868
chars_decode2(Bytes,{Min,Max,CharInTab},NumBits,Len,Acc) ->
 
1869
    {Char,Bytes2} = getbits(Bytes,NumBits),
 
1870
    chars_decode2(Bytes2,{Min,Max,CharInTab},NumBits,Len -1,[element(Char+1,CharInTab)|Acc]).
 
1871
 
 
1872
 
 
1873
                                                % X.691:17
 
1874
encode_null(_Val) -> []; % encodes to nothing
 
1875
encode_null({Name,Val}) when atom(Name) ->
 
1876
    encode_null(Val).
 
1877
 
 
1878
decode_null(Bytes) ->
 
1879
    {'NULL',Bytes}.
 
1880
 
 
1881
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
1882
%% encode_object_identifier(Val) -> CompleteList
 
1883
%% encode_object_identifier({Name,Val}) -> CompleteList
 
1884
%% Val -> {Int1,Int2,...,IntN} % N >= 2
 
1885
%% Name -> atom()
 
1886
%% Int1 -> integer(0..2)
 
1887
%% Int2 -> integer(0..39) when Int1 (0..1) else integer()
 
1888
%% Int3-N -> integer()
 
1889
%% CompleteList -> [{bits,8,Val}|{octets,Ol}|align|...]
 
1890
%%
 
1891
encode_object_identifier({Name,Val}) when atom(Name) ->
 
1892
    encode_object_identifier(Val);
 
1893
encode_object_identifier(Val) ->
 
1894
    OctetList = e_object_identifier(Val),
 
1895
    Octets = list_to_binary(OctetList), % performs a flatten at the same time
 
1896
%    [{debug,object_identifier},encode_length(undefined,size(Octets)),{octets,Octets}].
 
1897
    [encode_length(undefined,size(Octets)),
 
1898
     octets_to_complete(size(Octets),Octets)].
 
1899
 
 
1900
%% This code is copied from asn1_encode.erl (BER) and corrected and modified
 
1901
 
 
1902
e_object_identifier({'OBJECT IDENTIFIER',V}) ->
 
1903
    e_object_identifier(V);
 
1904
e_object_identifier({Cname,V}) when atom(Cname),tuple(V) ->
 
1905
    e_object_identifier(tuple_to_list(V));
 
1906
e_object_identifier({Cname,V}) when atom(Cname),list(V) ->
 
1907
    e_object_identifier(V);
 
1908
e_object_identifier(V) when tuple(V) ->
 
1909
    e_object_identifier(tuple_to_list(V));
 
1910
 
 
1911
%% E1 = 0|1|2 and (E2 < 40 when E1 = 0|1)
 
1912
e_object_identifier([E1,E2|Tail]) when E1 >= 0, E1 < 2, E2 < 40 ; E1==2 ->
 
1913
    Head = 40*E1 + E2,  % weird
 
1914
    e_object_elements([Head|Tail],[]);
 
1915
e_object_identifier(Oid=[_,_|_Tail]) ->
 
1916
    exit({error,{asn1,{'illegal_value',Oid}}}).
 
1917
 
 
1918
e_object_elements([],Acc) ->
 
1919
    lists:reverse(Acc);
 
1920
e_object_elements([H|T],Acc) ->
 
1921
    e_object_elements(T,[e_object_element(H)|Acc]).
 
1922
 
 
1923
e_object_element(Num) when Num < 128 ->
 
1924
    Num;
 
1925
%% must be changed to handle more than 2 octets
 
1926
e_object_element(Num) ->  %% when Num < ???
 
1927
    Left = ((Num band 2#11111110000000) bsr 7) bor 2#10000000,
 
1928
    Right = Num band 2#1111111 ,
 
1929
    [Left,Right].
 
1930
 
 
1931
 
 
1932
 
 
1933
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
1934
%% decode_object_identifier(Bytes) -> {ObjId,RemainingBytes}
 
1935
%% ObjId -> {integer(),integer(),...} % at least 2 integers
 
1936
%% RemainingBytes -> [integer()] when integer() (0..255)
 
1937
decode_object_identifier(Bytes) ->
 
1938
    {Len,Bytes2} = decode_length(Bytes,undefined),
 
1939
    {Octs,Bytes3} = getoctets_as_list(Bytes2,Len),
 
1940
    [First|Rest] = dec_subidentifiers(Octs,0,[]),
 
1941
    Idlist = if
 
1942
                 First < 40 ->
 
1943
                     [0,First|Rest];
 
1944
                 First < 80 ->
 
1945
                     [1,First - 40|Rest];
 
1946
                 true ->
 
1947
                     [2,First - 80|Rest]
 
1948
             end,
 
1949
    {list_to_tuple(Idlist),Bytes3}.
 
1950
 
 
1951
dec_subidentifiers([H|T],Av,Al) when H >=16#80 ->
 
1952
    dec_subidentifiers(T,(Av bsl 7) + (H band 16#7F),Al);
 
1953
dec_subidentifiers([H|T],Av,Al) ->
 
1954
    dec_subidentifiers(T,0,[(Av bsl 7) + H |Al]);
 
1955
dec_subidentifiers([],_Av,Al) ->
 
1956
    lists:reverse(Al).
 
1957
 
 
1958
get_constraint([{Key,V}],Key) ->
 
1959
    V;
 
1960
get_constraint([],_) ->
 
1961
    no;
 
1962
get_constraint(C,Key) ->
 
1963
    case lists:keysearch(Key,1,C) of
 
1964
        false ->
 
1965
            no;
 
1966
        {value,{_,V}} ->
 
1967
            V
 
1968
    end.
 
1969
 
 
1970
 
 
1971
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
1972
%% complete(InList) -> ByteList
 
1973
%% Takes a coded list with bits and bytes and converts it to a list of bytes
 
1974
%% Should be applied as the last step at encode of a complete ASN.1 type
 
1975
%%
 
1976
 
 
1977
-ifdef(nodriver).
 
1978
 
 
1979
complete(L) ->
 
1980
    case complete1(L) of
 
1981
        {[],[]} ->
 
1982
            <<0>>;
 
1983
        {Acc,[]} ->
 
1984
            Acc;
 
1985
        {Acc,Bacc}  ->
 
1986
            [Acc|complete_bytes(Bacc)]
 
1987
    end.
 
1988
 
 
1989
 
 
1990
% this function builds the ugly form of lists [E1|E2] to avoid having to reverse it at the end.
 
1991
% this is done because it is efficient and that the result always will be sent on a port or
 
1992
% converted by means of list_to_binary/1
 
1993
 complete1(InList) when list(InList) ->
 
1994
     complete1(InList,[],[]);
 
1995
 complete1(InList) ->
 
1996
     complete1([InList],[],[]).
 
1997
 
 
1998
 complete1([],Acc,Bacc) ->
 
1999
     {Acc,Bacc};
 
2000
 complete1([H|T],Acc,Bacc) when list(H) ->
 
2001
     {NewH,NewBacc} = complete1(H,Acc,Bacc),
 
2002
     complete1(T,NewH,NewBacc);
 
2003
 
 
2004
 complete1([{octets,Bin}|T],Acc,[]) ->
 
2005
     complete1(T,[Acc|Bin],[]);
 
2006
 
 
2007
 complete1([{octets,Bin}|T],Acc,Bacc) ->
 
2008
     complete1(T,[Acc|[complete_bytes(Bacc),Bin]],[]);
 
2009
 
 
2010
 complete1([{debug,_}|T], Acc,Bacc) ->
 
2011
     complete1(T,Acc,Bacc);
 
2012
 
 
2013
 complete1([{bits,N,Val}|T],Acc,Bacc) ->
 
2014
     complete1(T,Acc,complete_update_byte(Bacc,Val,N));
 
2015
 
 
2016
 complete1([{bit,Val}|T],Acc,Bacc) ->
 
2017
     complete1(T,Acc,complete_update_byte(Bacc,Val,1));
 
2018
 
 
2019
 complete1([align|T],Acc,[]) ->
 
2020
     complete1(T,Acc,[]);
 
2021
 complete1([align|T],Acc,Bacc) ->
 
2022
     complete1(T,[Acc|complete_bytes(Bacc)],[]);
 
2023
 complete1([{0,Bin}|T],Acc,[]) when binary(Bin) ->
 
2024
     complete1(T,[Acc|Bin],[]);
 
2025
 complete1([{Unused,Bin}|T],Acc,[]) when integer(Unused),binary(Bin) ->
 
2026
     Size = size(Bin)-1,
 
2027
     <<Bs:Size/binary,B>> = Bin,
 
2028
     NumBits = 8-Unused,
 
2029
     complete1(T,[Acc|Bs],[[B bsr Unused]|NumBits]);
 
2030
 complete1([{Unused,Bin}|T],Acc,Bacc) when integer(Unused),binary(Bin) ->
 
2031
     Size = size(Bin)-1,
 
2032
     <<Bs:Size/binary,B>> = Bin,
 
2033
     NumBits = 8 - Unused,
 
2034
     Bf = complete_bytes(Bacc),
 
2035
     complete1(T,[Acc|[Bf,Bs]],[[B bsr Unused]|NumBits]).
 
2036
 
 
2037
 
 
2038
 complete_update_byte([],Val,Len) ->
 
2039
     complete_update_byte([[0]|0],Val,Len);
 
2040
 complete_update_byte([[Byte|Bacc]|NumBits],Val,Len) when NumBits + Len == 8 ->
 
2041
     [[0,((Byte bsl Len) + Val) band 255|Bacc]|0];
 
2042
 complete_update_byte([[Byte|Bacc]|NumBits],Val,Len) when NumBits + Len > 8  ->
 
2043
     Rem = 8 - NumBits,
 
2044
     Rest = Len - Rem,
 
2045
     complete_update_byte([[0,((Byte bsl Rem) + (Val bsr Rest)) band 255 |Bacc]|0],Val,Rest);
 
2046
 complete_update_byte([[Byte|Bacc]|NumBits],Val,Len) ->
 
2047
     [[((Byte bsl Len) + Val) band 255|Bacc]|NumBits+Len].
 
2048
 
 
2049
 
 
2050
 complete_bytes([[Byte|Bacc]|0]) ->
 
2051
     lists:reverse(Bacc);
 
2052
 complete_bytes([[Byte|Bacc]|NumBytes]) ->
 
2053
     lists:reverse([(Byte bsl (8-NumBytes)) band 255|Bacc]);
 
2054
 complete_bytes([]) ->
 
2055
     [].
 
2056
 
 
2057
-else.
 
2058
 
 
2059
 
 
2060
 complete(L) ->
 
2061
    case catch port_control(drv_complete,1,L) of
 
2062
        Bin when binary(Bin) ->
 
2063
            Bin;
 
2064
        List when list(List) -> handle_error(List,L);
 
2065
        {'EXIT',{badarg,Reason}} ->
 
2066
            asn1rt_driver_handler:load_driver(),
 
2067
            receive
 
2068
                driver_ready ->
 
2069
                    case catch port_control(drv_complete,1,L) of
 
2070
                        Bin2 when binary(Bin2) -> Bin2;
 
2071
                        List when list(List) -> handle_error(List,L);
 
2072
                        Error -> exit(Error)
 
2073
                    end;
 
2074
                {error,Error} -> % error when loading driver
 
2075
                    %% the driver could not be loaded
 
2076
                    exit(Error);
 
2077
                Error={port_error,Reason} ->
 
2078
                    exit(Error)
 
2079
            end;
 
2080
        {'EXIT',Reason} ->
 
2081
            exit(Reason)
 
2082
    end.
 
2083
 
 
2084
handle_error([],_)->
 
2085
    exit({error,{"memory allocation problem"}});
 
2086
handle_error("1",L) -> % error in complete in driver
 
2087
    exit({error,{asn1_error,L}});
 
2088
handle_error(ErrL,L) ->
 
2089
    exit({error,{unknown_error,ErrL,L}}).
 
2090
 
 
2091
-endif.
 
2092
 
 
2093
 
 
2094
octets_to_complete(Len,Val) when Len < 256 ->
 
2095
    [20,Len,Val];
 
2096
octets_to_complete(Len,Val) ->
 
2097
    [21,<<Len:16>>,Val].
 
2098
 
 
2099
octets_unused_to_complete(Unused,Len,Val) when Len < 256 ->
 
2100
    [30,Unused,Len,Val];
 
2101
octets_unused_to_complete(Unused,Len,Val) ->
 
2102
    [31,Unused,<<Len:16>>,Val].