~rdoering/ubuntu/karmic/erlang/fix-535090

« back to all changes in this revision

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

  • Committer: Bazaar Package Importer
  • Author(s): Sergei Golovan
  • Date: 2009-02-15 16:42:52 UTC
  • mfrom: (1.1.13 upstream)
  • mto: (3.3.1 squeeze)
  • mto: This revision was merged to the branch mainline in revision 17.
  • Revision ID: james.westby@ubuntu.com-20090215164252-dxpjjuq108nz4noa
Upload to unstable after lenny is released.

Show diffs side-by-side

added added

removed removed

Lines of Context:
 
1
%%<copyright>
 
2
%% <year>2008-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,
 
7
%% Version 1.1, (the "License"); you may not use this file except in
 
8
%% compliance with the License. You should have received a copy of the
 
9
%% Erlang Public License along with this software. If not, it can be
 
10
%% retrieved online at http://www.erlang.org/.
 
11
%%
 
12
%% Software distributed under the License is distributed on an "AS IS"
 
13
%% basis, WITHOUT WARRANTY OF ANY KIND, either express or implied. See
 
14
%% the License for the specific language governing rights and limitations
 
15
%% under the License.
 
16
%%
 
17
%% The Initial Developer of the Original Code is Ericsson AB.
 
18
%%</legalnotice>
 
19
%%
 
20
-module(asn1rt_uper_bin).
 
21
 
 
22
%% encoding / decoding of PER unaligned
 
23
 
 
24
-include("asn1_records.hrl").
 
25
 
 
26
%%-compile(export_all).
 
27
 
 
28
 -export([cindex/3, list_to_record/2]).
 
29
 -export([setext/1, fixoptionals/3, 
 
30
         fixextensions/2, 
 
31
         getext/1, getextension/2, skipextensions/3, getbit/1, getchoice/3 ]).
 
32
 -export([getoptionals2/2, set_choice/3, encode_integer/2, encode_integer/3  ]).
 
33
 -export([decode_integer/2, decode_integer/3, encode_small_number/1, encode_boolean/1, 
 
34
         decode_boolean/1, encode_length/2, decode_length/1, decode_length/2,
 
35
         encode_small_length/1, decode_small_length/1,
 
36
         decode_compact_bit_string/3]).
 
37
 -export([decode_enumerated/3, 
 
38
         encode_bit_string/3, decode_bit_string/3  ]).
 
39
 -export([encode_octet_string/2, decode_octet_string/2,
 
40
          encode_null/1, decode_null/1,
 
41
          encode_relative_oid/1, decode_relative_oid/1,
 
42
         encode_object_identifier/1, decode_object_identifier/1,
 
43
          encode_real/1, decode_real/1,
 
44
         complete/1, complete_NFP/1]).
 
45
 
 
46
 
 
47
 -export([encode_open_type/2, decode_open_type/2]).
 
48
 
 
49
 -export([encode_UniversalString/2, decode_UniversalString/2,
 
50
         encode_PrintableString/2, decode_PrintableString/2,
 
51
         encode_GeneralString/2, decode_GeneralString/2,
 
52
         encode_GraphicString/2, decode_GraphicString/2,
 
53
         encode_TeletexString/2, decode_TeletexString/2,
 
54
         encode_VideotexString/2, decode_VideotexString/2,
 
55
         encode_VisibleString/2, decode_VisibleString/2,
 
56
         encode_UTF8String/1, decode_UTF8String/1,
 
57
         encode_BMPString/2, decode_BMPString/2,
 
58
         encode_IA5String/2, decode_IA5String/2,
 
59
         encode_NumericString/2, decode_NumericString/2,
 
60
         encode_ObjectDescriptor/2, decode_ObjectDescriptor/1
 
61
        ]).
 
62
 
 
63
-define('16K',16384).
 
64
-define('32K',32768).
 
65
-define('64K',65536).
 
66
 
 
67
 
 
68
cindex(Ix,Val,Cname) ->
 
69
    case element(Ix,Val) of
 
70
        {Cname,Val2} -> Val2;
 
71
        X -> X
 
72
    end.
 
73
 
 
74
%% converts a list to a record if necessary
 
75
list_to_record(_Name,Tuple) when tuple(Tuple) ->
 
76
    Tuple;
 
77
list_to_record(Name,List) when list(List) ->
 
78
    list_to_tuple([Name|List]).
 
79
 
 
80
 
 
81
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
82
%% setext(true|false) ->  CompleteList
 
83
%%
 
84
 
 
85
setext(false) ->
 
86
    <<0:1>>;
 
87
setext(true) ->
 
88
    <<1:1>>.
 
89
 
 
90
 
 
91
 
 
92
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
93
%% This is the new fixoptionals/3 which is used by the new generates
 
94
%%
 
95
fixoptionals(OptList,OptLength,Val) when tuple(Val) ->
 
96
    Bits = fixoptionals(OptList,Val,0),
 
97
    {Val,<<Bits:OptLength>>};
 
98
 
 
99
fixoptionals([],_Val,Acc) ->
 
100
    %% Optbits
 
101
    Acc;
 
102
fixoptionals([Pos|Ot],Val,Acc) ->
 
103
    case element(Pos,Val) of
 
104
        asn1_NOVALUE -> fixoptionals(Ot,Val,Acc bsl 1);
 
105
        asn1_DEFAULT -> fixoptionals(Ot,Val,Acc bsl 1);
 
106
        _ -> fixoptionals(Ot,Val,(Acc bsl 1) + 1)
 
107
    end.
 
108
 
 
109
 
 
110
getext(Bytes) when is_bitstring(Bytes) ->
 
111
    getbit(Bytes).
 
112
 
 
113
getextension(0, Bytes) ->
 
114
    {{},Bytes};
 
115
getextension(1, Bytes) ->
 
116
    {Len,Bytes2} = decode_small_length(Bytes),
 
117
    {Blist, Bytes3} = getbits_as_list(Len,Bytes2),
 
118
    {list_to_tuple(Blist),Bytes3}.
 
119
 
 
120
fixextensions({ext,ExtPos,ExtNum},Val) ->
 
121
    case fixextensions(ExtPos,ExtNum+ExtPos,Val,0) of
 
122
        0 -> [];
 
123
        ExtBits ->
 
124
            [encode_small_length(ExtNum),<<ExtBits:ExtNum>>]
 
125
    end.
 
126
 
 
127
fixextensions(Pos,MaxPos,_,Acc) when Pos >= MaxPos ->
 
128
    Acc;
 
129
fixextensions(Pos,ExtPos,Val,Acc) ->
 
130
    Bit = case catch(element(Pos+1,Val)) of
 
131
              asn1_NOVALUE ->
 
132
                  0;
 
133
              asn1_NOEXTVALUE ->
 
134
                  0;
 
135
              {'EXIT',_} ->
 
136
                  0;
 
137
              _ ->
 
138
                  1
 
139
          end,
 
140
    fixextensions(Pos+1,ExtPos,Val,(Acc bsl 1)+Bit).
 
141
 
 
142
skipextensions(Bytes,Nr,ExtensionBitPattern) -> 
 
143
    case (catch element(Nr,ExtensionBitPattern)) of
 
144
        1 ->
 
145
            {_,Bytes2} = decode_open_type(Bytes,[]),
 
146
            skipextensions(Bytes2, Nr+1, ExtensionBitPattern);
 
147
        0 ->
 
148
            skipextensions(Bytes, Nr+1, ExtensionBitPattern);
 
149
        {'EXIT',_} -> % badarg, no more extensions
 
150
            Bytes
 
151
    end.
 
152
 
 
153
 
 
154
getchoice(Bytes,1,0) -> % only 1 alternative is not encoded
 
155
    {0,Bytes};
 
156
getchoice(Bytes,_,1) ->
 
157
    decode_small_number(Bytes);
 
158
getchoice(Bytes,NumChoices,0) ->
 
159
    decode_constrained_number(Bytes,{0,NumChoices-1}).
 
160
 
 
161
 
 
162
%%%%%%%%%%%%%%%
 
163
getoptionals2(Bytes,NumOpt) ->
 
164
    getbits(Bytes,NumOpt).
 
165
 
 
166
 
 
167
%% getbits_as_binary(Num,Bytes) -> {{Unused,BinBits},RestBytes},
 
168
%% Num = integer(),
 
169
%% Bytes = list() | tuple(),
 
170
%% Unused = integer(),
 
171
%% BinBits = binary(),
 
172
%% RestBytes = tuple()
 
173
getbits_as_binary(Num,Bytes) when is_bitstring(Bytes) ->
 
174
    <<BS:Num/bitstring,Rest/bitstring>> = Bytes,
 
175
    {BS,Rest}.
 
176
 
 
177
getbits_as_list(Num,Bytes) when is_bitstring(Bytes) ->
 
178
    <<BitStr:Num/bitstring,Rest/bitstring>> = Bytes,
 
179
    {[ B || <<B:1>> <= BitStr],Rest}.
 
180
 
 
181
getbit(Buffer) ->
 
182
    <<B:1,Rest/bitstring>> = Buffer,
 
183
    {B,Rest}.
 
184
 
 
185
 
 
186
getbits(Buffer,Num) when is_bitstring(Buffer) ->
 
187
    <<Bs:Num,Rest/bitstring>> = Buffer,
 
188
    {Bs,Rest}.
 
189
 
 
190
 
 
191
 
 
192
%% Pick the first Num octets.
 
193
%% Returns octets as an integer with bit significance as in buffer.
 
194
getoctets(Buffer,Num) when is_bitstring(Buffer) ->
 
195
    <<Val:Num/integer-unit:8,RestBitStr/bitstring>> = Buffer,
 
196
    {Val,RestBitStr}.
 
197
 
 
198
%% Pick the first Num octets.
 
199
%% Returns octets as a binary
 
200
getoctets_as_bin(Bin,Num) when is_bitstring(Bin) ->
 
201
    <<Octets:Num/binary,RestBin/bitstring>> = Bin,
 
202
    {Octets,RestBin}.
 
203
 
 
204
%% same as above but returns octets as a List
 
205
getoctets_as_list(Buffer,Num) ->
 
206
    {Bin,Buffer2} = getoctets_as_bin(Buffer,Num),
 
207
    {binary_to_list(Bin),Buffer2}.
 
208
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
209
%% set_choice(Alt,Choices,Altnum) -> ListofBitSettings
 
210
%% Alt = atom()
 
211
%% Altnum = integer() | {integer(),integer()}% number of alternatives
 
212
%% Choices = [atom()] | {[atom()],[atom()]}
 
213
%% When Choices is a tuple the first list is the Rootset and the
 
214
%% second is the Extensions and then Altnum must also be a tuple with the
 
215
%% lengths of the 2 lists 
 
216
%%
 
