Skip to content

Commit

Permalink
asn1: Fix compilation error when BER and JER are combined
Browse files Browse the repository at this point in the history
Closes #8291
  • Loading branch information
bjorng committed Mar 22, 2024
1 parent 928d03e commit 58bd650
Show file tree
Hide file tree
Showing 2 changed files with 25 additions and 20 deletions.
30 changes: 15 additions & 15 deletions lib/asn1/src/asn1rtt_jer.erl
Original file line number Diff line number Diff line change
Expand Up @@ -464,7 +464,7 @@ jer_do_encode_named_bit_string([FirstVal | RestVal], NamedBitList) ->
ToSetPos = jer_get_all_bitposes([FirstVal | RestVal], NamedBitList, []),
Size = lists:max(ToSetPos) + 1,
BitList = jer_make_and_set_list(Size, ToSetPos, 0),
encode_bitstring(BitList).
jer_encode_bitstring(BitList).

jer_get_all_bitposes([{bit, ValPos} | Rest], NamedBitList, Ack) ->
jer_get_all_bitposes(Rest, NamedBitList, [ValPos | Ack]);
Expand Down Expand Up @@ -494,31 +494,31 @@ jer_make_and_set_list(Len, [], XPos) ->
%% ([bitlist]) -> {ListLen, UnusedBits, OctetList}
%%=================================================================

encode_bitstring([B8, B7, B6, B5, B4, B3, B2, B1 | Rest]) ->
jer_encode_bitstring([B8, B7, B6, B5, B4, B3, B2, B1 | Rest]) ->
Val = (B8 bsl 7) bor (B7 bsl 6) bor (B6 bsl 5) bor (B5 bsl 4) bor
(B4 bsl 3) bor (B3 bsl 2) bor (B2 bsl 1) bor B1,
encode_bitstring(Rest, <<Val>>);
encode_bitstring(Val) ->
unused_bitlist(Val, <<>>).
jer_encode_bitstring(Rest, <<Val>>);
jer_encode_bitstring(Val) ->
jer_unused_bitlist(Val, <<>>).

encode_bitstring([B8, B7, B6, B5, B4, B3, B2, B1 | Rest], Ack) ->
jer_encode_bitstring([B8, B7, B6, B5, B4, B3, B2, B1 | Rest], Acc) ->
Val = (B8 bsl 7) bor (B7 bsl 6) bor (B6 bsl 5) bor (B5 bsl 4) bor
(B4 bsl 3) bor (B3 bsl 2) bor (B2 bsl 1) bor B1,
encode_bitstring(Rest, [Ack | [Val]]);
jer_encode_bitstring(Rest, [Acc | [Val]]);
%%even multiple of 8 bits..
encode_bitstring([], Ack) ->
Ack;
jer_encode_bitstring([], Acc) ->
Acc;
%% unused bits in last octet
encode_bitstring(Rest, Ack) ->
unused_bitlist(Rest,Ack).
jer_encode_bitstring(Rest, Acc) ->
jer_unused_bitlist(Rest, Acc).

%%%%%%%%%%%%%%%%%%
%% unused_bitlist([list of ones and zeros <= 7], 7, []) ->
%% {Unused bits, Last octet with bits moved to right}
unused_bitlist([], Ack) ->
Ack;
unused_bitlist([Bit | Rest], Ack) ->
unused_bitlist(Rest, <<Ack/bitstring,Bit:1>>).
jer_unused_bitlist([], Acc) ->
Acc;
jer_unused_bitlist([Bit | Rest], Acc) ->
jer_unused_bitlist(Rest, <<Acc/bitstring,Bit:1>>).

jer_bitstr2names(BitStr,[]) ->
BitStr;
Expand Down
15 changes: 10 additions & 5 deletions lib/asn1/test/asn1_SUITE.erl
Original file line number Diff line number Diff line change
Expand Up @@ -224,7 +224,7 @@ have_jsonlib() ->

test(Config, TestF) ->
TestJer = case have_jsonlib() of
true -> [jer];
true -> [jer, {ber, [ber,jer]}];
false -> []
end,
test(Config, TestF, [per,
Expand Down Expand Up @@ -445,7 +445,13 @@ testExtensionDefault(Config) ->
test(Config, fun testExtensionDefault/3).
testExtensionDefault(Config, Rule, Opts) ->
asn1_test_lib:compile_all(["ExtensionDefault"], Config, [Rule|Opts]),
testExtensionDefault:main(Rule).
case lists:member(ber, Opts) andalso lists:member(jer, Opts) of
true ->
%% JER back-end disables maps for BER, too.
ok;
false ->
testExtensionDefault:main(Rule)
end.

testMaps(Config) ->
Jer = case have_jsonlib() of
Expand Down Expand Up @@ -1012,9 +1018,8 @@ testNortel(Config) -> test(Config, fun testNortel/3).
testNortel(Config, Rule, Opts) ->
asn1_test_lib:compile("Nortel", Config, [Rule|Opts]).

test_undecoded_rest(Config) -> test(Config, fun test_undecoded_rest/3).
test_undecoded_rest(_Config,jer,_Opts) ->
ok; % not relevant for JER
test_undecoded_rest(Config) ->
test(Config, fun test_undecoded_rest/3, [per, uper, ber]).
test_undecoded_rest(Config, Rule, Opts) ->
do_test_undecoded_rest(Config, Rule, Opts),
do_test_undecoded_rest(Config, Rule, [no_ok_wrapper|Opts]),
Expand Down

0 comments on commit 58bd650

Please sign in to comment.