blob: 7396b1c1781b037b2fb12fa3520f3f483ff85d00 [file] [log] [blame]
Harald Weltec60e8402011-03-08 23:02:32 +01001-module(map_codec_tests).
2-author('Harald Welte <laforge@gnumonks.org>').
3
4-include_lib("eunit/include/eunit.hrl").
5
6-include("map.hrl").
7-include_lib("osmo_ss7/include/isup.hrl").
Harald Welte49525f82011-03-11 18:47:23 +01008-include_lib("osmo_ss7/include/m2ua.hrl").
9-include_lib("osmo_ss7/include/mtp3.hrl").
10-include_lib("osmo_ss7/include/sccp.hrl").
Harald Weltec60e8402011-03-08 23:02:32 +010011
Harald Welte3575d442011-03-12 10:23:10 +010012% modified version of assertEqual()
13-define(assertEqualArgs(Expect, Expr, Args),
14 ((fun (__X) ->
15 case (Expr) of
16 __X -> ok;
17 __V -> ?debugFmt("Expected: ~w~nValue: ~w~n", [__X, __V]),
18 .erlang:error({assertEqual_failed,
19 [{module, ?MODULE},
20 {line, ?LINE},
21 {expression, (??Expr)},
22 {expected, __X},
23 {value, __V}] ++ Args})
24 end
25 end)(Expect))).
26-define(_assertEqualArgs(Expect, Expr, Args), ?_test(?assertEqual(Expect, Expr, Args))).
27
Harald Weltec60e8402011-03-08 23:02:32 +010028-define(TCAP_MSG_BIN, <<100,65,73,4,81,1,2,200,107,42,40,40,6,7,0,17,134,5,1,1,1,160,29,97,27,128,2,7,128,161,9,6,7,4,0,0,1,0,1,3,162,3,2,1,0,163,5,161,3,2,1,0,108,13,163,11,2,1,64,2,1,8,48,3,10,1,0>>).
29-define(TCAP_MSG_DEC, {'end',{'MapSpecificPDUs_end',[81,1,2,200],{'EXTERNAL',{syntax,{0,0,17,773,1,1,1}},asn1_NOVALUE,[97,27,128,2,7,128,161,9,6,7,4,0,0,1,0,1,3,162,3,2,1,0,163,5,161,3,2,1,0]},[{basicROS,{returnError,{'MapSpecificPDUs_end_components_SEQOF_basicROS_returnError',{present,64},{local,8},{'RoamingNotAllowedParam',plmnRoamingNotAllowed,asn1_NOVALUE}}}}]}}).
30
31parse_test() ->
32 ?assertEqual(?TCAP_MSG_DEC, map_codec:parse_tcap_msg(?TCAP_MSG_BIN)).
Harald Welte49525f82011-03-11 18:47:23 +010033% BER allows for different binary encodings of each message, the test below is not valid
34%encode_test() ->
35% ?assertEqual(?TCAP_MSG_BIN, map_codec:encode_tcap_msg(?TCAP_MSG_DEC)).
Harald Weltec60e8402011-03-08 23:02:32 +010036
37-define(ADDR_DEC, #party_number{nature_of_addr_ind = ?ISUP_ADDR_NAT_INTERNATIONAL,
38 internal_net_num = undefined,
39 number_incompl_ind = undefined,
40 numbering_plan = 0,
41 present_restrict = undefined,
42 screening_ind = undefined,
43 phone_number = [1,2,3,4,5,6,7,8,9,0]}).
44-define(ADDR_LIST, [144,33,67,101,135,9]).
45
46encode_addr_list_test() ->
47 ?assertEqual(?ADDR_LIST, map_codec:encode_addr_string(?ADDR_DEC)).
48encode_addr_int_test() ->
49 AddrDec = ?ADDR_DEC,
50 ?assertEqual(?ADDR_LIST, map_codec:encode_addr_string(AddrDec#party_number{phone_number=1234567890})).
51decode_addr_list_test() ->
52 ?assertEqual(?ADDR_DEC, map_codec:parse_addr_string(?ADDR_LIST)).
53decode_addr_bin_test() ->
54 ?assertEqual(?ADDR_DEC, map_codec:parse_addr_string(list_to_binary(?ADDR_LIST))).
Harald Welte49525f82011-03-11 18:47:23 +010055
56
57pcap_parse_test_() ->
58 { timeout, 5*60, [ fun pcap_parse_t/0 ] }.
59
60% parser test for real-world MAP/TCAP data
61pcap_parse_t() ->
62 Args = [{rewrite_fn, fun pcap_cb/5}],
63 File = "../priv/map.pcap",
64 case file:read_file_info(File) of
65 {ok, _Info} ->
66 {ok, NrPkts} = ?debugTime("PCAP", osmo_ss7_pcap:pcap_apply(File, "", Args)),
67 ?debugFmt("Parsed ~p PCAP packets~n", [NrPkts]);
68 {error, _Reason} ->
69 ?debugFmt("Skipping PCAP based tests as no ~p could be found~n",
70 [File])
71 end.
72
Harald Welte3575d442011-03-12 10:23:10 +010073pcap_cb(sctp, _From, Path, 2, DataBin) ->
Harald Welte49525f82011-03-11 18:47:23 +010074 {ok, M2ua} = m2ua_codec:parse_m2ua_msg(DataBin),
Harald Welte3575d442011-03-12 10:23:10 +010075 M2uaReenc = m2ua_codec:encode_m2ua_msg(M2ua),
76 ?assertEqualArgs(DataBin, M2uaReenc, [{layer, m2ua}, {path, Path}]),
77 handle_m2ua(M2ua, Path),
78 DataBin.
Harald Welte49525f82011-03-11 18:47:23 +010079
Harald Welte3575d442011-03-12 10:23:10 +010080handle_m2ua(M2ua = #m2ua_msg{msg_class = ?M2UA_MSGC_MAUP,
81 msg_type = ?M2UA_MAUP_MSGT_DATA,
82 parameters = Params}, Path) ->
Harald Welte49525f82011-03-11 18:47:23 +010083 {_Len, M2uaPayload} = proplists:get_value(16#300, Params),
84 Mtp3 = mtp3_codec:parse_mtp3_msg(M2uaPayload),
Harald Welte3575d442011-03-12 10:23:10 +010085 Mtp3Reenc = mtp3_codec:encode_mtp3_msg(Mtp3),
86 ?assertEqualArgs(M2uaPayload, Mtp3Reenc, [{layer, mtp3}, {path, Path}]),
87 handle_mtp3(Mtp3, Path ++ [M2ua]);
88handle_m2ua(M2ua = #m2ua_msg{}, _Path) ->
Harald Welte49525f82011-03-11 18:47:23 +010089 M2ua.
90
Harald Welte3575d442011-03-12 10:23:10 +010091handle_mtp3(Mtp3 = #mtp3_msg{service_ind = ?MTP3_SERV_SCCP,
92 payload = Payload}, Path) ->
Harald Welte49525f82011-03-11 18:47:23 +010093 {ok, SccpDec} = sccp_codec:parse_sccp_msg(Payload),
Harald Welte3575d442011-03-12 10:23:10 +010094 SccpReenc = sccp_codec:encode_sccp_msg(SccpDec),
95 % We cannot assume that the data is equal due to SCCP allowing
96 % different encodings of the same data. instead we re-decode
97 {ok, SccpReencDec} = sccp_codec:parse_sccp_msg(SccpReenc),
98 ?assertEqualArgs(SccpDec, SccpReencDec, [{layer, sccp}, {path, Path}]),
99 handle_sccp(SccpDec, Path ++ [Mtp3]);
100handle_mtp3(Mtp3 = #mtp3_msg{}, _Path) ->
Harald Welte49525f82011-03-11 18:47:23 +0100101 Mtp3.
102
Harald Welte3575d442011-03-12 10:23:10 +0100103handle_sccp(S = #sccp_msg{msg_type = ?SCCP_MSGT_UDT, parameters = Params}, Path) ->
Harald Welte49525f82011-03-11 18:47:23 +0100104 UserData = proplists:get_value(user_data, Params),
Harald Welte3575d442011-03-12 10:23:10 +0100105 PathOut = Path ++ [S],
106 case map_codec:parse_tcap_msg(UserData) of
107 {error, Error} ->
108 ErrTuple = {Error, erlang:get_stacktrace(), []},
109 ?debugFmt("Path: ~p~nMAP Decode Error: ~w~n", [PathOut, ErrTuple]),
110 erlang:error(ErrTuple);
111 MapDec ->
112 case map_codec:encode_tcap_msg(MapDec) of
113 {error, Error} ->
114 ErrTuple = {Error, erlang:get_stacktrace(), [{map_dec, MapDec}]},
115 ?debugFmt("Path: ~p~nMAP Encode Error: ~w~n", [PathOut, ErrTuple]),
116 erlang:error(ErrTuple);
117 MapReenc ->
118 MapReencDec = map_codec:parse_tcap_msg(MapReenc),
119 ?assertEqualArgs(MapDec, MapReencDec, [{layer, map}, {path, Path}])
120 end
121 end,
Harald Welte49525f82011-03-11 18:47:23 +0100122 S;
Harald Welte3575d442011-03-12 10:23:10 +0100123handle_sccp(S = #sccp_msg{}, _Path) ->
Harald Welte49525f82011-03-11 18:47:23 +0100124 S.