217
set_choice(Alt,{L1,L2},{Len1,_Len2}) ->
 
218
    case set_choice_tag(Alt,L1) of
 
219
        N when integer(N), Len1 > 1 ->
 
220
            [<<0:1>>, % the value is in the root set
 
221
             encode_integer([{'ValueRange',{0,Len1-1}}],N)];
 
222
        N when integer(N) ->
 
223
            <<0:1>>; % no encoding if only 0 or 1 alternative
 
224
        false ->
 
225
            [<<1:1>>, % extension value
 
226
             case set_choice_tag(Alt,L2) of
 
227
                 N2 when integer(N2) ->
 
228
                     encode_small_number(N2);
 
229
                 false ->
 
230
                     unknown_choice_alt
 
231
             end]
 
232
    end;
 
233
set_choice(Alt,L,Len) ->
 
234
    case set_choice_tag(Alt,L) of
 
235
        N when integer(N), Len > 1 ->
 
236
            encode_integer([{'ValueRange',{0,Len-1}}],N);
 
237
        N when integer(N) ->
 
238
            []; % no encoding if only 0 or 1 alternative
 
239
        false ->
 
240
            [unknown_choice_alt]
 
241
    end.
 
242
 
 
243
set_choice_tag(Alt,Choices) ->
 
244
    set_choice_tag(Alt,Choices,0).
 
245
 
 
246
set_choice_tag(Alt,[Alt|_Rest],Tag) ->
 
247
    Tag;
 
248
set_choice_tag(Alt,[_H|Rest],Tag) ->
 
249
    set_choice_tag(Alt,Rest,Tag+1);
 
250
set_choice_tag(_Alt,[],_Tag) ->
 
251
    false.
 
252
 
 
253
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
254
%% decode_fragmented_XXX; decode of values encoded fragmented according
 
255
%% to ITU-T X.691 clause 10.9.3.8. The unit (XXX) is either bits, octets,
 
256
%% characters or number of components (in a choice,sequence or similar).
 
257
%% Buffer is a buffer {Used, Bin}.
 
258
%% C is the constrained length.
 
259
%% If the buffer is not aligned, this function does that.
 
260
decode_fragmented_bits(Buffer,C) ->
 
261
    decode_fragmented_bits(Buffer,C,[]).
 
262
decode_fragmented_bits(<<3:2,Len:6,BitStr/bitstring>>,C,Acc) ->
 
263
%%    {Value,Bin2} = split_binary(Bin, Len * ?'16K'),
 
264
    FragLen = (Len*?'16K') div 8,
 
265
    <<Value:FragLen/binary,BitStr2/bitstring>> = BitStr,
 
266
    decode_fragmented_bits(BitStr2,C,[Value|Acc]);
 
267
decode_fragmented_bits(<<0:1,0:7,BitStr/bitstring>>,C,Acc) ->
 
268
    BinBits = list_to_binary(lists:reverse(Acc)),
 
269
    case C of
 
270
        Int when integer(Int),C == size(BinBits) ->
 
271
            {BinBits,BitStr};
 
272
        Int when integer(Int) ->
 
273
            exit({error,{asn1,{illegal_value,C,BinBits}}})
 
274
    end;
 
275
decode_fragmented_bits(<<0:1,Len:7,BitStr/bitstring>>,C,Acc) ->
 
276
    <<Val:Len/bitstring,Rest/bitstring>> = BitStr,
 
277
%%    <<Value:Len/binary-unit:1,Bin2/binary>> = Bin,
 
278
    ResBitStr = list_to_bitstring(lists:reverse([Val|Acc])),
 
279
    case C of
 
280
        Int when integer(Int),C == bit_size(ResBitStr) ->
 
281
            {ResBitStr,Rest};
 
282
        Int when integer(Int) ->
 
283
            exit({error,{asn1,{illegal_value,C,ResBitStr}}})
 
284
    end.
 
285
 
 
286
 
 
287
decode_fragmented_octets({0,Bin},C) ->
 
288
    decode_fragmented_octets(Bin,C,[]).
 
289
 
 
290
decode_fragmented_octets(<<3:2,Len:6,BitStr/bitstring>>,C,Acc) ->
 
291
    FragLen = Len * ?'16K',
 
292
    <<Value:FragLen/binary,Rest/bitstring>> = BitStr,
 
293
    decode_fragmented_octets(Rest,C,[Value|Acc]);
 
294
decode_fragmented_octets(<<0:1,0:7,Bin/bitstring>>,C,Acc) ->
 
295
    Octets = list_to_binary(lists:reverse(Acc)),
 
296
    case C of
 
297
        Int when integer(Int), C == size(Octets) ->
 
298
            {Octets,Bin};
 
299
        Int when integer(Int) ->
 
300
            exit({error,{asn1,{illegal_value,C,Octets}}})
 
301
    end;
 
302
decode_fragmented_octets(<<0:1,Len:7,BitStr/bitstring>>,C,Acc) ->
 
303
    <<Value:Len/binary-unit:8,BitStr2/binary>> = BitStr,
 
304
    BinOctets = list_to_binary(lists:reverse([Value|Acc])),
 
305
    case C of
 
306
        Int when integer(Int),size(BinOctets) == Int ->
 
307
            {BinOctets,BitStr2};
 
308
        Int when integer(Int) ->
 
309
            exit({error,{asn1,{illegal_value,C,BinOctets}}})
 
310
    end.
 
311
 
 
312
 
 
313
    
 
314
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
315
%% encode_open_type(Constraint, Value) -> CompleteList
 
316
%% Value = list of bytes of an already encoded value (the list must be flat)
 
317
%%         | binary
 
318
%% Contraint = not used in this version
 
319
%%
 
320
encode_open_type(C, Val) when list(Val) ->
 
321
    encode_open_type(C, list_to_binary(Val));
 
322
encode_open_type(_C, Val) when binary(Val) ->
 
323
    [encode_length(undefined,size(Val)),Val].
 
324
 
 
325
 
 
326
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
327
%% decode_open_type(Buffer,Constraint) -> Value
 
328
%% Constraint is not used in this version
 
329
%% Buffer = [byte] with PER encoded data 
 
330
%% Value = [byte] with decoded data (which must be decoded again as some type)
 
331
%%
 
332
decode_open_type(Bytes, _C) ->
 
333
    {Len,Bytes2} = decode_length(Bytes,undefined),
 
334
    getoctets_as_bin(Bytes2,Len).
 
335
 
 
336
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
337
%% encode_integer(Constraint,Value,NamedNumberList) -> CompleteList
 
338
%% encode_integer(Constraint,Value) -> CompleteList
 
339
%% encode_integer(Constraint,{Name,Value}) -> CompleteList
 
340
%% 
 
341
%%
 
342
encode_integer(C,V,NamedNumberList) when atom(V) ->
 
343
    case lists:keysearch(V,1,NamedNumberList) of
 
344
        {value,{_,NewV}} -> 
 
345
            encode_integer(C,NewV);
 
346
        _ -> 
 
347
            exit({error,{asn1,{namednumber,V}}})
 
348
    end;
 
349
encode_integer(C,V,_NamedNumberList) when integer(V) ->
 
350
    encode_integer(C,V);
 
351
encode_integer(C,{Name,V},NamedNumberList) when atom(Name) ->
 
352
    encode_integer(C,V,NamedNumberList).
 
353
 
 
354
encode_integer(C,{Name,Val}) when atom(Name) ->
 
355
    encode_integer(C,Val);
 
356
 
 
357
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.
 
358
    case (catch encode_integer([Rc],Val)) of
 
359
        {'EXIT',{error,{asn1,_}}} ->
 
360
            [<<1:1>>,encode_unconstrained_number(Val)];
 
361
        Encoded ->
 
362
            [<<0:1>>,Encoded]
 
363
    end;
 
364
encode_integer(C,Val ) when list(C) ->
 
365
    case get_constraint(C,'SingleValue') of
 
366
        no ->
 
367
            encode_integer1(C,Val);
 
368
        V when integer(V),V == Val ->
 
369
            []; % a type restricted to a single value encodes to nothing
 
370
        V when list(V) ->
 
371
            case lists:member(Val,V) of
 
372
                true ->
 
373
                    encode_integer1(C,Val);
 
374
                _ ->
 
375
                    exit({error,{asn1,{illegal_value,Val}}})
 
376
            end;
 
377
        _ ->
 
378
            exit({error,{asn1,{illegal_value,Val}}})
 
379
    end.
 
380
 
 
381
encode_integer1(C, Val) ->                  
 
382
    case VR = get_constraint(C,'ValueRange') of
 
383
        no ->
 
384
            encode_unconstrained_number(Val);
 
385
        {Lb,'MAX'} ->
 
386
            encode_semi_constrained_number(Lb,Val);
 
387
        %% positive with range
 
388
        {Lb,Ub} when Val >= Lb,
 
389
                     Ub >= Val ->
 
390
            encode_constrained_number(VR,Val);
 
391
        _ ->
 
392
            exit({error,{asn1,{illegal_value,VR,Val}}})
 
393
    end.
 
394
 
 
395
decode_integer(Buffer,Range,NamedNumberList) ->
 
396
    {Val,Buffer2} = decode_integer(Buffer,Range),
 
397
    case lists:keysearch(Val,2,NamedNumberList) of
 
398
        {value,{NewVal,_}} -> {NewVal,Buffer2};
 
399
        _ -> {Val,Buffer2}
 
400
    end.
 
401
 
 
402
decode_integer(Buffer,[{Rc,_Ec}]) when tuple(Rc) ->
 
403
    {Ext,Buffer2} = getext(Buffer),
 
404
    case Ext of
 
405
        0 -> decode_integer(Buffer2,[Rc]); %% Value in root of constraint
 
406
        1 -> decode_unconstrained_number(Buffer2)
 
407
    end;
 
408
decode_integer(Buffer,undefined) ->
 
409
    decode_unconstrained_number(Buffer);
 
410
decode_integer(Buffer,C) ->
 
411
    case get_constraint(C,'SingleValue') of
 
412
        V when integer(V) ->
 
413
            {V,Buffer};
 
414
        V when list(V) ->
 
415
            {Val,Buffer2} = decode_integer1(Buffer,C),
 
416
            case lists:member(Val,V) of
 
417
                true ->
 
418
                    {Val,Buffer2};
 
419
                _ -> 
 
420
                    exit({error,{asn1,{illegal_value,Val}}})
 
421
            end;
 
422
        _ ->
 
423
            decode_integer1(Buffer,C)
 
424
    end.
 
425
 
 
426
decode_integer1(Buffer,C) ->
 
427
    case VR = get_constraint(C,'ValueRange') of
 
428
        no ->
 
429
            decode_unconstrained_number(Buffer);
 
430
        {Lb, 'MAX'} ->
 
