Skip to content

Commit

Permalink
Merge branch 'maint'
Browse files Browse the repository at this point in the history
* maint:
  asn1: Fix several bugs in encoding and decoding of REALs
  • Loading branch information
bjorng committed Feb 24, 2025
2 parents 64185e7 + 97a9dcf commit d24c732
Show file tree
Hide file tree
Showing 4 changed files with 35 additions and 22 deletions.
12 changes: 10 additions & 2 deletions lib/asn1/doc/guides/asn1_getting_started.md
Original file line number Diff line number Diff line change
Expand Up @@ -417,13 +417,21 @@ It is assigned a value in Erlang as follows:

```text
R1value1 = "2.14",
R1value2 = {256,10,-2},
R1value2 = {256,10,-2}
```

In the last line, notice that the tuple \{256,10,-2\} is the real number 2.56 in
a special notation, which encodes faster than simply stating the number as
`"2.56"`. The arity three tuple is `{Mantissa,Base,Exponent}`, that is,
Mantissa \* Base^Exponent.
`Mantissa * Base^Exponent`.

The following special values are also recognized:

```text
R1value3 = 0,
R1value4 = 'PLUS-INFINITY',
R1value5 = 'MINUS-INFINITY'
```

### NULL

Expand Down
2 changes: 1 addition & 1 deletion lib/asn1/src/asn1ct_gen_ber_bin_v2.erl
Original file line number Diff line number Diff line change
Expand Up @@ -236,7 +236,7 @@ gen_encode_prim(_Erules, #type{}=D, DoTag, Value) ->
asn1ct_name:new(realsize),
emit(["begin",nl,
{curr,realval}," = ",
{call,real_common,ber_encode_real,[Value]},com,nl,
{call,real_common,encode_real,[Value]},com,nl,
{curr,realsize}," = ",
{call,erlang,byte_size,[{curr,realval}]},com,nl,
{call,ber,encode_tags,
Expand Down
34 changes: 16 additions & 18 deletions lib/asn1/src/asn1rtt_real_common.erl
Original file line number Diff line number Diff line change
Expand Up @@ -19,8 +19,7 @@
%%
-module(asn1rtt_real_common).

-export([encode_real/1,decode_real/1,
ber_encode_real/1]).
-export([encode_real/1,decode_real/1]).

%%============================================================================
%%
Expand All @@ -30,14 +29,14 @@
%% encode real value
%%============================================================================

ber_encode_real(0) ->
{[],0};
ber_encode_real('PLUS-INFINITY') ->
{[64],1};
ber_encode_real('MINUS-INFINITY') ->
{[65],1};
ber_encode_real(Val) when is_tuple(Val); is_list(Val) ->
encode_real(Val).
encode_real(0) ->
<<>>;
encode_real('PLUS-INFINITY') ->
<<2#0100_0000>>;
encode_real('MINUS-INFINITY') ->
<<2#0100_0001>>;
encode_real(Val) when is_tuple(Val); is_list(Val) ->
encode_real([], Val).

%%%%%%%%%%%%%%
%% only base 2 encoding!
Expand Down Expand Up @@ -73,9 +72,6 @@ ber_encode_real(Val) when is_tuple(Val); is_list(Val) ->
%% bit shifted until it is an odd number. Thus, do this for BER as
%% well.

encode_real(Real) ->
encode_real([], Real).

encode_real(_C, {Mantissa, Base, Exponent}) when Base =:= 2 ->
%% io:format("Mantissa: ~w Base: ~w, Exp: ~w~n",[Man, Base, Exp]),
{Man,ExpAdd} = truncate_zeros(Mantissa), %% DER adjustment
Expand Down Expand Up @@ -214,14 +210,16 @@ decode_real(Buffer) ->
{RealVal,<<>>,Sz} = decode_real2(Buffer, [], Sz, 0),
RealVal.

decode_real2(Buffer, _C, 0, _RemBytes) ->
{0,Buffer};
decode_real2(<<>>, _C, 0, _RemBytes) ->
{0,<<>>,0};
decode_real2(Buffer0, _C, Len, RemBytes1) ->
<<First, Buffer2/binary>> = Buffer0,
if
First =:= 2#01000000 -> {'PLUS-INFINITY', Buffer2};
First =:= 2#01000001 -> {'MINUS-INFINITY', Buffer2};
First =:= 1 orelse First =:= 2 orelse First =:= 3 ->
First =:= 2#01000000 ->
{'PLUS-INFINITY', Buffer2, 1};
First =:= 2#01000001 ->
{'MINUS-INFINITY', Buffer2, 1};
First =:= 1; First =:= 2; First =:= 3 ->
%% character string encoding of base 10
{NRx,Rest} = split_binary(Buffer2,Len-1),
{binary_to_list(NRx),Rest,Len};
Expand Down
9 changes: 8 additions & 1 deletion lib/asn1/test/testPrim.erl
Original file line number Diff line number Diff line change
Expand Up @@ -226,7 +226,14 @@ real(_Rules) ->
%%==========================================================
%% AngleInRadians ::= REAL
%%==========================================================


%% Zero
real_roundtrip('AngleInRadians', 0),

%% Infinities
real_roundtrip('AngleInRadians', 'MINUS-INFINITY'),
real_roundtrip('AngleInRadians', 'PLUS-INFINITY'),

%% Base 2
real_roundtrip('AngleInRadians', {1,2,1}),
real_roundtrip('AngleInRadians', {129,2,1}),
Expand Down

0 comments on commit d24c732

Please sign in to comment.