Implement SM-TP (Short Message Transport Protocol) codec

This commit is contained in:
Vadim Yanitskiy 2020-04-20 22:14:15 +07:00
parent a578e6bcae
commit 799b71592c
2 changed files with 624 additions and 0 deletions

413
src/sm_tp_codec.erl Normal file
View File

@ -0,0 +1,413 @@
% SM-TP (Short Message Transport Protocol) codec (as per 3GPP TS 23.040).
% Coding of some messages depends on type of the containing RPDU.
%
% (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(sm_tp_codec).
-export([encode/2, decode/2]).
-ifdef (TEST).
-export ([encode_tp_addr/2, decode_tp_addr/1]).
-export ([encode_tp_scts/2, decode_tp_scts/1]).
-export ([decode_tp_vp/2]).
-endif.
%% 9.2.3.1 "TP-Message-Type-Indicator (TP-MTI)"
-define(TP_MTI_SUBMIT, 02#01).
-define(TP_MTI_COMMAND, 02#10).
-define(TP_MTI_DELIVER, 02#00).
-define(TP_MTI_SUBMIT_REPORT, 02#01).
-define(TP_MTI_STATUS_REPORT, 02#10).
-define(TP_MTI_DELIVER_REPORT, 02#00).
%% 9.2.3.3 "TP-Validity-Period-Format (TP-VPF)"
-define(TP_VP_VPF_ABSENT, 02#00).
-define(TP_VP_VPF_RELATIVE, 02#10).
-define(TP_VP_VPF_ENHANCED, 02#01).
-define(TP_VP_VPF_ABSOLUTE, 02#11).
%% 9.2.3.12.3 "TP-Validity-Period (Enhanced format)" sub-types
-define(TP_VP_EVPF_ABSENT, 02#000).
-define(TP_VP_EVPF_RELATIVE, 02#001).
-define(TP_VP_EVPF_RELATIVE_SEC, 02#010).
-define(TP_VP_EVPF_RELATIVE_BCD, 02#011).
%% 9.2.2 TP-User-Data may contain up to 140 octets
%% (together with optional TP-User-Data-Header)
-define(TP_USER_DATA_MAX_LEN, 140).
-define(TP_USER_DATA_PADDING, 16#ff).
%% Encode TP-{Originating,Destination}-Address (see 9.2.3.7 and 9.2.3.8).
%% NOTE: The Addr is expected to be octet-aligned and encoded by the caller.
%% TODO: The maximum length of the full address field is 12 octets (see 9.1.2.5).
encode_tp_addr({NPI, ToN}, {AddrBitLen, Addr}) when is_binary(Addr) ->
%% QBitNum indicates number of useful nibbles (octet halves) in the Address
%% regardless of the indicated ToN (e.g. BCD number or alphanumeric),
%% excluding any nibbles containing only fill bits.
case {AddrBitLen div 4, AddrBitLen rem 4} of
{QBitEven, QBitRem} when QBitRem > 0 ->
AddrQBitLen = QBitEven + 1;
{QBitEven, 0} ->
AddrQBitLen = QBitEven
end,
%% As per 9.1.2.5, the 1st MSB of the 2nd octet shall be set high.
<< AddrQBitLen, 1:1, ToN:3, NPI:4, Addr/bytes >>.
%% Decode TP-{Originating,Destination}-Address (see 9.2.3.7 and 9.2.3.8).
%% NOTE: The returned Addr is octet-aligned and to be decoded by the caller.
decode_tp_addr(TPDU) when is_binary(TPDU) ->
%% QBitLen indicates number of useful nibbles (octet halves) in the Address
%% regardless of the indicated ToN (e.g. BCD number or alphanumeric),
%% excluding any nibbles containing only fill bits.
%% As per 9.1.2.5, the 1st MSB of the 2nd octet shall be set high.
<< QBitLen, 1:1, ToN:3, NPI:4, AddrRest/bytes >> = TPDU,
%% Full address field shall be octet-aligned, so there may be optional padding.
if (QBitLen rem 2) =/= 0 ->
AddrByteLen = QBitLen div 2 + 1;
true ->
AddrByteLen = QBitLen div 2
end,
<< Addr:AddrByteLen/bytes, Rest/bytes >> = AddrRest,
{ok, {NPI, ToN}, {QBitLen * 4, Addr}, Rest}.
%% Encode TP-Service-Centre-Time-Stamp as per 9.2.3.11.
encode_tp_scts(current, TimeZone) ->
LocalTime = erlang:localtime(),
encode_tp_scts(LocalTime, TimeZone);
encode_tp_scts(LocalTime, {TZHour, TZMin}) when (TZMin rem 15) == 0 ->
%% Encoded timezone is in quarters of an hour (signed)
if TZHour < 0 ->
AbsOffset = (TZHour * 60 * -1 + TZMin) div 15,
encode_tp_scts(LocalTime, 1, AbsOffset);
true ->
AbsOffset = (TZHour * 60 + TZMin) div 15,
encode_tp_scts(LocalTime, 0, AbsOffset)
end.
encode_tp_scts({{Year, Month, Day}, {Hour, Min, Sec}}, Minus, AbsOffset) ->
%% BCD-encode date and time as YY:MM:DD:hh:mm:ss.
DateTimeList = lists:map(fun bcd_codec:encode_num/1,
[Year rem 100, Month, Day, Hour, Min, Sec]),
DateTime = list_to_binary(DateTimeList),
%% BCD-encode the timezone offset.
N1 = AbsOffset div 10,
N2 = AbsOffset rem 10,
TZ = << N2:4, Minus:1, N1:3 >>,
<< DateTime/bytes, TZ/bytes >>.
%% Decode TP-Service-Centre-Time-Stamp as per 9.2.3.11.
decode_tp_scts(<< DateTime:6/bytes, N2:4, Minus:1, N1:3 >>) ->
%% Decode BCD-coded date and time as YY:MM:DD:hh:mm:ss.
DateTimeList = lists:map(fun bcd_codec:decode_num/1,
binary_to_list(DateTime)),
[Year, Month, Day, Hour, Min, Sec] = DateTimeList,
%% Decode BCD-encoded (in quarters of an hour) timezone offset.
AbsOffset = (N1 * 10) + N2,
if Minus == 1 ->
TZHour = -AbsOffset div 4;
true ->
TZHour = AbsOffset div 4
end,
TZMin = AbsOffset * 15 rem 60,
{ok, {{Year, Month, Day}, {Hour, Min, Sec}}, {TZHour, TZMin}}.
%% TP-Validity-Period is not present.
decode_tp_vp(?TP_VP_VPF_ABSENT, Rest) ->
{ok, omit, Rest};
%% 9.2.3.12.1 TP-Validity-Period (Relative format).
%% NOTE: Returned value is always in seconds.
decode_tp_vp(?TP_VP_VPF_RELATIVE, << VP:8, Rest/bytes >>) ->
if VP >= 0, VP =< 143 ->
Minutes = (VP + 1) * 5;
VP >= 144, VP =< 167 ->
%% 12 hours + (VP - 143) * 30 minutes
Minutes = 12 * 60 + (VP - 143) * 30;
VP >= 168, VP =< 196 ->
%% (VP - 166) days
Minutes = (VP - 166) * 24 * 60;
VP >= 197, VP =< 255 ->
%% (VP - 192) weeks
Minutes = (VP - 192) * 7 * 24 * 60
end,
{ok, {relative, Minutes * 60}, Rest};
%% 9.2.3.12.2 TP-Validity-Period (Absolute format).
%% The representation of time is identical to TP-Service-Centre-Time-Stamp.
decode_tp_vp(?TP_VP_VPF_ABSOLUTE, << VP:7/bytes, Rest/bytes >>) ->
{ok, DateTime, TimeZone} = decode_tp_scts(VP),
{ok, {absolute, DateTime, TimeZone}, Rest};
%% 9.2.3.12.3 TP-Validity-Period (Enhanced format, no extensions).
decode_tp_vp(?TP_VP_VPF_ENHANCED, << 0:1, SingleShot:1, _:3, EVPF:3,
VP:6/bytes, Rest/bytes >>) ->
case EVPF of
?TP_VP_EVPF_ABSENT ->
Result = omit;
?TP_VP_EVPF_RELATIVE ->
{ok, Result, _} = decode_tp_vp(?TP_VP_VPF_RELATIVE, VP);
?TP_VP_EVPF_RELATIVE_SEC ->
<< Seconds, _VPRest/bytes >> = VP,
Result = {relative, Seconds};
?TP_VP_EVPF_RELATIVE_BCD ->
<< Hh, Mm, Ss, _VPRest/bytes >> = VP,
Seconds = bcd_codec:decode_num(Hh) * 60 * 60
+ bcd_codec:decode_num(Mm) * 60
+ bcd_codec:decode_num(Ss),
Result = {relative, Seconds};
_ ->
Result = reserved
end,
{ok, {enhanced, SingleShot, Result}, Rest};
decode_tp_vp(02#01, << 1:1, _/bits >>) -> error({vpf_ext_not_supported});
decode_tp_vp(VPF, _) -> error({unknown_vpf, VPF}).
%% Decode TP-User-Data and TP-User-Data-Header (if present).
%% Depending on DCS, TP-User-Data-Length can be in septets or octets.
decode_tp_ud(_UDHI, _DCS, TPDU) ->
%% TODO: actually decode UD-Header if present
%% NOTE: UDLen may indicate either the number of octets or septets
%% NOTE: UDHLen always in octets
<< _UDLen, UserData/bytes >> = TPDU,
{ok, {[], UserData}}.
%% 23.040 9.2.2.2
decode_submit(TPDU) ->
%% Header and TP-Message-Reference
<< RP:1, UDHI:1, SRR:1, VPF:2, RD:1, ?TP_MTI_SUBMIT:2,
MR, Rest1/binary >> = TPDU,
%% TP-Destination-Address (variable size, odd units, padding)
{ok, DAType, DA, Rest2} = decode_tp_addr(Rest1),
%% TP-Protocol-Identifier and TP-Data-Coding-Scheme
<< PID, DCS, Rest3/binary >> = Rest2,
%% followed by optional TP-Validity-Period (depends on VPF)
{ok, VP, Rest4} = decode_tp_vp(VPF, Rest3),
%% Finally, TP-User-Data (and optional UD-Header)
{ok, UD} = decode_tp_ud(UDHI, DCS, Rest4),
{ok, {sm_tp_submit, #{reply_path_req => RP,
status_report_req => SRR,
reject_duplicates => RD,
tp_msg_ref => MR,
dest_addr => {DAType, DA},
pid => PID, dcs => DCS,
valid_period => VP,
user_data => UD}}}.
%% 23.040 9.2.2.4
decode_command(TPDU) ->
<< _:1, _UDHI:1, SRR:1, _:3, ?TP_MTI_COMMAND:2,
MR, PID, CT, MN, Rest1/binary >> = TPDU,
%% TP-Destination-Address (variable size, odd units, padding)
{ok, DAType, DA, Rest2} = decode_tp_addr(Rest1),
%% TP-Command-Data and its length
<< CDLen, CommandData:CDLen/bytes >> = Rest2,
{ok, {sm_tp_command, #{status_report_req => SRR,
tp_msg_ref => MR,
pid => PID,
cmd_type => CT,
msg_number => MN,
dest_addr => {DAType, DA},
cmd_data => CommandData}}}.
%% 23.040 9.2.2.2a (ii)
decode_submit_report_ack(TPDU) ->
%% NOTE: Extension bit (for PID) != 0 is not supported
<< _:1, UDHI:1, _:4, ?TP_MTI_SUBMIT_REPORT:2,
0:1, _:4, UDPres:1, DCSPres:1, PIDPres:1,
SCTS:7/bytes, Rest1/binary >> = TPDU,
%% PID, DCS fields are optional (presence defined by flags)
<< PID:PIDPres/unit:8, DCS:DCSPres/unit:8, Rest2/bytes >> = Rest1,
if %% TP-User-Data is also optional
UDPres == 1, size(Rest2) > 0 ->
{ok, UD} = decode_tp_ud(UDHI, DCS, Rest2);
true ->
UD = omit
end,
%% TODO: further decode TP-Service-Centre-Time-Stamp
{ok, {sm_tp_submit_report, #{sc_time_stamp => SCTS,
pid => PID, dcs => DCS,
user_data => UD}}}.
%% 23.040 9.2.2.2a (i)
decode_submit_report_error(TPDU) ->
%% NOTE: Extension bit (for PID) != 0 is not supported
<< _:1, UDHI:1, _:4, ?TP_MTI_SUBMIT_REPORT:2,
Cause, 0:1, _:4, UDPres:1, DCSPres:1, PIDPres:1,
SCTS:7/bytes, Rest1/binary >> = TPDU,
%% PID, DCS fields are optional (presence defined by flags)
<< PID:PIDPres/unit:8, DCS:DCSPres/unit:8, Rest2/bytes >> = Rest1,
if %% TP-User-Data is also optional
UDPres == 1, size(Rest2) > 0 ->
{ok, UD} = decode_tp_ud(UDHI, DCS, Rest2);
true ->
UD = omit
end,
%% TODO: further decode TP-Service-Centre-Time-Stamp
{ok, {sm_tp_submit_report, #{sc_time_stamp => SCTS,
pid => PID, dcs => DCS,
cause => Cause,
user_data => UD}}}.
decode(RPMsgType, << _:6, MTI:2, _/bits >> = TPDU) ->
case {RPMsgType, MTI} of
%% Mobile originated message submission
{sm_rp_mo_data, ?TP_MTI_SUBMIT} ->
%% MS -> MSC/SGSN: RP-DATA
decode_submit(TPDU);
{sm_rp_mo_data, ?TP_MTI_COMMAND} ->
%% MS -> MSC/SGSN: RP-DATA
decode_command(TPDU);
{sm_rp_mo_ack, ?TP_MTI_SUBMIT_REPORT} ->
%% MSC/SGSN -> MS: RP-ACK
decode_submit_report_ack(TPDU);
{sm_rp_mo_error, ?TP_MTI_SUBMIT_REPORT} ->
%% MSC/SGSN -> MS: RP-ERROR
decode_submit_report_error(TPDU);
_ ->
{error, unknown_msg}
end.
%% Encode TP-User-Data and TP-User-Data-Header(s) as per 9.2.3.24.
%% NOTE: UserData must be encoded by the caller itself.
encode_tp_ud(HdrList, UserData) ->
Hdrs = encode_tp_ud_hdrs(HdrList, << >>),
HdrsLen = byte_size(Hdrs),
%% The maximum length of TP-User-Data (and optional headers) is 140 octets.
%% NOTE: byte_size() will round the size to octet boundary.
TotalLen = HdrsLen + byte_size(UserData),
if TotalLen > ?TP_USER_DATA_MAX_LEN ->
error({sm_tp_ud, overflow, TotalLen});
true ->
%% TPDU must be octet-aligned
%% TODO: is there a more elegant way?
PadLen = byte_size(UserData) * 8 - bit_size(UserData),
UDEnc = << Hdrs/bytes, UserData/bits, ?TP_USER_DATA_PADDING:PadLen >>,
{HdrsLen, UDEnc}
end.
encode_tp_ud_hdrs([{Type, Value} | Tail], Hdrs) ->
Length = byte_size(Value),
HdrTLV = << Type:8, Length:8, Value/bytes >>,
encode_tp_ud_hdrs(Tail, << Hdrs/bytes, HdrTLV/bytes >> );
encode_tp_ud_hdrs([], Hdrs) -> Hdrs.
%% Calculate the number of septets or octets (depending on DCS)
%% in both TP-User-Data and TP-User-Data-Header(s).
calc_tp_udl(_DCS, HdrsLen, UserDataBitLen) ->
%% HACK! TODO: parse DCS as per 3GPP TS 23.038, section 4
if (UserDataBitLen rem 8) > 0 ->
(HdrsLen * 8 div 7) + (UserDataBitLen div 7);
true ->
HdrsLen + UserDataBitLen div 8
end.
%% 23.040 9.2.2.1 "SMS-DELIVER type"
encode_deliver(Params) ->
#{reply_path := RP,
status_report_ind := SRI,
loop_prevention := LP,
more_messages_to_send := MMS,
orig_addr := {OAType, OA},
pid := PID, dcs := DCS,
date_time := DateTime,
timezone := TimeZone,
user_data := {HdrList, UserData}} = Params,
%% TP-Originating-Address
OAEnc = encode_tp_addr(OAType, OA),
%% TP-Service-Centre-Time-Stamp
SCTS = encode_tp_scts(DateTime, TimeZone),
%% TP-User-Data and TP-User-Data-Header(s)
{HdrsLen, UDEnc} = encode_tp_ud(HdrList, UserData),
if HdrsLen > 0 ->
UDHI = 1;
true ->
UDHI = 0
end,
%% TP-User-Data-Length (depends on DCS)
UDLen = calc_tp_udl(DCS, HdrsLen, bit_size(UserData)),
<< RP:1, UDHI:1, SRI:1, 0:1, LP:1, MMS:1, ?TP_MTI_DELIVER:2,
OAEnc/bytes, PID, DCS, SCTS/bytes, UDLen, UDEnc/bytes >>.
encode(RPMsgType, {TPMsgType, Params}) ->
case {RPMsgType, TPMsgType} of
%% Mobile terminated message delivery
{sm_rp_mt_data, sm_tp_deliver} ->
%% MSC/SGSN -> MS: RP-DATA
encode_deliver(Params);
{sm_rp_mt_data, sm_tp_status_report} ->
%% MSC/SGSN -> MS: RP-DATA
%% encode_status_report(Params);
ok;
{sm_rp_mt_ack, sm_tp_deliver_report} ->
%% MS -> MSC/SGSN: RP-ACK
%% encode_deliver_report_ack(Params);
ok;
{sm_rp_mt_error, sm_tp_deliver_report} ->
%% MS -> MSC/SGSN: RP-ERROR
%% encode_deliver_report_error(Params);
ok;
_ ->
{error, unknown_msg}
end.

211
test/sm_tp_codec_test.erl Normal file
View File

@ -0,0 +1,211 @@
% SM-TP (Short Message Transport Protocol) codec unit tests.
%
% (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(sm_tp_codec_test).
-include_lib("eunit/include/eunit.hrl").
%% Rest octets following TP-Address field
-define(TEST_TP_DUMMY_REST, << 16#de, 16#ad, 16#be, 16#ef >>).
%% Alphanumeric address "MTC" (3 * 7 useful bits, 3 * 8 bits with padding)
-define(TEST_TP_ADDR_ANUM_T, {02#0000, 02#101}).
-define(TEST_TP_ADDR_ANUM_V, << 16#4d, 16#ea, 16#10 >>).
-define(TEST_TP_ADDR_ANUM_LV, {3 * 7, ?TEST_TP_ADDR_ANUM_V}).
-define(TEST_TP_ADDR_ANUM_TLV, ?TEST_TP_ADDR_ANUM_T, ?TEST_TP_ADDR_ANUM_LV).
-define(TEST_TP_ADDR_ANUM_ENC, << 16#06, 16#d0, ?TEST_TP_ADDR_ANUM_V/bytes >>).
-define(TEST_TP_ADDR_ANUM_LV_DEC, {3 * 8, ?TEST_TP_ADDR_ANUM_V}).
-define(TEST_TP_ADDR_ANUM_TLV_DEC, ?TEST_TP_ADDR_ANUM_T, ?TEST_TP_ADDR_ANUM_LV_DEC).
%% BCD-encoded odd address "+79137081000" (11 * 4 useful bits, 12 * 4 bits with padding)
-define(TEST_TP_ADDR_ONUM_T, {02#0001, 02#001}).
-define(TEST_TP_ADDR_ONUM_V, << 16#97, 16#31, 16#07, 16#18, 16#00, 16#f0 >>).
-define(TEST_TP_ADDR_ONUM_LV, {11 * 4, ?TEST_TP_ADDR_ONUM_V}).
-define(TEST_TP_ADDR_ONUM_TLV, ?TEST_TP_ADDR_ONUM_T, ?TEST_TP_ADDR_ONUM_LV).
-define(TEST_TP_ADDR_ONUM_ENC, << 16#0b, 16#91, ?TEST_TP_ADDR_ONUM_V/bytes >>).
%% BCD-encoded even address "123456" (6 * 4 useful bits, no padding)
-define(TEST_TP_ADDR_ENUM_T, {02#1000, 02#000}).
-define(TEST_TP_ADDR_ENUM_V, << 16#21, 16#43, 16#65 >>).
-define(TEST_TP_ADDR_ENUM_LV, {6 * 4, ?TEST_TP_ADDR_ENUM_V}).
-define(TEST_TP_ADDR_ENUM_TLV, ?TEST_TP_ADDR_ENUM_T, ?TEST_TP_ADDR_ENUM_LV).
-define(TEST_TP_ADDR_ENUM_ENC, << 16#06, 16#88, ?TEST_TP_ADDR_ENUM_V/bytes >>).
encode_tp_addr_test() ->
?assertEqual(?TEST_TP_ADDR_ANUM_ENC, sm_tp_codec:encode_tp_addr(?TEST_TP_ADDR_ANUM_TLV)),
?assertEqual(?TEST_TP_ADDR_ONUM_ENC, sm_tp_codec:encode_tp_addr(?TEST_TP_ADDR_ONUM_TLV)),
?assertEqual(?TEST_TP_ADDR_ENUM_ENC, sm_tp_codec:encode_tp_addr(?TEST_TP_ADDR_ENUM_TLV)).
decode_tp_addr_test() ->
%% Alphanumeric (GSM 7 bit encoding) address "MTC"
?assertEqual({ok, ?TEST_TP_ADDR_ANUM_TLV_DEC, << >>},
sm_tp_codec:decode_tp_addr(?TEST_TP_ADDR_ANUM_ENC)),
?assertEqual({ok, ?TEST_TP_ADDR_ANUM_TLV_DEC, ?TEST_TP_DUMMY_REST},
sm_tp_codec:decode_tp_addr(<< ?TEST_TP_ADDR_ANUM_ENC/bytes,
?TEST_TP_DUMMY_REST/bytes >>)),
%% BCD-encoded odd address "+79137081000"
?assertEqual({ok, ?TEST_TP_ADDR_ONUM_TLV, << >>},
sm_tp_codec:decode_tp_addr(?TEST_TP_ADDR_ONUM_ENC)),
?assertEqual({ok, ?TEST_TP_ADDR_ONUM_TLV, ?TEST_TP_DUMMY_REST},
sm_tp_codec:decode_tp_addr(<< ?TEST_TP_ADDR_ONUM_ENC/bytes,
?TEST_TP_DUMMY_REST/bytes >>)),
%% BCD-encoded even address "123456"
?assertEqual({ok, ?TEST_TP_ADDR_ENUM_TLV, << >>},
sm_tp_codec:decode_tp_addr(?TEST_TP_ADDR_ENUM_ENC)),
?assertEqual({ok, ?TEST_TP_ADDR_ENUM_TLV, ?TEST_TP_DUMMY_REST},
sm_tp_codec:decode_tp_addr(<< ?TEST_TP_ADDR_ENUM_ENC/bytes,
?TEST_TP_DUMMY_REST/bytes >>)).
-define(TEST_TP_SCTS_TIME0, {{00, 00, 00}, {00, 00, 00}}). % Intentionally incorrect
-define(TEST_TP_SCTS_TIME1, {{70, 04, 22}, {11, 10, 01}}). % Lenin's birthday!
-define(TEST_TP_SCTS_TIME2, {{69, 12, 01}, {22, 45, 33}}). % Just a random date
-define(TEST_TP_SCTS_TIME0_ENC, << 16#00, 16#00, 16#00, 16#00, 16#00, 16#00 >>).
-define(TEST_TP_SCTS_TIME1_ENC, << 16#07, 16#40, 16#22, 16#11, 16#01, 16#10 >>).
-define(TEST_TP_SCTS_TIME2_ENC, << 16#96, 16#21, 16#10, 16#22, 16#54, 16#33 >>).
-define(TEST_TP_SCTS_TZ_00_ENC, 16#00). % GMT+0
-define(TEST_TP_SCTS_TZ_40_ENC, 16#61). % GMT+4
-define(TEST_TP_SCTS_TZ_F715_ENC, 16#9a). % GMT-7,15
-define(TEST_TP_SCTS_TZ_F30_ENC, 16#29). % GMT-3
-define(TEST_TP_SCTS_TZ_1230_ENC, 16#05). % GMT+12,30
encode_tp_scts_test() ->
?assertEqual(<< ?TEST_TP_SCTS_TIME0_ENC:6/bytes, ?TEST_TP_SCTS_TZ_00_ENC >>,
sm_tp_codec:encode_tp_scts(?TEST_TP_SCTS_TIME0, {0, 0})),
?assertEqual(<< ?TEST_TP_SCTS_TIME1_ENC:6/bytes, ?TEST_TP_SCTS_TZ_40_ENC >>,
sm_tp_codec:encode_tp_scts(?TEST_TP_SCTS_TIME1, {4, 0})),
?assertEqual(<< ?TEST_TP_SCTS_TIME2_ENC:6/bytes, ?TEST_TP_SCTS_TZ_F715_ENC >>,
sm_tp_codec:encode_tp_scts(?TEST_TP_SCTS_TIME2, {-7, 15})),
?assertEqual(<< ?TEST_TP_SCTS_TIME1_ENC:6/bytes, ?TEST_TP_SCTS_TZ_F30_ENC >>,
sm_tp_codec:encode_tp_scts(?TEST_TP_SCTS_TIME1, {-3, 0})),
?assertEqual(<< ?TEST_TP_SCTS_TIME2_ENC:6/bytes, ?TEST_TP_SCTS_TZ_1230_ENC >>,
sm_tp_codec:encode_tp_scts(?TEST_TP_SCTS_TIME2, {12, 30})),
?assertError(_, % TODO: {error, function_clause, ...} due to YY > 99 and HH > 99
sm_tp_codec:encode_tp_scts({{1999, 01, 01}, {120, 00, 00}}, {0, 0})),
?assertError(_, % TODO: {error, function_clause, ...} due to HH < 0
sm_tp_codec:encode_tp_scts({{89, 02, 04}, {-5, 00, 00}}, {7, 0})),
?assertError(_, % TODO: {error, function_clause, ...} due to (TZMin rem 15) =/= 0
sm_tp_codec:encode_tp_scts(?TEST_TP_SCTS_TIME1, {5, 5})).
decode_tp_scts_test() ->
?assertEqual({ok, ?TEST_TP_SCTS_TIME0, {0, 0}},
sm_tp_codec:decode_tp_scts(<< ?TEST_TP_SCTS_TIME0_ENC:6/bytes,
?TEST_TP_SCTS_TZ_00_ENC >>)),
?assertEqual({ok, ?TEST_TP_SCTS_TIME1, {4, 0}},
sm_tp_codec:decode_tp_scts(<< ?TEST_TP_SCTS_TIME1_ENC:6/bytes,
?TEST_TP_SCTS_TZ_40_ENC >>)),
?assertEqual({ok, ?TEST_TP_SCTS_TIME2, {-7, 15}},
sm_tp_codec:decode_tp_scts(<< ?TEST_TP_SCTS_TIME2_ENC:6/bytes,
?TEST_TP_SCTS_TZ_F715_ENC >>)),
?assertEqual({ok, ?TEST_TP_SCTS_TIME1, {-3, 0}},
sm_tp_codec:decode_tp_scts(<< ?TEST_TP_SCTS_TIME1_ENC:6/bytes,
?TEST_TP_SCTS_TZ_F30_ENC >>)),
?assertEqual({ok, ?TEST_TP_SCTS_TIME2, {12, 30}},
sm_tp_codec:decode_tp_scts(<< ?TEST_TP_SCTS_TIME2_ENC:6/bytes,
?TEST_TP_SCTS_TZ_1230_ENC >>)).
%% TP-Validity-Period is absent.
-define(TEST_TP_VP_OMIT, 02#00, ?TEST_TP_DUMMY_REST).
%% 9.2.3.12.1 TP-Validity-Period (Relative format).
-define(TEST_TP_VP_RELATIVE0, 02#10, << 16#00, ?TEST_TP_DUMMY_REST/bytes >>). % 5 minutes
-define(TEST_TP_VP_RELATIVE1, 02#10, << 16#8f, ?TEST_TP_DUMMY_REST/bytes >>). % 12 hours
-define(TEST_TP_VP_RELATIVE2, 02#10, << 16#a7, ?TEST_TP_DUMMY_REST/bytes >>). % 24 hours
-define(TEST_TP_VP_RELATIVE3, 02#10, << 16#a8, ?TEST_TP_DUMMY_REST/bytes >>). % 2 days
-define(TEST_TP_VP_RELATIVE4, 02#10, << 16#ff, ?TEST_TP_DUMMY_REST/bytes >>). % 63 weeks
%% 9.2.3.12.2 TP-Validity-Period (Absolute format).
-define(TEST_TP_VP_ABSOLUTE1, 02#11, << ?TEST_TP_SCTS_TIME1_ENC:6/bytes,
?TEST_TP_SCTS_TZ_40_ENC >>).
-define(TEST_TP_VP_ABSOLUTE2, 02#11, << ?TEST_TP_SCTS_TIME2_ENC:6/bytes,
?TEST_TP_SCTS_TZ_F30_ENC >>).
%% 9.2.3.12.3 TP-Validity-Period (Enhanced format).
-define(TEST_TP_VP_ENHANCED0, 02#01, << 16#00, 16#00, 16#00, 16#00, 16#00, 16#00, 16#00,
?TEST_TP_DUMMY_REST/bytes >>). % not present
-define(TEST_TP_VP_ENHANCED1, 02#01, << 16#41, 16#01, 16#00, 16#00, 16#00, 16#00, 16#00,
?TEST_TP_DUMMY_REST/bytes >>). % relative, 10 minutes
-define(TEST_TP_VP_ENHANCED2, 02#01, << 16#42, 16#1e, 16#00, 16#00, 16#00, 16#00, 16#00,
?TEST_TP_DUMMY_REST/bytes >>). % relative, 30 seconds
-define(TEST_TP_VP_ENHANCED3, 02#01, << 16#03, 16#00, 16#22, 16#71, 16#00, 16#00, 16#00,
?TEST_TP_DUMMY_REST/bytes >>). % semi-octet, 00:22:17
-define(TEST_TP_VP_ENHANCED4, 02#01, << 16#47, 16#00, 16#00, 16#00, 16#00, 16#00, 16#00,
?TEST_TP_DUMMY_REST/bytes >>). % reserved EVPF
-define(TEST_TP_VP_ENHANCED5, 02#01, << 16#80, 16#00, 16#00, 16#00, 16#00, 16#00, 16#00,
?TEST_TP_DUMMY_REST/bytes >>). % extension bit=1
-define(TEST_TP_VPF_UNKNOWN, 16#ff, << ?TEST_TP_DUMMY_REST/bytes >>).
decode_tp_vp_test() ->
?assertEqual({ok, omit, << >>},
sm_tp_codec:decode_tp_vp(02#00, << >>)),
?assertEqual({ok, omit, ?TEST_TP_DUMMY_REST},
sm_tp_codec:decode_tp_vp(?TEST_TP_VP_OMIT)),
?assertEqual({ok, {relative, 5 * 60}, ?TEST_TP_DUMMY_REST},
sm_tp_codec:decode_tp_vp(?TEST_TP_VP_RELATIVE0)),
?assertEqual({ok, {relative, 12 * 3600}, ?TEST_TP_DUMMY_REST},
sm_tp_codec:decode_tp_vp(?TEST_TP_VP_RELATIVE1)),
?assertEqual({ok, {relative, 24 * 3600}, ?TEST_TP_DUMMY_REST},
sm_tp_codec:decode_tp_vp(?TEST_TP_VP_RELATIVE2)),
?assertEqual({ok, {relative, 2 * 24 * 3600}, ?TEST_TP_DUMMY_REST},
sm_tp_codec:decode_tp_vp(?TEST_TP_VP_RELATIVE3)),
?assertEqual({ok, {relative, 63 * 7 * 24 * 3600}, ?TEST_TP_DUMMY_REST},
sm_tp_codec:decode_tp_vp(?TEST_TP_VP_RELATIVE4)),
?assertEqual({ok, {absolute, ?TEST_TP_SCTS_TIME1, {4, 0}}, << >>},
sm_tp_codec:decode_tp_vp(?TEST_TP_VP_ABSOLUTE1)),
?assertEqual({ok, {absolute, ?TEST_TP_SCTS_TIME2, {-3, 0}}, << >>},
sm_tp_codec:decode_tp_vp(?TEST_TP_VP_ABSOLUTE2)),
?assertEqual({ok, {enhanced, 0, omit}, ?TEST_TP_DUMMY_REST},
sm_tp_codec:decode_tp_vp(?TEST_TP_VP_ENHANCED0)),
?assertEqual({ok, {enhanced, 1, {relative, 600}}, ?TEST_TP_DUMMY_REST},
sm_tp_codec:decode_tp_vp(?TEST_TP_VP_ENHANCED1)),
?assertEqual({ok, {enhanced, 1, {relative, 30}}, ?TEST_TP_DUMMY_REST},
sm_tp_codec:decode_tp_vp(?TEST_TP_VP_ENHANCED2)),
?assertEqual({ok, {enhanced, 0, {relative, 1337}}, ?TEST_TP_DUMMY_REST},
sm_tp_codec:decode_tp_vp(?TEST_TP_VP_ENHANCED3)),
?assertEqual({ok, {enhanced, 1, reserved}, ?TEST_TP_DUMMY_REST},
sm_tp_codec:decode_tp_vp(?TEST_TP_VP_ENHANCED4)),
?assertError({vpf_ext_not_supported}, % extension bit=1 not supported
sm_tp_codec:decode_tp_vp(?TEST_TP_VP_ENHANCED5)),
?assertError({unknown_vpf, 16#ff}, % unknown TP-Validity-Period-Format
sm_tp_codec:decode_tp_vp(?TEST_TP_VPF_UNKNOWN)).