431
            decode_semi_constrained_number(Buffer,Lb);
 
432
        {_,_} ->
 
433
            decode_constrained_number(Buffer,VR)
 
434
    end.
 
435
 
 
436
%% X.691:10.6 Encoding of a normally small non-negative whole number
 
437
%% Use this for encoding of CHOICE index if there is an extension marker in 
 
438
%% the CHOICE
 
439
encode_small_number({Name,Val}) when atom(Name) ->
 
440
    encode_small_number(Val);
 
441
encode_small_number(Val) when Val =< 63 ->
 
442
    <<Val:7>>;
 
443
encode_small_number(Val) ->
 
444
    [<<1:1>>,encode_semi_constrained_number(0,Val)].
 
445
 
 
446
decode_small_number(Bytes) ->
 
447
    {Bit,Bytes2} = getbit(Bytes),
 
448
    case Bit of
 
449
        0 -> 
 
450
            getbits(Bytes2,6);
 
451
        1 ->
 
452
            decode_semi_constrained_number(Bytes2,0)
 
453
    end.
 
454
 
 
455
%% X.691:10.7 Encoding of a semi-constrained whole number
 
456
%% might be an optimization encode_semi_constrained_number(0,Val) ->
 
457
encode_semi_constrained_number(C,{Name,Val}) when atom(Name) ->
 
458
    encode_semi_constrained_number(C,Val);
 
459
encode_semi_constrained_number({Lb,'MAX'},Val) ->
 
460
    encode_semi_constrained_number(Lb,Val);
 
461
encode_semi_constrained_number(Lb,Val) ->
 
462
    %% encoding in minimum no of octets preceeded by a length
 
463
    Val2 = Val - Lb,
 
464
%%    NumBits = num_bits(Val2),
 
465
    Bin = eint_bin_positive(Val2),
 
466
    Size = size(Bin),
 
467
    if 
 
468
        Size < 128 ->
 
469
            [<<Size>>,Bin]; % equiv with encode_length(undefined,Len) but faster
 
470
        Size < 16384 ->
 
471
            [<<2:2,Size:14>>,Bin];
 
472
        true ->
 
473
            [encode_length(undefined,Size),Bin]
 
474
    end.
 
475
 
 
476
decode_semi_constrained_number(Bytes,{Lb,_}) ->
 
477
    decode_semi_constrained_number(Bytes,Lb);
 
478
decode_semi_constrained_number(Bytes,Lb) ->
 
479
    {Len,Bytes2} = decode_length(Bytes,undefined),
 
480
    {V,Bytes3} = getoctets(Bytes2,Len),
 
481
    {V+Lb,Bytes3}.
 
482
 
 
483
encode_constrained_number(Range,{Name,Val}) when atom(Name) ->
 
484
    encode_constrained_number(Range,Val);
 
485
encode_constrained_number({Lb,Ub},Val) when Val >= Lb, Ub >= Val -> 
 
486
    Range = Ub - Lb + 1,
 
487
    Val2 = Val - Lb,
 
488
    NumBits = num_bits(Range),
 
489
    <<Val2:NumBits>>;
 
490
encode_constrained_number(Range,Val) -> 
 
491
    exit({error,{asn1,{integer_range,Range,value,Val}}}).
 
492
 
 
493
 
 
494
decode_constrained_number(Buffer,{Lb,Ub}) ->
 
495
    Range = Ub - Lb + 1,
 
496
    NumBits = num_bits(Range),
 
497
    {Val,Remain} = getbits(Buffer,NumBits),
 
498
    {Val+Lb,Remain}.
 
499
 
 
500
%% X.691:10.8 Encoding of an unconstrained whole number
 
501
 
 
502
encode_unconstrained_number(Val) when Val >= 0 ->
 
503
    Oct = eint_bin_2Cs(Val),
 
504
    Len = size(Oct),
 
505
    if 
 
506
        Len < 128 ->
 
507
            [<<Len>>,Oct]; % equiv with encode_length(undefined,Len) but faster
 
508
        Len < 16384 ->
 
509
            [<<2:2,Len:14>>,Oct];
 
510
        true ->
 
511
            [encode_length(undefined,Len),<<Len:16>>,Oct]
 
512
    end;
 
513
encode_unconstrained_number(Val) -> % negative
 
514
    Oct = enint(Val,[]),
 
515
    Len = size(Oct),
 
516
    if 
 
517
        Len < 128 ->
 
518
            [<<Len>>,Oct]; % equiv with encode_length(undefined,Len) but faster
 
519
        Len < 16384 ->
 
520
            [<<2:2,Len:14>>,Oct];
 
521
        true ->
 
522
            [encode_length(undefined,Len),Oct]
 
523
    end.
 
524
 
 
525
 
 
526
eint_bin_2Cs(Int) ->
 
527
    case eint_bin_positive(Int) of
 
528
        Bin = <<B,_/binary>> when B > 16#7f ->
 
529
            <<0,Bin/binary>>;
 
530
        Bin -> Bin
 
531
    end.
 
532
 
 
533
%% returns the integer as a binary
 
534
eint_bin_positive(Val) when Val < 16#100  ->
 
535
    <<Val>>;
 
536
eint_bin_positive(Val) when Val < 16#10000 ->
 
537
    <<Val:16>>;
 
538
eint_bin_positive(Val) when Val < 16#1000000 ->
 
539
    <<Val:24>>;
 
540
eint_bin_positive(Val) when Val < 16#100000000 ->
 
541
    <<Val:32>>;
 
542
eint_bin_positive(Val) ->
 
543
    list_to_binary([eint_bin_positive2(Val bsr 32)|<<Val:32>>]).
 
544
eint_bin_positive2(Val) when Val < 16#100  ->
 
545
    <<Val>>;
 
546
eint_bin_positive2(Val) when Val < 16#10000 ->
 
547
    <<Val:16>>;
 
548
eint_bin_positive2(Val) when Val < 16#1000000 ->
 
549
    <<Val:24>>;
 
550
eint_bin_positive2(Val) when Val < 16#100000000 ->
 
551
    <<Val:32>>;
 
552
eint_bin_positive2(Val) ->
 
553
    [eint_bin_positive2(Val bsr 32)|<<Val:32>>].
 
554
 
 
555
 
 
556
 
 
557
 
 
558
enint(-1, [B1|T]) when B1 > 127 ->
 
559
    list_to_binary([B1|T]);
 
560
enint(N, Acc) ->
 
