osmo_smsc/src/bcd_codec.erl

135 lines
4.7 KiB
Erlang

% BCD (Binary-Coded Decimal) routines.
% https://en.wikipedia.org/wiki/Binary-coded_decimal
%
% (C) 2020 by Vadim Yanitskiy <axilirator@gmail.com>
%
% All Rights Reserved
%
% This program is free software; you can redistribute it and/or modify
% it under the terms of the GNU Affero General Public License as
% published by the Free Software Foundation; either version 3 of the
% License, or (at your option) any later version.
%
% This program is distributed in the hope that it will be useful,
% but WITHOUT ANY WARRANTY; without even the implied warranty of
% MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
% GNU General Public License for more details.
%
% You should have received a copy of the GNU Affero General Public License
% along with this program. If not, see <http://www.gnu.org/licenses/>.
%
% Additional Permission under GNU AGPL version 3 section 7:
%
% If you modify this Program, or any covered work, by linking or
% combining it with runtime libraries of Erlang/OTP as released by
% Ericsson on http://www.erlang.org (or a modified version of these
% libraries), containing parts covered by the terms of the Erlang Public
% License (http://www.erlang.org/EPLICENSE), the licensors of this
% Program grant you additional permission to convey the resulting work
% without the need to license the runtime libraries of Erlang/OTP under
% the GNU Affero General Public License. Corresponding Source for a
% non-source form of such a combination shall include the source code
% for the parts of the runtime libraries of Erlang/OTP used as well as
% that of the covered work.
-module(bcd_codec).
-export([encode/1,
encode_nopad/1,
decode/1,
encode_num/1,
decode_num/1
]).
%% BCD-encode a number or a string of digits.
%% The result is octet-aligned (with optional padding).
%% Examples: "26242" -> << 16#62, 16#42, 16#f2 >>,
%% 90170 -> << 16#09, 16#71, 16#f0 >>.
-spec encode(list() | binary() | integer()) -> binary().
encode(Data) when is_list(Data); is_binary(Data); is_integer(Data) ->
encode_pad_nopad(Data, true).
%% Same as encode/1, but without padding.
-spec encode_nopad(list() | binary() | integer()) -> bitstring().
encode_nopad(Data) when is_list(Data); is_binary(Data); is_integer(Data) ->
encode_pad_nopad(Data, false).
-spec encode_pad_nopad(list() | binary() | integer(), boolean()) -> bitstring().
encode_pad_nopad(Data, Pad) when is_integer(Data) ->
encode_pad_nopad(integer_to_list(Data), Pad);
encode_pad_nopad(Data, Pad) when is_binary(Data) ->
encode_pad_nopad(binary_to_list(Data), Pad);
encode_pad_nopad(Data, Pad) when is_list(Data) ->
case {encode(Data, << >>), Pad} of
{{odd, BCDNum, N1}, true} ->
%% Odd number of digits, with padding
<< BCDNum/bytes, 02#1111:4, N1:4 >>;
{{odd, BCDNum, N1}, false} ->
%% Odd number of digits, without padding
<< BCDNum/bytes, N1:4 >>;
{{even, BCDNum}, _} ->
%% Even number of digits
BCDNum
end.
encode([D1, D2 | Tail], BCDNum) ->
N1 = bcd_nibble(D1), N2 = bcd_nibble(D2),
N21 = N1 bor (N2 bsl 4),
encode(Tail, << BCDNum/bytes, N21 >>);
encode([D1], BCDNum) ->
N1 = bcd_nibble(D1),
{odd, << BCDNum/bytes >>, N1};
encode([], BCDNum) -> {even, BCDNum}.
%% Convert an ASCII character to a BCD digit (nibble).
bcd_nibble(C) when C >= $0, C =< $9 -> C - $0;
bcd_nibble($a) -> 16#0a;
bcd_nibble($b) -> 16#0b;
bcd_nibble($c) -> 16#0c;
bcd_nibble($*) -> 16#0d;
bcd_nibble($#) -> 16#0e;
bcd_nibble(C) -> error({bad_bcd_character, C}).
%% Convert a BCD digit (nibble) to an ASCII character.
bcd_ascii(D) when D >= 0, D =< 9 -> D + $0;
bcd_ascii(16#0a) -> $a;
bcd_ascii(16#0b) -> $b;
bcd_ascii(16#0c) -> $c;
bcd_ascii(16#0d) -> $*;
bcd_ascii(16#0e) -> $#;
bcd_ascii(D) -> error({bad_bcd_nibble, D}).
%% Decode a BCD-encoded number into a "string" (list of ACSII symbols).
%% Examples: << 16#62, 16#42, 16#f2 >> -> "26242",
%% << 16#09, 16#71, 16#f0 >> -> "90170".
-spec decode(binary() | list()) -> list().
decode(Data) when is_list(Data) ->
Binary = list_to_binary(Data),
decode(Binary, []);
decode(Data) when is_binary(Data) ->
decode(Data, []).
decode(<< 02#1111:4, N1:4 >>, ACSII) ->
C1 = bcd_ascii(N1),
decode(<< >>, [C1 | ACSII]);
decode(<< N2:4, N1:4, Tail/bits >>, ACSII) ->
C1 = bcd_ascii(N1), C2 = bcd_ascii(N2),
decode(Tail, [C2, C1 | ACSII]);
decode(<< >>, ACSII) -> lists:reverse(ACSII).
%% BCD-encode a number in range [0 .. 99].
%% Examples: 10#05 -> 16#50,
%% 10#82 -> 16#28.
-spec encode_num(integer()) -> integer().
encode_num(Num) when Num >= 0, Num =< 99 ->
N1 = Num div 10, N2 = Num rem 10,
N1 bor (N2 bsl 4).
%% Decode a BCD-coded number in range [0 .. 99].
%% Examples: 16#14 -> 10#41,
%% 16#39 -> 10#93.
-spec decode_num(integer()) -> integer().
decode_num(Num) when Num >= 0, Num =< 16#99, (Num rem 16) < 10 ->
<< N2:4, N1:4 >> = << Num >>,
N1 * 10 + N2.