561
    enint(N bsr 8, [N band 16#ff|Acc]).
 
562
 
 
563
decode_unconstrained_number(Bytes) ->
 
564
    {Len,Bytes2} = decode_length(Bytes,undefined),
 
565
    {Ints,Bytes3} = getoctets_as_bin(Bytes2,Len),
 
566
    {dec_integer(Ints),Bytes3}.
 
567
 
 
568
dec_integer(Bin = <<0:1,_:7,_/bitstring>>) ->  
 
569
    decpint(Bin);
 
570
dec_integer(<<_:1,B:7,BitStr/bitstring>>) ->
 
571
    Size = bit_size(BitStr),
 
572
    <<I:Size>> = BitStr,
 
573
    (-128 + B) bsl bit_size(BitStr) bor I.
 
574
    
 
575
decpint(Bin) ->
 
576
    Size = bit_size(Bin),
 
577
    <<Int:Size>> = Bin,
 
578
    Int.
 
579
 
 
580
 
 
581
%% X.691:10.9 Encoding of a length determinant
 
582
%%encode_small_length(undefined,Len) -> % null means no UpperBound
 
583
%%    encode_small_number(Len).
 
584
 
 
585
%% X.691:10.9.3.5 
 
586
%% X.691:10.9.3.7
 
587
encode_length(undefined,Len) -> % un-constrained
 
588
    if 
 
589
        Len < 128 ->
 
590
            <<Len>>;
 
591
        Len < 16384 ->
 
592
            <<2:2,Len:14>>;
 
593
        true  -> % should be able to endode length >= 16384
 
594
            exit({error,{asn1,{encode_length,{nyi,above_16k}}}})
 
595
    end;
 
596
 
 
597
encode_length({0,'MAX'},Len) ->
 
598
    encode_length(undefined,Len);
 
599
encode_length(Vr={Lb,Ub},Len) when Ub =< 65535 ,Lb >= 0 -> % constrained
 
600
    encode_constrained_number(Vr,Len);
 
601
encode_length({Lb,_Ub},Len) when integer(Lb), Lb >= 0 -> % Ub > 65535
 
602
    encode_length(undefined,Len);
 
603
encode_length({Vr={Lb,Ub},Ext},Len) 
 
604
  when Ub =< 65535 ,Lb >= 0, Len=<Ub, is_list(Ext) -> 
 
605
    %% constrained extensible
 
606
    [<<0:1>>,encode_constrained_number(Vr,Len)];
 
607
encode_length({{Lb,_Ub},Ext},Len) when is_list(Ext) ->
 
608
    [<<1:1>>,encode_semi_constrained_number(Lb,Len)];
 
609
encode_length(SingleValue,_Len) when integer(SingleValue) ->
 
610
    [].
 
611
 
 
612
%% X.691 10.9.3.4 (only used for length of bitmap that prefixes extension 
 
613
%% additions in a sequence or set
 
614
encode_small_length(Len) when Len =< 64 ->
 
615
    <<(Len-1):7>>;
 
616
encode_small_length(Len) ->
 
617
    [<<1:1>>,encode_length(undefined,Len)].
 
618
 
 
619
 
 
620
decode_small_length(Buffer) ->
 
621
    case getbit(Buffer) of
 
622
        {0,Remain} -> 
 
623
            {Bits,Remain2} = getbits(Remain,6),
 
624
            {Bits+1,Remain2};
 
625
        {1,Remain} -> 
 
626
            decode_length(Remain,undefined)
 
627
    end.
 
628
 
 
629
decode_length(Buffer) ->
 
630
    decode_length(Buffer,undefined).
 
631
 
 
632
%% un-constrained
 
633
decode_length(<<0:1,Oct:7,Rest/bitstring>>,undefined)  ->
 
634
    {Oct,Rest};
 
635
decode_length(<<2:2,Val:14,Rest/bitstring>>,undefined)  ->
 
636
    {Val,Rest};
 
637
decode_length(<<3:2,_:14,_Rest/bitstring>>,undefined)  ->
 
638
    exit({error,{asn1,{decode_length,{nyi,above_16k}}}});
 
639
 
 
640
decode_length(Buffer,{Lb,Ub}) when Ub =< 65535 ,Lb >= 0 -> % constrained
 
641
    decode_constrained_number(Buffer,{Lb,Ub});
 
642
decode_length(Buffer,{Lb,_}) when integer(Lb), Lb >= 0 -> % Ub > 65535
 
643
    decode_length(Buffer,undefined);
 
644
decode_length(Buffer,{VR={_Lb,_Ub},Ext}) when is_list(Ext) ->
 
645
    {0,Buffer2} = getbit(Buffer),
 
646
    decode_length(Buffer2, VR);
 
647
        
 
648
 
 
649
%When does this case occur with {_,_Lb,Ub} ??
 
650
% X.691:10.9.3.5 
 
651
decode_length(Bin,{_,_Lb,_Ub}) -> %when Len =< 127 -> % Unconstrained or large Ub NOTE! this case does not cover case when Ub > 65535
 
652
    case Bin of
 
653
        <<0:1,Val:7,Rest/bitstring>> -> 
 
654
            {Val,Rest};
 
655
        <<2:2,Val:14,Rest/bitstring>> -> 
 
656
            {Val,Rest};
 
657
        <<3:2,_:14,_Rest/bitstring>> -> 
 
658
            exit({error,{asn1,{decode_length,{nyi,length_above_64K}}}})
 
659
    end;
 
660
decode_length(Buffer,SingleValue) when integer(SingleValue) ->
 
661
    {SingleValue,Buffer}.
 
662
 
 
663
 
 
664
                                                % X.691:11
 
665
encode_boolean(true) ->
 
666
    <<1:1>>;
 
667
encode_boolean(false) ->
 
668
    <<0:1>>;
 
669
encode_boolean({Name,Val}) when atom(Name) ->
 
670
    encode_boolean(Val);
 
671
encode_boolean(Val) ->
 
672
    exit({error,{asn1,{encode_boolean,Val}}}).
 
673
 
 
674
decode_boolean(Buffer) -> %when record(Buffer,buffer)
 
675
    case getbit(Buffer) of
 
676
        {1,Remain} -> {true,Remain};
 
677
        {0,Remain} -> {false,Remain}
 
678
    end.
 
679
 
 
680
 
 
681
%% ENUMERATED with extension marker
 
682
decode_enumerated(Buffer,C,{Ntup1,Ntup2}) when tuple(Ntup1), tuple(Ntup2) ->
 
683
    {Ext,Buffer2} = getext(Buffer),
 
684
    case Ext of
 
685
        0 -> % not an extension value
 
686
            {Val,Buffer3} = decode_integer(Buffer2,C),
 
687
            case catch (element(Val+1,Ntup1)) of
 
688
                NewVal when atom(NewVal) -> {NewVal,Buffer3};
 
689
                _Error -> exit({error,{asn1,{decode_enumerated,{Val,[Ntup1,Ntup2]}}}})
 
690
            end;
 
691
        1 -> % this an extension value
 
692
            {Val,Buffer3} = decode_small_number(Buffer2),
 
693
            case catch (element(Val+1,Ntup2)) of
 
694
                NewVal when atom(NewVal) -> {NewVal,Buffer3};
 
695
                _ -> {{asn1_enum,Val},Buffer3}
 
696
            end
 
697
    end;
 
698
 
 
699
decode_enumerated(Buffer,C,NamedNumberTup) when tuple(NamedNumberTup) ->
 
700
    {Val,Buffer2} = decode_integer(Buffer,C),
 
701
    case catch (element(Val+1,NamedNumberTup)) of
 
702
        NewVal when atom(NewVal) -> {NewVal,Buffer2};
 
703
        _Error -> exit({error,{asn1,{decode_enumerated,{Val,NamedNumberTup}}}})
 
704
    end.
 
705
 
 
706
 
 
707
%%============================================================================
 
708
%%============================================================================
 
709
%% Bitstring value, ITU_T X.690 Chapter 8.5
 
710
%%============================================================================
 
711
%%============================================================================
 
712
 
 
713
%%============================================================================
 
714
%% encode bitstring value
 
715
%%============================================================================
 
716
 
 
717
 
 
718
 
 
719
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
720
%% bitstring NamedBitList
 
721
%% Val can be  of:
 
722
%% - [identifiers] where only named identifers are set to one, 
 
723
%%   the Constraint must then have some information of the 
 
724
%%   bitlength.
 
725
%% - [list of ones and zeroes] all bits 
 
726
%% - integer value representing the bitlist
 
727
%% C is constraint Len, only valid when identifiers
 
728
 
 
729
 
 
730
%% when the value is a list of {Unused,BinBits}, where 
 
731
%% Unused = integer(),
 
732
%% BinBits = binary().
 
733
 
 
734
encode_bit_string(C,Bin={Unused,BinBits},NamedBitList) when integer(Unused),
 
735
                                                            binary(BinBits) ->
 
736
    encode_bin_bit_string(get_constraint(C,'SizeConstraint'),Bin,NamedBitList);
 
737
 
 
738
encode_bit_string(C, BitListVal, NamedBitList) ->
 
739
    encode_bit_string1(get_constraint(C,'SizeConstraint'), BitListVal, NamedBitList).
 
740
%% when the value is a list of named bits
 
741
encode_bit_string1(C, LoNB=[FirstVal | _RestVal], NamedBitList) when atom(FirstVal) ->
 
742
    ToSetPos = get_all_bitposes(LoNB, NamedBitList, []),
 
743
    BitList = make_and_set_list(ToSetPos,0),
 
744
    encode_bit_string1(C,BitList,NamedBitList);
 
745
 
 
746
encode_bit_string1(C, BL=[{bit,_No} | _RestVal], NamedBitList) ->
 
747
    ToSetPos = get_all_bitposes(BL, NamedBitList, []),
 
748
    BitList = make_and_set_list(ToSetPos,0),
 
749
    encode_bit_string1(C,BitList,NamedBitList);
 
750
%% when the value is a list of ones and zeroes
 
751
encode_bit_string1(Int, BitListValue, _) 
 
752
  when list(BitListValue),integer(Int) ->
 
753
    %% The type is constrained by a single value size constraint
 
754
    bit_list2bitstr(Int,BitListValue);
 
755
encode_bit_string1(no, BitListValue,[]) 
 
756
  when list(BitListValue) ->
 
757
    Len = length(BitListValue),
 
758
    [encode_length(undefined,Len),bit_list2bitstr(Len,BitListValue)];
 
759
encode_bit_string1(C, BitListValue,[]) 
 
760
  when list(BitListValue) ->
 
761
    Len = length(BitListValue),
 
762
    [encode_length(C,Len),bit_list2bitstr(Len,BitListValue)];
 
763
encode_bit_string1(no, BitListValue,_NamedBitList) 
 
764
  when list(BitListValue) ->
 
765
    %% this case with an unconstrained BIT STRING can be made more efficient
 
766
    %% if the complete driver can take a special code so the length field
 
767
    %% is encoded there.
 
768
    NewBitLVal = lists:reverse(lists:dropwhile(fun(0)->true;(1)->false end,
 
769
                                            lists:reverse(BitListValue))),
 
770
    Len = length(NewBitLVal),
 
771
    [encode_length(undefined,Len),bit_list2bitstr(Len,NewBitLVal)];
 
772
encode_bit_string1(C,BitListValue,_NamedBitList) 
 
773
  when list(BitListValue) ->% C = {_,'MAX'}
 
774
    NewBitStr = bitstr_trailing_zeros(BitListValue,C),
 
775
    [encode_length(C,bit_size(NewBitStr)),NewBitStr];
 
776
 
 
777
 
 
778
%% when the value is an integer
 
779
encode_bit_string1(C, IntegerVal, NamedBitList) when integer(IntegerVal)->
 
780
    BitList = int_to_bitlist(IntegerVal),
 
781
    encode_bit_string1(C,BitList,NamedBitList);
 
782
 
 
783
%% when the value is a tuple
 
784
encode_bit_string1(C,{Name,Val}, NamedBitList) when atom(Name) ->
 
785
    encode_bit_string1(C,Val,NamedBitList).
 
786
 
 
787
bit_list2bitstr(Len,BitListValue) ->
 
788
    case length(BitListValue) of
 
789
        Len ->
 
790
            << <<B:1>> ||B <- BitListValue>>;
 
791
        L when L > Len -> % truncate
 
792
            << << <<B:1>> ||B <- BitListValue>> :Len/bitstring>>;
 
793
        L -> % Len > L -> pad
 
794
            << << <<B:1>> ||B <- BitListValue>>/bitstring ,0:(Len-L)>>
 
795
        end.
 
796
 
 
797
adjust_trailing_zeros(Len,Bin) when Len == size(Bin) ->
 
798
    Bin;
 
799
adjust_trailing_zeros(Len,Bin) when Len > bit_size(Bin) ->
 
800
    <<Bin/bitstring,0:(Len-bit_size(Bin))>>;
 
801
adjust_trailing_zeros(Len,Bin) ->
 
802
    <<Bin:Len/bitstring>>.
 
803
 
 
804
bitstr_trailing_zeros(BitList,C) when integer(C) ->
 
805
    bitstr_trailing_zeros1(BitList,C,C);
 
806
bitstr_trailing_zeros(BitList,{Lb,Ub}) when integer(Lb) ->
 
807
    bitstr_trailing_zeros1(BitList,Lb,Ub);
 
808
bitstr_trailing_zeros(BitList,{{Lb,Ub},_}) when integer(Lb) ->
 
809
    bitstr_trailing_zeros1(BitList,Lb,Ub);
 
810
bitstr_trailing_zeros(BitList,_) ->
 
811
    bit_list2bitstr(length(BitList),BitList).
 
812
 
 
813
bitstr_trailing_zeros1(BitList,Lb,Ub) ->
 
814
    case length(BitList) of
 
815
        Lb -> bit_list2bitstr(Lb,BitList);
 
816
        B when B<Lb -> bit_list2bitstr(Lb,BitList);
 
817
        D -> F = fun(L,LB,LB,_,_)->bit_list2bitstr(LB,lists:reverse(L));
 
818
                    ([0|R],L1,LB,UB,Fun)->Fun(R,L1-1,LB,UB,Fun);
 
819
                    (L,L1,_,UB,_)when L1 =< UB -> 
 
820
                         bit_list2bitstr(L1,lists:reverse(L));
 
821
                    (_,_L1,_,_,_) ->exit({error,{list_length_BIT_STRING,
 
822
                                                 BitList}}) end,
 
823
             F(lists:reverse(BitList),D,Lb,Ub,F)
 
824
    end.
 
825
 
 
826
%% encode_bin_bit_string/3, when value is a tuple of Unused and BinBits.
 
827
%% Unused = integer(),i.e. number unused bits in least sign. byte of
 
828
%% BinBits = binary().
 
829
encode_bin_bit_string(C,{_,BinBits},_NamedBitList)
 
830
  when integer(C),C=<16 ->
 
831
    adjust_trailing_zeros(C,BinBits);
 
832
encode_bin_bit_string(C,{_Unused,BinBits},_NamedBitList)
 
833
  when integer(C) ->
 
834
    adjust_trailing_zeros(C,BinBits);
 
835
encode_bin_bit_string(C,UnusedAndBin={_,_},NamedBitList) ->
 
836
    %% removes all trailing bits if NamedBitList is not empty
 
837
    BitStr = remove_trailing_bin(NamedBitList,UnusedAndBin),
 
838
    case C of
 
839
        {Lb,Ub} when integer(Lb),integer(Ub) ->
 
840
            [encode_length({Lb,Ub},bit_size(BitStr)),BitStr];
 
841
        no ->
 
842
            [encode_length(undefined,bit_size(BitStr)),BitStr];
 
843
        Sc -> 
 
844
            [encode_length(Sc,bit_size(BitStr)),BitStr]
 
845
    end.
 
846
 
 
847
 
 
848
remove_trailing_bin([], {Unused,Bin}) ->
 
849
    BS = bit_size(Bin)-Unused,
 
850
    <<BitStr:BS/bitstring,_:Unused>> = Bin,
 
851
    BitStr;
 
852
remove_trailing_bin(_NamedNumberList,{_Unused,<<>>}) ->
 
853
    <<>>;
 
854
remove_trailing_bin(NamedNumberList, {_Unused,Bin}) ->
 
855
    Size = size(Bin)-1,
 
856
    <<Bfront:Size/binary, LastByte:8>> = Bin,
 
857
 
 
858
    %% clear the Unused bits to be sure
 
859
    Unused1 = trailingZeroesInNibble(LastByte band 15),
 
860
    Unused2 = 
 
861
        case Unused1 of 
 
862
            4 ->
 
863
                4 + trailingZeroesInNibble(LastByte bsr 4);
 
864
            _ -> Unused1
 
865
        end,
 
866
    case Unused2 of
 
867
        8 ->
 
868
            remove_trailing_bin(NamedNumberList,{0,Bfront});
 
869
        _ ->
 
870
            BS = bit_size(Bin) - Unused2,
 
871
            <<BitStr:BS/bitstring,_:Unused2>> = Bin,
 
872
            BitStr
 
873
    end.
 
874
 
 
875
trailingZeroesInNibble(0) ->
 
876
    4;
 
877
trailingZeroesInNibble(1) ->
 
878
    0;
 
879
trailingZeroesInNibble(2) ->
 
880
    1;
 
881
trailingZeroesInNibble(3) ->
 
882
    0;
 
883
trailingZeroesInNibble(4) ->
 
884
    2;
 
885
trailingZeroesInNibble(5) ->
 
886
    0;
 
887
trailingZeroesInNibble(6) ->
 
888
    1;
 
889
trailingZeroesInNibble(7) ->
 
890
    0;
 
891
trailingZeroesInNibble(8) ->
 
892
    3;
 
893
trailingZeroesInNibble(9) ->
 
894
    0;
 
895
trailingZeroesInNibble(10) ->
 
896
    1;
 
897
trailingZeroesInNibble(11) ->
 
898
    0;
 
899
trailingZeroesInNibble(12) -> %#1100
 
900
    2;
 
901
trailingZeroesInNibble(13) ->
 
902
    0;
 
903
trailingZeroesInNibble(14) ->
 
904
    1;
 
905
trailingZeroesInNibble(15) ->
 
906
    0.
 
907
 
 
908
%%%%%%%%%%%%%%%
 
909
%% The result is presented as a list of named bits (if possible)
 
910
%% else as a tuple {Unused,Bits}. Unused is the number of unused
 
911
%% bits, least significant bits in the last byte of Bits. Bits is
 
912
%% the BIT STRING represented as a binary.
 
913
%% 
 
914
decode_compact_bit_string(Buffer, C, NamedNumberList) ->
 
915
    case get_constraint(C,'SizeConstraint') of
 
916
        0 -> % fixed length
 
917
            {{8,0},Buffer};
 
918
        V when integer(V),V=<16 -> %fixed length 16 bits or less
 
919
            compact_bit_string(Buffer,V,NamedNumberList);
 
920
        V when integer(V),V=<65536 -> %fixed length > 16 bits
 
921
            compact_bit_string(Buffer,V,NamedNumberList);
 
922
        V when integer(V) -> % V > 65536 => fragmented value
 
923
            {Bin,Buffer2} = decode_fragmented_bits(Buffer,V),
 
924
            PadLen = (8 - (bit_size(Bin) rem 8)) rem 8,
 
925
            {{PadLen,<<Bin/bitstring,0:PadLen>>},Buffer2};
 
926
%%              {0,_} -> {{0,Bin},Buffer2};
 
927
%%              {U,_} -> {{8-U,Bin},Buffer2}
 
928
        {Lb,Ub} when integer(Lb),integer(Ub) ->
 
929
            %% This case may demand decoding of fragmented length/value
 
930
            {Len,Bytes2} = decode_length(Buffer,{Lb,Ub}),
 
931
            compact_bit_string(Bytes2,Len,NamedNumberList);
 
932
        no ->
 
933
            %% This case may demand decoding of fragmented length/value
 
934
            {Len,Bytes2} = decode_length(Buffer,undefined),
 
935
            compact_bit_string(Bytes2,Len,NamedNumberList);
 
936
        Sc ->
 
937
            {Len,Bytes2} = decode_length(Buffer,Sc),
 
938
            compact_bit_string(Bytes2,Len,NamedNumberList)
 
939
    end.
 
940
 
 
941
 
 
942
%%%%%%%%%%%%%%%
 
943
%% The result is presented as a list of named bits (if possible)
 
944
%% else as a list of 0 and 1.
 
945
%% 
 
946
decode_bit_string(Buffer, C, NamedNumberList) ->
 
947
    case get_constraint(C,'SizeConstraint') of
 
948
        {Lb,Ub} when integer(Lb),integer(Ub) ->
 
949
            {Len,Bytes2} = decode_length(Buffer,{Lb,Ub}),
 
950
            bit_list_or_named(Bytes2,Len,NamedNumberList);
 
951
        no ->
 
952
            {Len,Bytes2} = decode_length(Buffer,undefined),
 
953
            bit_list_or_named(Bytes2,Len,NamedNumberList);
 
954
        0 -> % fixed length
 
955
            {[],Buffer}; % nothing to encode
 
956
        V when integer(V),V=<16 -> % fixed length 16 bits or less
 
957
            bit_list_or_named(Buffer,V,NamedNumberList);
 
958
        V when integer(V),V=<65536 ->
 
959
            bit_list_or_named(Buffer,V,NamedNumberList);
 
960
        V when integer(V) ->
 
961
            {BinBits,_} = decode_fragmented_bits(Buffer,V),
 
962
            bit_list_or_named(BinBits,V,NamedNumberList);
 
963
        Sc -> % extension marker
 
964
            {Len,Bytes2} = decode_length(Buffer,Sc),
 
965
            bit_list_or_named(Bytes2,Len,NamedNumberList)
 
966
    end.
 
967
 
 
968
 
 
969
%% if no named bits are declared we will return a
 
970
%% {Unused,Bits}. Unused = integer(),
 
971
%% Bits = binary().
 
972
compact_bit_string(Buffer,Len,[]) ->
 
973
    {BitStr,Rest} = getbits_as_binary(Len,Buffer), % {{Unused,BinBits},NewBuffer}
 
974
    PadLen = (8 - (bit_size(BitStr) rem 8)) rem 8,
 
975
    {{PadLen,<<BitStr/bitstring,0:PadLen>>},Rest};
 
976
compact_bit_string(Buffer,Len,NamedNumberList) ->
 
977
    bit_list_or_named(Buffer,Len,NamedNumberList).
 
978
 
 
979
 
 
980
%% if no named bits are declared we will return a
 
981
%% BitList = [0 | 1]
 
982
 
 
983
bit_list_or_named(Buffer,Len,[]) ->
 
984
    getbits_as_list(Len,Buffer);
 
985
 
 
986
%% if there are named bits declared we will return a named
 
987
%% BitList where the names are atoms and unnamed bits represented
 
988
%% as {bit,Pos}
 
989
%% BitList = [atom() | {bit,Pos}]
 
990
%% Pos = integer()
 
991
 
 
992
bit_list_or_named(Buffer,Len,NamedNumberList) ->
 
993
    {BitList,Rest} = getbits_as_list(Len,Buffer),
 
994
    {bit_list_or_named1(0,BitList,NamedNumberList,[]), Rest}.
 
995
 
 
996
bit_list_or_named1(Pos,[0|Bt],Names,Acc) ->
 
997
    bit_list_or_named1(Pos+1,Bt,Names,Acc);
 
998
bit_list_or_named1(Pos,[1|Bt],Names,Acc) ->
 
999
    case lists:keysearch(Pos,2,Names) of
 
1000
        {value,{Name,_}} ->
 
1001
            bit_list_or_named1(Pos+1,Bt,Names,[Name|Acc]);
 
1002
        _  -> 
 
1003
            bit_list_or_named1(Pos+1,Bt,Names,[{bit,Pos}|Acc])
 
1004
    end;
 
1005
bit_list_or_named1(_,[],_,Acc) ->
 
1006
    lists:reverse(Acc).
 
1007
 
 
1008
 
 
1009
 
 
1010
%%%%%%%%%%%%%%%
 
1011
%% 
 
1012
 
 
1013
int_to_bitlist(Int) when integer(Int), Int > 0 ->
 
1014
    [Int band 1 | int_to_bitlist(Int bsr 1)];
 
1015
int_to_bitlist(0) ->
 
1016
    [].
 
1017
 
 
1018
 
 
1019
%%%%%%%%%%%%%%%%%%
 
1020
%% get_all_bitposes([list of named bits to set], named_bit_db, []) ->
 
1021
%%   [sorted_list_of_bitpositions_to_set]
 
1022
 
 
1023
get_all_bitposes([{bit,ValPos}|Rest], NamedBitList, Ack) ->
 
1024
    get_all_bitposes(Rest, NamedBitList, [ValPos | Ack ]);
 
1025
 
 
1026
get_all_bitposes([Val | Rest], NamedBitList, Ack) ->
 
1027
    case lists:keysearch(Val, 1, NamedBitList) of
 
1028
        {value, {_ValName, ValPos}} ->
 
1029
            get_all_bitposes(Rest, NamedBitList, [ValPos | Ack]);
 
1030
        _ ->
 
1031
            exit({error,{asn1, {bitstring_namedbit, Val}}})
 
1032
    end;
 
1033
get_all_bitposes([], _NamedBitList, Ack) ->
 
1034
    lists:sort(Ack).
 
1035
 
 
1036
%%%%%%%%%%%%%%%%%%
 
1037
%% make_and_set_list([list of positions to set to 1])->
 
1038
%% returns list with all in SetPos set.
 
1039
%% in positioning in list the first element is 0, the second 1 etc.., but
 
1040
%% 
 
1041
 
 
1042
make_and_set_list([XPos|SetPos], XPos) ->
 
1043
    [1 | make_and_set_list(SetPos, XPos + 1)];
 
1044
make_and_set_list([Pos|SetPos], XPos) ->
 
1045
    [0 | make_and_set_list([Pos | SetPos], XPos + 1)];
 
1046
make_and_set_list([], _) ->
 
1047
    [].
 
1048
 
 
1049
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
1050
%% X.691:16
 
1051
%% encode_octet_string(Constraint,Val)
 
1052
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
1053
 
 
1054
encode_octet_string(C,{_Name,Val}) ->
 
1055
    encode_octet_string(C,Val);
 
1056
encode_octet_string(C,Val) ->
 
1057
    case get_constraint(C,'SizeConstraint') of
 
1058
        0 ->
 
1059
            <<>>;
 
1060
        1 ->
 
1061
            list_to_binary(Val);
 
1062
        2 ->
 
1063
            list_to_binary(Val);
 
1064
        Sv when Sv =<65535, Sv == length(Val) -> % fixed length
 
1065
            list_to_binary(Val);
 
1066
        VR = {_,_}  ->
 
1067
            [encode_length(VR,length(Val)),list_to_binary(Val)];
 
1068
        Sv when list(Sv) ->
 
1069
            [encode_length({hd(Sv),lists:max(Sv)},length(Val)),list_to_binary(Val)];
 
1070
        no  ->
 
1071
            [encode_length(undefined,length(Val)),list_to_binary(Val)]
 
1072
    end.
 
1073
 
 
1074
decode_octet_string(Bytes,C) ->
 
1075
    decode_octet_string1(Bytes,get_constraint(C,'SizeConstraint')).
 
1076
decode_octet_string1(<<B1,Bytes/bitstring>>,1) ->
 
1077
    {[B1],Bytes};
 
1078
decode_octet_string1(<<B1,B2,Bytes/bitstring>>,2) ->
 
1079
    {[B1,B2],Bytes};
 
1080
decode_octet_string1(Bytes,Sv) when integer(Sv),Sv=<65535 ->
 
1081
    getoctets_as_list(Bytes,Sv);
 
1082
decode_octet_string1(Bytes,Sv) when integer(Sv) ->
 
1083
    decode_fragmented_octets(Bytes,Sv);
 
1084
decode_octet_string1(Bytes,{Lb,Ub}) ->
 
1085
    {Len,Bytes2} = decode_length(Bytes,{Lb,Ub}),
 
1086
    getoctets_as_list(Bytes2,Len);
 
1087
decode_octet_string1(Bytes,Sv) when list(Sv) ->
 
1088
    {Len,Bytes2} = decode_length(Bytes,{hd(Sv),lists:max(Sv)}),
 
1089
    getoctets_as_list(Bytes2,Len);
 
1090
decode_octet_string1(Bytes,no) ->
 
1091
    {Len,Bytes2} = decode_length(Bytes,undefined),
 
1092
    getoctets_as_list(Bytes2,Len).
 
1093
 
 
1094
 
 
1095
 
 
1096
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
1097
%% Restricted char string types 
 
1098
%% (NumericString, PrintableString,VisibleString,IA5String,BMPString,UniversalString)
 
1099
%% X.691:26 and X.680:34-36
 
1100
%%encode_restricted_string('BMPString',Constraints,Extension,Val)
 
1101
 
 
1102
 
 
1103
encode_restricted_string({Name,Val}) when atom(Name) ->
 
1104
    encode_restricted_string(Val);
 
1105
 
 
1106
encode_restricted_string(Val) when list(Val)->
 
1107
    [encode_length(undefined,length(Val)),list_to_binary(Val)].
 
1108
 
 
1109
encode_known_multiplier_string(StringType,C,{Name,Val}) when atom(Name) ->
 
1110
    encode_known_multiplier_string(StringType,C,Val);
 
1111
 
 
1112
encode_known_multiplier_string(StringType,C,Val) ->
 
1113
    Result = chars_encode(C,StringType,Val),
 
1114
    NumBits = get_NumBits(C,StringType),
 
1115
    case get_constraint(C,'SizeConstraint') of
 
1116
        Ub when integer(Ub), Ub*NumBits =< 16  ->
 
1117
            Result;
 
1118
        0 ->
 
1119
            [];
 
1120
        Ub when integer(Ub),Ub =<65535 -> % fixed length
 
1121
            Result;
 
1122
        {Ub,Lb} ->
 
1123
            [encode_length({Ub,Lb},length(Val)),Result];
 
1124
        Vl when list(Vl) ->
 
1125
            [encode_length({lists:min(Vl),lists:max(Vl)},length(Val)),Result];
 
1126
        no  ->
 
1127
            [encode_length(undefined,length(Val)),Result]
 
1128
    end.
 
1129
 
 
1130
decode_restricted_string(Bytes) ->
 
1131
    {Len,Bytes2} = decode_length(Bytes,undefined),
 
1132
    getoctets_as_list(Bytes2,Len).
 
1133
 
 
1134
decode_known_multiplier_string(Bytes,StringType,C,_Ext) ->
 
1135
    NumBits = get_NumBits(C,StringType),
 
1136
    case get_constraint(C,'SizeConstraint') of
 
1137
        Ub when integer(Ub), Ub*NumBits =< 16  ->
 
1138
            chars_decode(Bytes,NumBits,StringType,C,Ub);
 
1139
        Ub when integer(Ub),Ub =<65535 -> % fixed length
 
1140
            chars_decode(Bytes,NumBits,StringType,C,Ub);
 
1141
        0 ->
 
1142
            {[],Bytes};
 
1143
        Vl when list(Vl) ->
 
1144
            {Len,Bytes1} = decode_length(Bytes,{hd(Vl),lists:max(Vl)}),
 
1145
            chars_decode(Bytes1,NumBits,StringType,C,Len);
 
1146
        no  ->
 
1147
            {Len,Bytes1} = decode_length(Bytes,undefined),
 
1148
            chars_decode(Bytes1,NumBits,StringType,C,Len);
 
1149
        {Lb,Ub}->
 
1150
            {Len,Bytes1} = decode_length(Bytes,{Lb,Ub}),
 
1151
            chars_decode(Bytes1,NumBits,StringType,C,Len)
 
1152
    end.
 
1153
 
 
1154
 
 
1155
encode_NumericString(C,Val) ->
 
1156
    encode_known_multiplier_string('NumericString',C,Val).
 
1157
decode_NumericString(Bytes,C) ->
 
1158
    decode_known_multiplier_string(Bytes,'NumericString',C,false).
 
1159
 
 
1160
encode_PrintableString(C,Val) ->
 
1161
    encode_known_multiplier_string('PrintableString',C,Val).
 
1162
decode_PrintableString(Bytes,C) ->
 
1163
    decode_known_multiplier_string(Bytes,'PrintableString',C,false).
 
1164
 
 
1165
encode_VisibleString(C,Val) -> % equivalent with ISO646String
 
1166
    encode_known_multiplier_string('VisibleString',C,Val).
 
1167
decode_VisibleString(Bytes,C) ->
 
1168
    decode_known_multiplier_string(Bytes,'VisibleString',C,false).
 
1169
 
 
1170
encode_IA5String(C,Val) ->
 
1171
    encode_known_multiplier_string('IA5String',C,Val).
 
1172
decode_IA5String(Bytes,C) ->
 
1173
    decode_known_multiplier_string(Bytes,'IA5String',C,false).
 
1174
 
 
1175
encode_BMPString(C,Val) ->
 
1176
    encode_known_multiplier_string('BMPString',C,Val).
 
1177
decode_BMPString(Bytes,C) ->
 
1178
    decode_known_multiplier_string(Bytes,'BMPString',C,false).
 
1179
 
 
1180
encode_UniversalString(C,Val) ->
 
1181
    encode_known_multiplier_string('UniversalString',C,Val).
 
1182
decode_UniversalString(Bytes,C) ->
 
1183
    decode_known_multiplier_string(Bytes,'UniversalString',C,false).
 
1184
 
 
1185
    
 
1186
%% end of known-multiplier strings for which PER visible constraints are
 
1187
%% applied
 
1188
 
 
1189
encode_GeneralString(_C,Val) ->
 
1190
    encode_restricted_string(Val).
 
1191
decode_GeneralString(Bytes,_C) ->
 
1192
    decode_restricted_string(Bytes).
 
1193
 
 
1194
encode_GraphicString(_C,Val) ->
 
1195
    encode_restricted_string(Val).
 
1196
decode_GraphicString(Bytes,_C) ->
 
1197
    decode_restricted_string(Bytes).
 
1198
 
 
1199
encode_ObjectDescriptor(_C,Val) ->
 
1200
    encode_restricted_string(Val).
 
1201
decode_ObjectDescriptor(Bytes) ->
 
1202
    decode_restricted_string(Bytes).
 
1203
 
 
1204
encode_TeletexString(_C,Val) -> % equivalent with T61String
 
1205
    encode_restricted_string(Val).
 
1206
decode_TeletexString(Bytes,_C) ->
 
1207
    decode_restricted_string(Bytes).
 
1208
 
 
1209
encode_VideotexString(_C,Val) ->
 
1210
    encode_restricted_string(Val).
 
1211
decode_VideotexString(Bytes,_C) ->
 
1212
    decode_restricted_string(Bytes).
 
1213
 
 
1214
 
 
1215
 
 
1216
 
 
1217
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
1218
%% getBMPChars(Bytes,Len) ->{BMPcharList,RemainingBytes}
 
1219
%%
 
1220
getBMPChars(Bytes,1) ->
 
1221
    {O1,Bytes2} = getbits(Bytes,8),
 
1222
    {O2,Bytes3} = getbits(Bytes2,8),
 
1223
    if 
 
1224
        O1 == 0 ->
 
1225
            {[O2],Bytes3};
 
1226
        true ->
 
1227
            {[{0,0,O1,O2}],Bytes3}
 
1228
    end;
 
1229
getBMPChars(Bytes,Len) ->
 
1230
    getBMPChars(Bytes,Len,[]).
 
1231
 
 
1232
getBMPChars(Bytes,0,Acc) ->
 
1233
    {lists:reverse(Acc),Bytes};
 
1234
getBMPChars(Bytes,Len,Acc) ->
 
1235
    {Octs,Bytes1} = getoctets_as_list(Bytes,2),
 
1236
    case Octs of
 
1237
        [0,O2] ->
 
1238
            getBMPChars(Bytes1,Len-1,[O2|Acc]);
 
1239
        [O1,O2]->
 
1240
            getBMPChars(Bytes1,Len-1,[{0,0,O1,O2}|Acc])
 
1241
    end.
 
1242
 
 
1243
 
 
1244
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
1245
%% chars_encode(C,StringType,Value) -> ValueList
 
1246
%%
 
1247
%% encodes chars according to the per rules taking the constraint PermittedAlphabet 
 
1248
%% into account.
 
1249
%% This function does only encode the value part and NOT the length
 
1250
 
 
1251
chars_encode(C,StringType,Value) ->
 
1252
    case {StringType,get_constraint(C,'PermittedAlphabet')} of
 
1253
        {'UniversalString',{_,_Sv}} ->
 
1254
            exit({error,{asn1,{'not implemented',"UniversalString with PermittedAlphabet constraint"}}});
 
1255
        {'BMPString',{_,_Sv}} ->
 
1256
            exit({error,{asn1,{'not implemented',"BMPString with PermittedAlphabet constraint"}}});
 
1257
        _ ->
 
1258
            {NumBits,CharOutTab} = {get_NumBits(C,StringType),get_CharOutTab(C,StringType)}, 
 
1259
            chars_encode2(Value,NumBits,CharOutTab)
 
1260
    end.
 
1261
 
 
1262
chars_encode2([H|T],NumBits,{Min,Max,notab}) when  H =< Max, H >= Min ->
 
1263
    %%[{bits,NumBits,H-Min}|chars_encode2(T,NumBits,{Min,Max,notab})];
 
1264
    [<<(H-Min):NumBits>>|chars_encode2(T,NumBits,{Min,Max,notab})];
 
1265
chars_encode2([H|T],NumBits,{Min,Max,Tab}) when H =< Max, H >= Min ->
 
1266
%%    [{bits,NumBits,exit_if_false(H,element(H-Min+1,Tab))}|chars_encode2(T,NumBits,{Min,Max,Tab})];
 
1267
    Ch = exit_if_false(H,element(H-Min+1,Tab)),
 
1268
    [<<Ch:NumBits>>|chars_encode2(T,NumBits,{Min,Max,Tab})];
 
1269
chars_encode2([{A,B,C,D}|T],NumBits,{Min,Max,notab}) -> 
 
1270
    %% no value range check here (ought to be, but very expensive)
 
1271
%%    [{bits,NumBits,((((((A bsl 8)+B) bsl 8)+C) bsl 8)+D)-Min}|chars_encode2(T,NumBits,{Min,Max,notab})];
 
1272
    Ch = ((((((A bsl 8)+B) bsl 8)+C) bsl 8)+D)-Min,
 
1273
    [<<Ch:NumBits>>|chars_encode2(T,NumBits,{Min,Max,notab})];
 
1274
chars_encode2([{A,B,C,D}|T],NumBits,{Min,Max,Tab}) -> 
 
1275
    %% no value range check here (ought to be, but very expensive)
 
1276
%%    [{bits,NumBits,exit_if_false({A,B,C,D},element(((((((A bsl 8)+B) bsl 8)+C) bsl 8)+D)-Min,Tab))}|chars_encode2(T,NumBits,{Min,Max,notab})];
 
1277
    Ch = exit_if_false({A,B,C,D},element(((((((A bsl 8)+B) bsl 8)+C) bsl 8)+D)-Min,Tab)),
 
1278
    [<<Ch:NumBits>>|chars_encode2(T,NumBits,{Min,Max,notab})];
 
1279
chars_encode2([H|_T],_,{_,_,_}) ->
 
1280
    exit({error,{asn1,{illegal_char_value,H}}});
 
1281
chars_encode2([],_,_) ->
 
1282
    [].
 
1283
 
 
1284
exit_if_false(V,false)->
 
1285
    exit({error,{asn1,{"illegal value according to Permitted alphabet constraint",V}}});
 
1286
exit_if_false(_,V) ->V.
 
1287
 
 
1288
 
 
1289
get_NumBits(C,StringType) ->
 
1290
    case get_constraint(C,'PermittedAlphabet') of
 
1291
        {'SingleValue',Sv} ->
 
1292
            charbits(length(Sv));
 
1293
        no ->
 
1294
            case StringType of
 
1295
                'IA5String' ->
 
1296
                    charbits(128); % 16#00..16#7F
 
1297
                'VisibleString' ->
 
1298
                    charbits(95); % 16#20..16#7E
 
1299
                'PrintableString' ->
 
1300
                    charbits(74); % [$\s,$',$(,$),$+,$,,$-,$.,$/,"0123456789",$:,$=,$?,$A..$Z,$a..$z
 
1301
                'NumericString' ->
 
1302
                    charbits(11); % $ ,"0123456789"
 
1303
                'UniversalString' ->
 
1304
                    32;
 
1305
                'BMPString' ->
 
1306
                    16
 
1307
            end
 
1308
    end.
 
1309
 
 
1310
get_CharOutTab(C,StringType) ->
 
1311
    get_CharTab(C,StringType,out).
 
1312
 
 
1313
get_CharInTab(C,StringType) ->
 
1314
    get_CharTab(C,StringType,in).
 
1315
 
 
1316
get_CharTab(C,StringType,InOut) ->
 
1317
    case get_constraint(C,'PermittedAlphabet') of
 
1318
        {'SingleValue',Sv} ->
 
1319
            get_CharTab2(C,StringType,hd(Sv),lists:max(Sv),Sv,InOut);
 
1320
        no ->
 
1321
            case StringType of
 
1322
                'IA5String' ->
 
1323
                    {0,16#7F,notab};
 
1324
                'VisibleString' ->
 
1325
                    get_CharTab2(C,StringType,16#20,16#7F,notab,InOut);
 
1326
                'PrintableString' ->
 
1327
                    Chars = lists:sort(
 
1328
                              " '()+,-./0123456789:=?ABCDEFGHIJKLMNOPQRSTUVWXYZabcdefghijklmnopqrstuvwxyz"),
 
1329
                    get_CharTab2(C,StringType,hd(Chars),lists:max(Chars),Chars,InOut);
 
1330
                'NumericString' ->
 
1331
                    get_CharTab2(C,StringType,16#20,$9," 0123456789",InOut);
 
1332
                'UniversalString' ->
 
1333
                    {0,16#FFFFFFFF,notab};
 
1334
                'BMPString' ->
 
1335
                    {0,16#FFFF,notab}
 
1336
            end
 
1337
    end.
 
1338
 
 
1339
get_CharTab2(C,StringType,Min,Max,Chars,InOut) ->
 
1340
    BitValMax = (1 bsl get_NumBits(C,StringType))-1,
 
1341
    if
 
1342
        Max =< BitValMax ->
 
1343
            {0,Max,notab};
 
1344
        true ->
 
1345
            case InOut of
 
1346
                out ->
 
1347
                    {Min,Max,create_char_tab(Min,Chars)};
 
1348
                in  ->
 
1349
                    {Min,Max,list_to_tuple(Chars)}
 
1350
            end
 
1351
    end.
 
1352
 
 
1353
create_char_tab(Min,L) ->
 
1354
    list_to_tuple(create_char_tab(Min,L,0)).
 
1355
create_char_tab(Min,[Min|T],V) ->
 
1356
    [V|create_char_tab(Min+1,T,V+1)];
 
1357
create_char_tab(_Min,[],_V) ->
 
1358
    [];
 
1359
create_char_tab(Min,L,V) ->
 
1360
    [false|create_char_tab(Min+1,L,V)].
 
1361
 
 
1362
%% See Table 20.3 in Dubuisson
 
1363
charbits(NumOfChars) when NumOfChars =< 2 -> 1;
 
1364
charbits(NumOfChars) when NumOfChars =< 4 -> 2;
 
1365
charbits(NumOfChars) when NumOfChars =< 8 -> 3;
 
1366
charbits(NumOfChars) when NumOfChars =< 16 -> 4;
 
1367
charbits(NumOfChars) when NumOfChars =< 32 -> 5;
 
1368
charbits(NumOfChars) when NumOfChars =< 64 -> 6;
 
1369
charbits(NumOfChars) when NumOfChars =< 128 -> 7;
 
1370
charbits(NumOfChars) when NumOfChars =< 256 -> 8;
 
1371
charbits(NumOfChars) when NumOfChars =< 512 -> 9;
 
1372
charbits(NumOfChars) when NumOfChars =< 1024 -> 10;
 
1373
charbits(NumOfChars) when NumOfChars =< 2048 -> 11;
 
1374
charbits(NumOfChars) when NumOfChars =< 4096 -> 12;
 
1375
charbits(NumOfChars) when NumOfChars =< 8192 -> 13;
 
1376
charbits(NumOfChars) when NumOfChars =< 16384 -> 14;
 
1377
charbits(NumOfChars) when NumOfChars =< 32768 -> 15;
 
1378
charbits(NumOfChars) when NumOfChars =< 65536 -> 16;
 
1379
charbits(NumOfChars) when integer(NumOfChars) ->
 
1380
    16 + charbits1(NumOfChars bsr 16).
 
1381
 
 
1382
charbits1(0) ->
 
1383
    0;
 
1384
charbits1(NumOfChars) ->
 
1385
    1 + charbits1(NumOfChars bsr 1).
 
1386
 
 
1387
 
 
1388
chars_decode(Bytes,_,'BMPString',C,Len) ->
 
1389
    case get_constraint(C,'PermittedAlphabet') of
 
1390
        no ->
 
1391
            getBMPChars(Bytes,Len);
 
1392
        _ ->
 
1393
            exit({error,{asn1,
 
1394
                         {'not implemented',
 
1395
                          "BMPString with PermittedAlphabet constraint"}}})
 
1396
    end;
 
1397
chars_decode(Bytes,NumBits,StringType,C,Len) -> 
 
1398
    CharInTab = get_CharInTab(C,StringType),
 
1399
    chars_decode2(Bytes,CharInTab,NumBits,Len).
 
1400
 
 
1401
 
 
1402
chars_decode2(Bytes,CharInTab,NumBits,Len) ->
 
1403
    chars_decode2(Bytes,CharInTab,NumBits,Len,[]).
 
1404
 
 
1405
chars_decode2(Bytes,_CharInTab,_NumBits,0,Acc) ->
 
1406
    {lists:reverse(Acc),Bytes};
 
1407
chars_decode2(Bytes,{Min,Max,notab},NumBits,Len,Acc) when NumBits > 8 ->
 
1408
    {Char,Bytes2} = getbits(Bytes,NumBits),
 
1409
    Result = 
 
1410
        if
 
1411
            Char < 256 -> Char;
 
1412
            true ->
 
1413
                list_to_tuple(binary_to_list(<<Char:32>>))
 
1414
        end,
 
1415
    chars_decode2(Bytes2,{Min,Max,notab},NumBits,Len -1,[Result|Acc]);
 
1416
chars_decode2(Bytes,{Min,Max,notab},NumBits,Len,Acc) ->
 
1417
    {Char,Bytes2} = getbits(Bytes,NumBits),
 
1418
    chars_decode2(Bytes2,{Min,Max,notab},NumBits,Len -1,[Char+Min|Acc]);
 
1419
 
 
1420
%% BMPString and UniversalString with PermittedAlphabet is currently not supported
 
1421
chars_decode2(Bytes,{Min,Max,CharInTab},NumBits,Len,Acc) ->
 
1422
    {Char,Bytes2} = getbits(Bytes,NumBits),
 
1423
    chars_decode2(Bytes2,{Min,Max,CharInTab},NumBits,Len -1,[element(Char+1,CharInTab)|Acc]).
 
1424
 
 
1425
 
 
1426
%% UTF8String
 
1427
encode_UTF8String(Val) when binary(Val) ->
 
1428
    [encode_length(undefined,size(Val)),Val];
 
1429
encode_UTF8String(Val) ->
 
1430
    Bin = list_to_binary(Val),
 
1431
    encode_UTF8String(Bin).
 
1432
 
 
1433
decode_UTF8String(Bytes) ->
 
1434
    {Len,Bytes2} = decode_length(Bytes,undefined),
 
1435
    getoctets_as_bin(Bytes2,Len).
 
1436
    
 
1437
 
 
1438
                                                % X.691:17 
 
1439
encode_null(_) -> []. % encodes to nothing
 
1440
 
 
1441
decode_null(Bytes) ->
 
1442
    {'NULL',Bytes}.
 
1443
 
 
1444
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
1445
%% encode_object_identifier(Val) -> CompleteList
 
1446
%% encode_object_identifier({Name,Val}) -> CompleteList
 
1447
%% Val -> {Int1,Int2,...,IntN} % N >= 2
 
1448
%% Name -> atom()
 
1449
%% Int1 -> integer(0..2)
 
1450
%% Int2 -> integer(0..39) when Int1 (0..1) else integer()
 
1451
%% Int3-N -> integer()
 
1452
%% CompleteList -> [binary()|bitstring()|list()]
 
1453
%%
 
1454
encode_object_identifier({Name,Val}) when atom(Name) ->
 
1455
    encode_object_identifier(Val);
 
1456
encode_object_identifier(Val) ->
 
1457
    OctetList = e_object_identifier(Val),
 
1458
    Octets = list_to_binary(OctetList), % performs a flatten at the same time
 
1459
    [encode_length(undefined,size(Octets)),Octets].
 
1460
 
 
1461
%% This code is copied from asn1_encode.erl (BER) and corrected and modified 
 
1462
 
 
1463
e_object_identifier({'OBJECT IDENTIFIER',V}) ->
 
1464
    e_object_identifier(V);
 
1465
e_object_identifier({Cname,V}) when atom(Cname),tuple(V) ->
 
1466
    e_object_identifier(tuple_to_list(V));
 
1467
e_object_identifier({Cname,V}) when atom(Cname),list(V) ->
 
1468
    e_object_identifier(V);
 
1469
e_object_identifier(V) when tuple(V) ->
 
1470
    e_object_identifier(tuple_to_list(V));
 
1471
 
 
1472
%% E1 = 0|1|2 and (E2 < 40 when E1 = 0|1) 
 
1473
e_object_identifier([E1,E2|Tail]) when E1 >= 0, E1 < 2, E2 < 40 ; E1==2 ->
 
1474
    Head = 40*E1 + E2,  % weird
 
1475
    e_object_elements([Head|Tail],[]);
 
1476
e_object_identifier(Oid=[_,_|_Tail]) ->
 
1477
    exit({error,{asn1,{'illegal_value',Oid}}}).
 
1478
 
 
1479
e_object_elements([],Acc) ->
 
1480
    lists:reverse(Acc);
 
1481
e_object_elements([H|T],Acc) ->
 
1482
    e_object_elements(T,[e_object_element(H)|Acc]).
 
1483
 
 
1484
e_object_element(Num) when Num < 128 ->
 
1485
    [Num];
 
1486
e_object_element(Num) ->
 
1487
    [e_o_e(Num bsr 7)|[Num band 2#1111111]].
 
1488
e_o_e(Num) when Num < 128 ->
 
1489
    Num bor 2#10000000;
 
1490
e_o_e(Num) ->
 
1491
    [e_o_e(Num bsr 7)|[(Num band 2#1111111) bor 2#10000000]].
 
1492
 
 
1493
 
 
1494
 
 
1495
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
1496
%% decode_object_identifier(Bytes) -> {ObjId,RemainingBytes}
 
1497
%% ObjId -> {integer(),integer(),...} % at least 2 integers
 
1498
%% RemainingBytes -> [integer()] when integer() (0..255)
 
1499
decode_object_identifier(Bytes) ->
 
1500
    {Len,Bytes2} = decode_length(Bytes,undefined),
 
1501
    {Octs,Bytes3} = getoctets_as_list(Bytes2,Len),
 
1502
    [First|Rest] = dec_subidentifiers(Octs,0,[]),
 
1503
    Idlist = if
 
1504
                 First < 40 ->
 
1505
                     [0,First|Rest];
 
1506
                 First < 80 ->
 
1507
                     [1,First - 40|Rest];
 
1508
                 true ->
 
1509
                     [2,First - 80|Rest]
 
1510
             end,
 
1511
    {list_to_tuple(Idlist),Bytes3}.
 
1512
 
 
1513
dec_subidentifiers([H|T],Av,Al) when H >=16#80 ->
 
1514
    dec_subidentifiers(T,(Av bsl 7) + (H band 16#7F),Al);
 
1515
dec_subidentifiers([H|T],Av,Al) ->
 
1516
    dec_subidentifiers(T,0,[(Av bsl 7) + H |Al]);
 
1517
dec_subidentifiers([],_Av,Al) ->
 
1518
    lists:reverse(Al).
 
1519
 
 
1520
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
1521
%% encode_relative_oid(Val) -> CompleteList
 
1522
%% encode_relative_oid({Name,Val}) -> CompleteList
 
1523
encode_relative_oid({Name,Val}) when is_atom(Name) ->
 
1524
    encode_relative_oid(Val);
 
1525
encode_relative_oid(Val) when is_tuple(Val) ->
 
1526
    encode_relative_oid(tuple_to_list(Val));
 
1527
encode_relative_oid(Val) when is_list(Val) ->
 
1528
    Octets = list_to_binary([e_object_element(X)||X <- Val]),
 
1529
    [encode_length(undefined,size(Octets)),Octets].
 
1530
    
 
1531
    
 
1532
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
1533
%% decode_relative_oid(Val) -> CompleteList
 
1534
%% decode_relative_oid({Name,Val}) -> CompleteList
 
1535
decode_relative_oid(Bytes) ->
 
1536
    {Len,Bytes2} = decode_length(Bytes,undefined),
 
1537
    {Octs,Bytes3} = getoctets_as_list(Bytes2,Len),
 
1538
    ObjVals = dec_subidentifiers(Octs,0,[]),
 
1539
    {list_to_tuple(ObjVals),Bytes3}.
 
1540
 
 
1541
 
 
1542
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
1543
%% encode_real(Val) -> CompleteList
 
1544
%% encode_real({Name,Val}) -> CompleteList
 
1545
encode_real({Name,Val}) when is_atom(Name) ->
 
1546
    encode_real(Val);
 
1547
encode_real(Real) ->
 
1548
    {EncVal,Len} = ?RT_COMMON:encode_real([],Real),
 
1549
    [encode_length(undefined,Len),EncVal].
 
1550
 
 
1551
 
 
1552
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
1553
%% decode_real(Val) -> {REALvalue,Rest}
 
1554
%% decode_real({Name,Val}) -> {REALvalue,Rest}
 
1555
decode_real(Bytes) ->
 
1556
    {Len,Bytes2} = decode_length(Bytes,undefined),
 
1557
    <<Bytes3:Len/binary,Rest/bitstring>> = Bytes2,
 
1558
    {RealVal,Rest,Len} = ?RT_COMMON:decode_real(Bytes3,Len),
 
1559
    {RealVal,Rest}.
 
1560
 
 
1561
 
 
1562
get_constraint([{Key,V}],Key) ->
 
1563
    V;
 
1564
get_constraint([],_Key) ->
 
1565
    no;
 
1566
get_constraint(C,Key) ->
 
1567
    case lists:keysearch(Key,1,C) of
 
1568
        false ->
 
1569
            no;
 
1570
        {value,{_,V}} -> 
 
1571
            V
 
1572
    end.
 
1573
 
 
1574
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
1575
%% complete(InList) -> ByteList
 
1576
%% Takes a coded list with bits and bytes and converts it to a list of bytes
 
1577
%% Should be applied as the last step at encode of a complete ASN.1 type
 
1578
%%
 
1579
complete(InList) when is_list(InList) ->
 
1580
    case complete1(InList) of
 
1581
        <<>> ->
 
1582
            <<0>>;
 
1583
        Res ->
 
1584
            case bit_size(Res) band 7 of
 
1585
                0 -> Res;
 
1586
                Bits -> <<Res/bitstring,0:(8-Bits)>>
 
1587
        end
 
1588
    end;
 
1589
complete(InList) when is_binary(InList) ->
 
1590
    InList;
 
1591
complete(InList) when is_bitstring(InList) ->
 
1592
    PadLen = 8 - (bit_size(InList) band 7),
 
1593
    <<InList/bitstring,0:PadLen>>.
 
1594
 
 
1595
complete1(L) when is_list(L) ->
 
1596
    list_to_bitstring(L).
 
1597
 
 
1598
%% Special version of complete that does not align the completed message.
 
1599
complete_NFP(InList) when is_list(InList) ->
 
1600
    list_to_bitstring(InList);
 
1601
complete_NFP(InList) when is_bitstring(InList) ->
 
1602
    InList.
 
1603
 
 
1604
%% unaligned helpers
 
1605
num_bits(1) -> 0;
 
1606
num_bits(2) -> 1;
 
1607
num_bits(R) when R =< 4 -> 
 
1608
    2;
 
1609
num_bits(R) when R =< 8 ->
 
1610
    3;
 
1611
num_bits(R) when R =< 16 ->
 
1612
    4;
 
1613
num_bits(R) when R =< 32 ->
 
1614
    5;  
 
1615
num_bits(R) when R =< 64 ->
 
1616
    6;
 
1617
num_bits(R) when R =< 128 ->
 
1618
    7;
 
1619
num_bits(R) when R =< 255 ->
 
1620
    8;
 
1621
num_bits(R) when R =< 511 ->
 
1622
    9;
 
1623
num_bits(R) when R =< 1023 ->
 
1624
    10;
 
1625
num_bits(R) ->
 
1626
    1+num_bits(R bsr 1).