From 26bdef27ddc68be80e838e25a3b6f764719e8f87 Mon Sep 17 00:00:00 2001 From: Harald Welte Date: Mon, 16 Jan 2012 22:22:17 +0100 Subject: Commit current state of working MTP3-in-M2PA The current implementation can successfully establish M2PA with Cisco ITP. --- ebin/osmo_ss7.app | 8 +- include/sua.hrl | 117 ++++++++++++++++++++++++ src/mtp3_hmdt.erl | 102 +++++++++++++++++++++ src/mtp3_sltc.erl | 22 ++--- src/sctp_core.erl | 268 ++++++++++++++++++++++++++++++++++++++++++++++++++++++ src/sctp_m2pa.erl | 198 ++++++++++++++++++++++++++++++++++++++++ src/sua_codec.erl | 89 ++++++++++++++++++ 7 files changed, 791 insertions(+), 13 deletions(-) create mode 100644 include/sua.hrl create mode 100644 src/mtp3_hmdt.erl create mode 100644 src/sctp_core.erl create mode 100644 src/sctp_m2pa.erl create mode 100644 src/sua_codec.erl diff --git a/ebin/osmo_ss7.app b/ebin/osmo_ss7.app index ee031f7..03075fb 100644 --- a/ebin/osmo_ss7.app +++ b/ebin/osmo_ss7.app @@ -2,12 +2,16 @@ [{description, "Osmocom SS7 code"}, {vsn, "1"}, {modules, [ osmo_util, exprecs, - ipa_proto, + ipa_proto, + sctp_core, bssmap_codec, isup_codec, + mtp2_lsc, mtp2_iac, m2ua_codec, + m2pa_codec, sctp_m2pa, m3ua_codec, m3ua_core, m3ua_example, - mtp3_codec, + mtp3_codec, mtp3_hmdt, mtp3_sltc, + sua_codec, sccp_codec, osmo_ss7_sup, osmo_ss7_app, ss7_links, ss7_link_m3ua, ss7_link_ipa_client, diff --git a/include/sua.hrl b/include/sua.hrl new file mode 100644 index 0000000..c9383e7 --- /dev/null +++ b/include/sua.hrl @@ -0,0 +1,117 @@ +% RFC 3868 SUA SCCP User Adaption + +% (C) 2012 by Harald Welte +% +% 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 . + +% 3.1.2 Message Classes +-define(SUA_MSGC_MGMT, 0). +-define(SUA_MSGC_SNM, 2). +-define(SUA_MSGC_ASPSM, 3). +-define(SUA_MSGC_ASPTM, 4). +-define(SUA_MSGC_CL, 7). +-define(SUA_MSGC_CO, 8). +-define(SUA_MSGC_RKM, 9). + +% 3.1.3 Message Types +-define(SUA_MGMT_ERR, 0). +-define(SUA_MGMT_NTFY, 1). + +-define(SUA_SNM_DUNA, 1). +-define(SUA_SNM_DAVA, 2). +-define(SUA_SNM_DAUD, 3). +-define(SUA_SNM_SCON, 4). +-define(SUA_SNM_DUPU, 5). +-define(SUA_SNM_DRST, 6). + +-define(SUA_ASPSM_UP, 1). +-define(SUA_ASPSM_DOWN, 2). +-define(SUA_ASPSM_BEAT, 3). +-define(SUA_ASPSM_UP_ACK, 4). +-define(SUA_ASPSM_DOWN_ACK, 5). +-define(SUA_ASPSM_BEAT_ACK, 6). + +-define(SUA_ASPTM_ACTIVE, 1). +-define(SUA_ASPTM_INACTIVE, 2). +-define(SUA_ASPTM_ACTIVE_ACK, 3). +-define(SUA_ASPTM_INACTIVE_ACK, 4). + +-define(SUA_RKM_REG_REQ, 1). +-define(SUA_RKM_REG_RSP, 2). +-define(SUA_RKM_DEREG_REQ, 3). +-define(SUA_RKM_DEREG_RSP, 4). + +-define(SUA_CL_CLDT, 1). +-define(SUA_CL_CLDR, 2). + +-define(SUA_CO_CORE, 1). +-define(SUA_CO_COAK, 2). +-define(SUA_CO_COREF, 3). +-define(SUA_CO_RELRE, 4). +-define(SUA_CO_RELCO, 5). +-define(SUA_CO_RESCO, 6). +-define(SUA_CO_RESRE, 7). +-define(SUA_CO_CODT, 8). +-define(SUA_CO_CODA, 9). +-define(SUA_CO_COERR, 10). +-define(SUA_CO_COIT, 11). + +-define(SUA_IEI_ROUTE_CTX, 16#0006). +-define(SUA_IEI_CORR_ID, 16#0013). +-define(SUA_IEI_REG_RESULT, 16#0014). +-define(SUA_IEI_DEREG_RESULT, 16#0015). + +% 3.10 SUA specific parameters + +-define(SUA_IEI_S7_HOP_CTR, 16#0101). +-define(SUA_IEI_SRC_ADDR, 16#0102). +-define(SUA_IEI_DEST_ADDRA, 16#0103). +-define(SUA_IEI_SRC_REF, 16#0104). +-define(SUA_IEI_DEST_REF, 16#0105). +-define(SUA_IEI_CAUSE, 16#0106). +-define(SUA_IEI_SEQ_NR, 16#0107). +-define(SUA_IEI_RX_SEQ_NR, 16#0108). +-define(SUA_IEI_ASP_CAPA, 16#0109). +-define(SUA_IEI_CREDIT, 16#010A). +-define(SUA_IEI_DATA, 16#010B). +-define(SUA_IEI_USER_CAUSE, 16#010C). +-define(SUA_IEI_NET_APPEARANCE, 16#010D). +-define(SUA_IEI_ROUTING_KEY, 16#010E). +-define(SUA_IEI_DRN, 16#010F). +-define(SUA_IEI_TID, 16#0110). +-define(SUA_IEI_SMI, 16#0112). +-define(SUA_IEI_IMPORTANCE, 16#0113). +-define(SUA_IEI_MSG_PRIO, 16#0114). +-define(SUA_IEI_PROTO_CLASS, 16#0115). +-define(SUA_IEI_SEQ_CTRL, 16#0116). +-define(SUA_IEI_SEGMENTATION, 16#0117). +-define(SUA_IEI_CONG_LEVEL, 16#0118). + +-define(SUA_IEI_GT, 16#8001). +-define(SUA_IEI_PC, 16#8002). +-define(SUA_IEI_SSN, 16#8003). +-define(SUA_IEI_IPv4, 16#8004). +-define(SUA_IEI_HOST, 16#8005). +-define(SUA_IEI_IPv6, 16#8006). + +-record(sua_msg, { + version :: 0..255, + msg_class :: 0..255, + msg_type :: 0..255, + msg_length :: non_neg_integer(), + payload + }). + diff --git a/src/mtp3_hmdt.erl b/src/mtp3_hmdt.erl new file mode 100644 index 0000000..ebac4ba --- /dev/null +++ b/src/mtp3_hmdt.erl @@ -0,0 +1,102 @@ +% MTP3 Message handling; message distribution (HMDT) according to Q.704 + +% (C) 2011-2012 by Harald Welte +% +% 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 . + +-module(mtp3_hmdt). +-author('Harald Welte '). +-behaviour(gen_fsm). + +-include("mtp3.hrl"). + +% gen_fsm exports +-export([init/1, terminate/3, code_change/4, handle_event/3, handle_info/3]). + +% individual FSM states +-export([idle/2, own_sp_restart/2]). + +-record(hmdt_state, { + sltc_pid + }). + +%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% +% gen_fsm callbacks +%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% + +init([Sltc]) when is_pid(Sltc) -> + HmdtState = #hmdt_state{sltc_pid = Sltc}, + {ok, idle, HmdtState}. + +terminate(Reason, State, _LoopDat) -> + io:format("Terminating ~p in State ~p (Reason: ~p)~n", + [?MODULE, State, Reason]), + ok. + +code_change(_OldVsn, StateName, LoopDat, _Extra) -> + {ok, StateName, LoopDat}. + +handle_event(Event, State, LoopDat) -> + io:format("Unknown Event ~p in state ~p~n", [Event, State]), + {next_state, State, LoopDat}. + +handle_info(Info, State, LoopDat) -> + io:format("Unknown Info ~p in state ~p~n", [Info, State]), + {next_state, State, LoopDat}. + +% See Figure 2 of Q.707 + +%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% +% STATE: idle +%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% + +idle(M=#mtp3_msg{service_ind=Sio}, LoopDat) -> + handle_mtp3(Sio, M, LoopDat), + {next_state, idle, LoopDat}; + +idle(restart_begins, LoopDat) -> + {next_state, own_sp_restart, LoopDat}. + +%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% +% STATE: own_sp_restart +%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% + +own_sp_restart(M=#mtp3_msg{service_ind=Sio}, LoopDat) when + Sio == ?MTP3_SERV_MGMT; Sio == ?MTP3_SERV_MTN -> + handle_mtp3(Sio, M, LoopDat), + {next_state, own_sp_restart, LoopDat}; + +own_sp_restart(restart_ends, LoopDat) -> + {next_state, idle, LoopDat}. + + +%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% +% helper functions +%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% + +handle_mtp3(?MTP3_SERV_MTN, Mtp3, LoopDat) -> + io:format("SIO ~p HMDT -> SLTC~n", [?MTP3_SERV_MTN]), + gen_fsm:send_event(LoopDat#hmdt_state.sltc_pid, Mtp3); +handle_mtp3(?MTP3_SERV_MGMT, Mtp3, LoopDat) -> + io:format("SIO ~p HMDT -> NULL~n", [?MTP3_SERV_MGMT]), + % FIXME: distinguish between SRM, SLM and STM + ok; +handle_mtp3(Sio, Mtp3, LoopDat) -> + io:format("SIO ~p HMDT -> ss7_links~n", [Sio]), + % deliver to subsystem + ss7_links:mtp3_rx(Mtp3), + % FIXME: Send UPU! ? + ok. diff --git a/src/mtp3_sltc.erl b/src/mtp3_sltc.erl index 2f52301..d440be0 100644 --- a/src/mtp3_sltc.erl +++ b/src/mtp3_sltc.erl @@ -82,7 +82,7 @@ handle_info(Info, State, LoopDat) -> % STATE: idle %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% -idle(M=#mtp3_msg{service_ind = ?MTP3_SERV_MGMT, +idle(M=#mtp3_msg{service_ind = ?MTP3_SERV_MTN, payload = #mtp3mg_msg{h0 = ?MTP3MG_H0_TEST, h1 = ?MTP3MG_H1_SLTM}}, LoopDat) -> Slta = slta_from_sltm(M), @@ -101,14 +101,14 @@ idle(start, LoopDat) -> % STATE: first_attempt %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% -first_attempt(M=#mtp3_msg{service_ind = ?MTP3_SERV_MGMT, +first_attempt(M=#mtp3_msg{service_ind = ?MTP3_SERV_MTN, payload = #mtp3mg_msg{h0 = ?MTP3MG_H0_TEST, h1 = ?MTP3MG_H1_SLTM}}, LoopDat) -> Slta = slta_from_sltm(M), send_to(hmrt, Slta, LoopDat), {next_state, first_attempt, LoopDat}; -first_attempt(M = #mtp3_msg{service_ind = ?MTP3_SERV_MGMT, +first_attempt(M = #mtp3_msg{service_ind = ?MTP3_SERV_MTN, payload = #mtp3mg_msg{h0 = ?MTP3MG_H0_TEST, h1 = ?MTP3MG_H1_SLTA}}, LoopDat) -> timer:cancel(LoopDat#sltc_state.t1), @@ -129,14 +129,14 @@ first_attempt(M = #mtp3_msg{service_ind = ?MTP3_SERV_MGMT, % STATE: second_attempt %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% -second_attempt(M=#mtp3_msg{service_ind = ?MTP3_SERV_MGMT, +second_attempt(M=#mtp3_msg{service_ind = ?MTP3_SERV_MTN, payload = #mtp3mg_msg{h0 = ?MTP3MG_H0_TEST, h1 = ?MTP3MG_H1_SLTM}}, LoopDat) -> Slta = slta_from_sltm(M), send_to(hmrt, Slta, LoopDat), {next_state, second_attempt, LoopDat}; -second_attempt(M = #mtp3_msg{service_ind = ?MTP3_SERV_MGMT, +second_attempt(M = #mtp3_msg{service_ind = ?MTP3_SERV_MTN, payload = #mtp3mg_msg{h0 = ?MTP3MG_H0_TEST, h1 = ?MTP3MG_H1_SLTA}}, LoopDat) -> timer:cancel(LoopDat#sltc_state.t1), @@ -165,26 +165,26 @@ send_to(mgmt, What, #sltc_state{mgmt_pid = Txc}) -> send_to(lsac, What, #sltc_state{lsac_pid = Txc}) -> Txc ! {sltc_lsac, What}. -slta_from_sltm(M = #mtp3_msg{service_ind = ?MTP3_SERV_MGMT, +slta_from_sltm(M = #mtp3_msg{service_ind = ?MTP3_SERV_MTN, routing_label = RoutLbl, payload = #mtp3mg_msg{h0 = ?MTP3MG_H0_TEST, h1 = ?MTP3MG_H1_SLTM, - test_pattern = TP}}) -> + payload = TP}}) -> InvRoutLbl = invert_rout_lbl(RoutLbl), M#mtp3_msg{routing_label = InvRoutLbl, payload = #mtp3mg_msg{h0 = ?MTP3MG_H0_TEST, h1 = ?MTP3MG_H1_SLTA, - test_pattern = TP}}. + payload = TP}}. generate_sltm(LoopDat) -> Mg = #mtp3mg_msg{h0 = ?MTP3MG_H0_TEST, h1 = ?MTP3MG_H1_SLTM, - test_pattern = LoopDat#sltc_state.x}, + payload = LoopDat#sltc_state.x}, Lbl = #mtp3_routing_label{sig_link_sel = LoopDat#sltc_state.sls, origin_pc = LoopDat#sltc_state.opc, dest_pc = LoopDat#sltc_state.adj_dpc}, #mtp3_msg{network_ind = ?MTP3_NETIND_INTERNATIONAL, - service_ind = ?MTP3_SERV_MGMT, + service_ind = ?MTP3_SERV_MTN, routing_label = Lbl, payload = Mg}. rout_lbl_matches(#mtp3_routing_label{sig_link_sel = SlsLocal, @@ -197,7 +197,7 @@ rout_lbl_matches(#mtp3_routing_label{sig_link_sel = SlsLocal, end. slt_matches(#mtp3_msg{routing_label = RoutLbl, - payload = #mtp3mg_msg{test_pattern = TP}}, LoopDat) -> + payload = #mtp3mg_msg{payload = TP}}, LoopDat) -> case LoopDat#sltc_state.x of TP -> rout_lbl_matches(RoutLbl, LoopDat); diff --git a/src/sctp_core.erl b/src/sctp_core.erl new file mode 100644 index 0000000..f3a2bb9 --- /dev/null +++ b/src/sctp_core.erl @@ -0,0 +1,268 @@ +% SCTP wrapper behavior, used by M2PA/M2UA/M3UA/SUA + +% (C) 2011-2012 by Harald Welte +% +% 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 . + +-module(sctp_core). +-author('Harald Welte '). +-behaviour(gen_fsm). + +-include_lib("kernel/include/inet_sctp.hrl"). +-include("osmo_util.hrl"). + +-export([start_link/1]). + +-export([init/1, terminate/3, code_change/4, handle_event/3, handle_info/3]). + +-export([behaviour_info/1]). + +% FSM states: +-export([idle/2, associating/2, established/2]). + +behaviour_info(callbacks) -> + gen_fsm:behaviour_info(callbacks) ++ [{rx_sctp, 4}, {mtp_xfer, 2}, {state_change, 2}]; +behaviour_info(Other) -> + gen_fsm:behaviour_info(Other). + +% Loop Data +-record(sctp_state, { + role, % passive | active + state, % idle | associating | established + user_pid, + sctp_remote_ip, + sctp_remote_port, + sctp_local_port, + sctp_sock, + sctp_assoc_id, + module, % callback module + ext_state % state of the callback module + }). + +start_link(InitOpts) -> + gen_fsm:start_link(?MODULE, InitOpts, [{debug, [trace]}]). + +reconnect_sctp(L = #sctp_state{sctp_remote_ip = Ip, sctp_remote_port = Port, sctp_sock = Sock}) -> + io:format("SCTP Reconnect ~p:~p~n", [Ip, Port]), + timer:sleep(1*1000), + InitMsg = #sctp_initmsg{num_ostreams = 2, max_instreams = 2}, + case gen_sctp:connect_init(Sock, Ip, Port, [{active, once}, {reuseaddr, true}, + {sctp_initmsg, InitMsg}]) of + ok -> + ok; + {error, Error } -> + io:format("SCTP Error ~p, reconnecting~n", [Error]), + reconnect_sctp(L) + end. + +init(InitOpts) -> + OpenOptsBase = [{active, once}, {reuseaddr, true}], + Module = proplists:get_value(module, InitOpts), + ModuleArgs = proplists:get_value(module_args, InitOpts), + LocalPort = proplists:get_value(sctp_local_port, InitOpts), + Role = proplists:get_value(sctp_role, InitOpts), + case LocalPort of + undefined -> + OpenOpts = OpenOptsBase; + _ -> + OpenOpts = OpenOptsBase ++ [{port, LocalPort}] + end, + {ok, SctpSock} = gen_sctp:open(OpenOpts), + case Module:init(ModuleArgs) of + {ok, ExtState} -> + LoopDat = #sctp_state{role = Role, sctp_sock = SctpSock, + user_pid = proplists:get_value(user_pid, InitOpts), + ext_state = ExtState, module = Module, + sctp_remote_ip = proplists:get_value(sctp_remote_ip, InitOpts), + sctp_remote_port = proplists:get_value(sctp_remote_port, InitOpts), + sctp_local_port = LocalPort}, + case Role of + active -> + gen_fsm:send_event(self(), osmo_util:make_prim('M','SCTP_ESTABLISH',request)); + _ -> + ok + end, + {ok, idle, LoopDat}; + Default -> + {error, {module_returned, Default}} + end. + +terminate(Reason, State, LoopDat) -> + io:format("Terminating ~p (Reason: ~p)~n", [?MODULE, Reason]), + Module = LoopDat#sctp_state.module, + gen_sctp:close(LoopDat#sctp_state.sctp_sock), + Module:terminate(Reason, State, LoopDat#sctp_state.ext_state). + +code_change(OldVsn, StateName, LoopDat, Extra) -> + Module = LoopDat#sctp_state.module, + case Module:code_change(OldVsn, StateName, LoopDat#sctp_state.ext_state, Extra) of + {ok, ExtState} -> + {ok, StateName, LoopDat#sctp_state{ext_state = ExtState}}; + Other -> + Other + end. + +% Helper function to send data to the SCTP peer +send_sctp_to_peer(LoopDat, PktData, StreamId, Ppid) when is_binary(PktData) -> + #sctp_state{sctp_sock = Sock, sctp_assoc_id = Assoc} = LoopDat, + SndRcvInfo = #sctp_sndrcvinfo{assoc_id = Assoc, ppid = Ppid, stream = StreamId}, + gen_sctp:send(Sock, SndRcvInfo, PktData). + +send_prim_to_user(LoopDat, Prim) when is_record(LoopDat, sctp_state), is_record(Prim, primitive) -> + %#m3ua_state{user_fun = Fun, user_args = Args} = LoopDat, + %Fun(Prim, Args). + UserPid = LoopDat#sctp_state.user_pid, + UserPid ! Prim. + + +handle_event(Event, State, LoopDat) -> + Module = LoopDat#sctp_state.module, + io:format("Unknown Event ~p in state ~p~n", [Event, State]), + case Module:handle_event(Event, State, LoopDat#sctp_state.ext_state) of + {next_state, State, ExtState} -> + {next_state, State, LoopDat#sctp_state{ext_state = ExtState}} + end. + + +handle_info({sctp, Socket, _RemoteIp, _RemotePort, {ANC, SAC}}, + State, LoopDat) when is_record(SAC, sctp_assoc_change) -> + io:format("SCTP Assoc Change ~p ~p~n", [ANC, SAC]), + #sctp_assoc_change{state = SacState, outbound_streams = _OutStreams, + inbound_streams = _InStreams, assoc_id = AssocId} = SAC, + if + SacState == comm_up; + SacState == restart -> + case State of + associating -> + NewState = established, + Spec = confirm; + _ -> + NewState = State, + Spec = indication + end, + % primitive to the user + send_prim_to_user(LoopDat, osmo_util:make_prim('M','SCTP_ESTABLISH',Spec)); + SacState == comm_lost -> + case State of + releasing -> + Spec = confirm; + _ -> + Spec = indication + end, + send_prim_to_user(LoopDat, osmo_util:make_prim('M','SCTP_RELEASE',Spec)), + case LoopDat#sctp_state.role of + active -> + NewState = associating, + reconnect_sctp(LoopDat); + _ -> + NewState = idle + end; + SacState == addr_unreachable -> + case LoopDat#sctp_state.role of + active -> + NewState = associating, + reconnect_sctp(LoopDat); + _ -> + NewState = idle + end + end, + inet:setopts(Socket, [{active, once}]), + next_state(State, NewState, LoopDat#sctp_state{sctp_assoc_id = AssocId}); + +handle_info({sctp, Socket, RemoteIp, RemotePort, {[Anc], Data}}, State, LoopDat) -> + Module = LoopDat#sctp_state.module, + io:format("SCTP rx data: ~p ~p~n", [Anc, Data]), + % process incoming SCTP data + if Socket == LoopDat#sctp_state.sctp_sock, + RemoteIp == LoopDat#sctp_state.sctp_remote_ip, + RemotePort == LoopDat#sctp_state.sctp_remote_port -> + Ret = Module:rx_sctp(Anc, Data, State, LoopDat#sctp_state.ext_state), + case Ret of + {ok, Prim, ExtState} -> + send_prim_to_user(LoopDat, Prim); + {ignore, ExtState} -> + ok + end; + true -> + io:format("unknown SCTP: ~p ~p~n", [Anc, Data]), + ExtState = LoopDat#sctp_state.ext_state + end, + inet:setopts(Socket, [{active, once}]), + next_state(State, State, LoopDat#sctp_state{ext_state = ExtState}); + +handle_info({sctp, Socket, RemoteIp, RemotePort, {_Anc, Data}}, State, LoopDat) + when is_record(Data, sctp_shutdown_event) -> + io:format("SCTP remote ~p:~p shutdown~n", [RemoteIp, RemotePort]), + % FIXME: send SCTP_RELEASE.ind ? + inet:setopts(Socket, [{active, once}]), + case LoopDat#sctp_state.role of + active -> + reconnect_sctp(LoopDat); + _ -> + ok + end, + next_state(State, associating, LoopDat); + +handle_info(Info, State, LoopDat) -> + Module = LoopDat#sctp_state.module, + case Module:handle_info(Info, State, LoopDat#sctp_state.ext_state) of + {next_state, State, ExtState} -> + {next_state, State, LoopDat#sctp_state{ext_state = ExtState}} + end. + + +idle(#primitive{subsystem = 'M', gen_name = 'SCTP_ESTABLISH', spec_name = request}, LoopDat) -> + case LoopDat#sctp_state.role of + active -> + reconnect_sctp(LoopDat); + _ -> + ok + end, + next_state(idle, associating, LoopDat). + + + +associating(#primitive{subsystem = 'M', gen_name = 'SCTP_RELEASE', + spec_name = request}, LoopDat) -> + % directly send RELEASE.conf ?!? + next_state(associating, idle, LoopDat). + + +established(#primitive{subsystem = 'M', gen_name = 'SCTP_RELEASE', + spec_name = request}, LoopDat) -> + next_state(established, releasing, LoopDat); +established(#primitive{subsystem = 'MTP', gen_name = 'TRANSFER', + spec_name = request, parameters = Params}, LoopDat) -> + % MTP-TRANSFER.req from user app; Send message to remote peer + Module = LoopDat#sctp_state.module, + ExtState = Module:mtp_xfer(Params, LoopDat#sctp_state.ext_state), + next_state(established, established, LoopDat#sctp_state{ext_state = ExtState}); +established(#primitive{subsystem = 'SCTP', gen_name = 'TRANSFER', + spec_name = request, parameters = {Stream, Ppid, Data}}, LoopDat) -> + io:format("SCTP-TRANSFER.req~n",[]), + % somebody (typically callback module) requests us to send SCTP data + send_sctp_to_peer(LoopDat, Data, Stream, Ppid), + next_state(established, established, LoopDat). + +next_state(State, NewState, LoopDat) when is_record(LoopDat, sctp_state) -> + Module = LoopDat#sctp_state.module, + case NewState of + State -> + {next_state, NewState, LoopDat}; + _ -> + ExtState = Module:state_change(State, NewState, LoopDat#sctp_state.ext_state), + {next_state, NewState, LoopDat#sctp_state{ext_state = ExtState}} + end. diff --git a/src/sctp_m2pa.erl b/src/sctp_m2pa.erl new file mode 100644 index 0000000..d31f7de --- /dev/null +++ b/src/sctp_m2pa.erl @@ -0,0 +1,198 @@ +% M2PA in accordance with RFC4165 (http://tools.ietf.org/html/rfc4665) + +% (C) 2011-2012 by Harald Welte +% +% 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 . + +-module(sctp_m2pa). +-author('Harald Welte '). +-behaviour(sctp_core). + +-include_lib("kernel/include/inet_sctp.hrl"). +-include("osmo_util.hrl"). +-include("m2pa.hrl"). + +-export([init/1, terminate/3, code_change/4, handle_event/3, handle_info/3]). + +-export([rx_sctp/4, mtp_xfer/2, state_change/3]). + +-record(m2pa_state, { + last_bsn_received, + last_fsn_sent, + lsc_pid, + iac_pid + }). + +%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% +% gen_fsm callbacks +%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% + +init(_InitOpts) -> + % start MTP2 IAC FSM pointing LSC, AERM and TXC to us + {ok, Lsc} = gen_fsm:start_link(mtp2_lsc, [self(), self(), self(),self()], [{debug, [trace]}]), + {ok, Iac} = gen_fsm:sync_send_event(Lsc, get_iac_pid), + gen_fsm:send_event(Lsc, power_on), + {ok, #m2pa_state{last_bsn_received=16#ffffff, last_fsn_sent=16#ffffff, + lsc_pid=Lsc, iac_pid=Iac}}. + +terminate(Reason, _State, _LoopDat) -> + io:format("Terminating ~p (Reason ~p)~n", [?MODULE, Reason]), + ok. + +code_change(_OldVsn, _State, LoopDat, _Extra) -> + {ok, LoopDat}. + +handle_event(_Event, State, LoopDat) -> + {next_state, State, LoopDat}. + +handle_info({lsc_txc, What}, State, LoopDat) when + What == start; What == retrieval_request_and_fsnc -> + {next_state, State, LoopDat}; +handle_info({Who, What}, established, LoopDat) when Who == iac_txc; Who == lsc_txc -> + Ls = iac_to_ls(What), + send_linkstate(Ls, LoopDat), + {next_state, established, LoopDat}; +handle_info(_Info, State, LoopDat) -> + {next_state, State, LoopDat}. + +%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% +% sctp_core callbacks +%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% + +% sctp_core indicates that ew have received some data... +rx_sctp(#sctp_sndrcvinfo{ppid = ?M2PA_PPID}, Data, State, LoopDat) -> + {ok, M2pa} = m2pa_codec:parse_msg(Data), + FsnRecv = M2pa#m2pa_msg.fwd_seq_nr, + % FIXME: check sequenc number linearity + case M2pa of + #m2pa_msg{msg_class = ?M2PA_CLASS_M2PA, + msg_type = ?M2PA_TYPE_USER} -> + Mtp3 = M2pa#m2pa_msg.mtp3, + Prim = osmo_util:make_prim('MTP','TRANSFER',indication, Mtp3), + {ok, Prim, LoopDat#m2pa_state{last_bsn_received = FsnRecv}}; + #m2pa_msg{msg_type = ?M2PA_TYPE_LINK} -> + handle_linkstate(M2pa, LoopDat), + {ignore, LoopDat}; + _ -> + % do something with link related msgs + io:format("M2PA Unknown message ~p in state ~p~n", [M2pa, State]), + {ignore, State, LoopDat} + end. + +% MTP-TRANSFER.req has arrived at sctp_core, encapsulate+tx it +mtp_xfer(Mtp3, LoopDat) -> + Fsn = inc_seq_nr(LoopDat#m2pa_state.last_fsn_sent), + M2pa = #m2pa_msg{msg_class = ?M2PA_CLASS_M2PA, + msg_type = ?M2PA_TYPE_USER, + fwd_seq_nr = Fsn, + back_seq_nr = LoopDat#m2pa_state.last_bsn_received, + mtp3 = Mtp3}, + M2paBin = m2pa_codec:encode_msg(M2pa), + LoopDat2 = LoopDat#m2pa_state{last_fsn_sent = Fsn}, + tx_sctp(?M2PA_STREAM_USER, M2paBin), + LoopDat2. + +state_change(_, established, LoopDat) -> + % emulate a 'start' from LSC + gen_fsm:send_event(LoopDat#m2pa_state.lsc_pid, start), + LoopDat; +state_change(established, _, LoopDat) -> + gen_fsm:send_event(LoopDat#m2pa_state.lsc_pid, link_failure), + LoopDat; +state_change(_, _, LoopDat) -> + LoopDat. + + +%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% +% helper functions +%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% + +inc_seq_nr(SeqNr) when is_integer(SeqNr) -> + SeqNr + 1 rem 16#FFFFFF. + +handle_linkstate(M2pa, LoopDat) when is_record(M2pa, m2pa_msg) -> + Linkstate = proplists:get_value(link_state, M2pa#m2pa_msg.parameters), + LsMtp2 = ls_to_iac(Linkstate), + if LsMtp2 == fisu -> + gen_fsm:send_event(LoopDat#m2pa_state.lsc_pid, fisu_msu_received); + LsMtp2 == si_po -> + gen_fsm:send_event(LoopDat#m2pa_state.lsc_pid, LsMtp2); + LsMtp2 == si_n; LsMtp2 == si_e; LsMtp2 == si_o; LsMtp2 == si_os -> + gen_fsm:send_event(LoopDat#m2pa_state.lsc_pid, LsMtp2), + gen_fsm:send_event(LoopDat#m2pa_state.iac_pid, LsMtp2) + end. + +% convert M2PA link state to MTP2 +ls_to_iac(?M2PA_LS_OOS) -> + si_os; +ls_to_iac(?M2PA_LS_ALIGNMENT) -> + si_o; +ls_to_iac(?M2PA_LS_PROVING_NORMAL) -> + si_n; +ls_to_iac(?M2PA_LS_PROVING_EMERG) -> + si_e; +ls_to_iac(?M2PA_LS_READY) -> + fisu; +ls_to_iac(?M2PA_LS_PROC_OUTAGE) -> + si_po; +ls_to_iac(?M2PA_LS_PROC_RECOVERED) -> + fisu; +ls_to_iac(?M2PA_LS_BUSY) -> + si_b. +% FIXME: what about BUSY_ENDED? + + +% convert MTP2 link state to M2PA +iac_to_ls(si_os) -> + ?M2PA_LS_OOS; +iac_to_ls(si_o) -> + ?M2PA_LS_ALIGNMENT; +iac_to_ls(si_n) -> + ?M2PA_LS_PROVING_NORMAL; +iac_to_ls(si_e) -> + ?M2PA_LS_PROVING_EMERG; +iac_to_ls(fisu) -> + ?M2PA_LS_READY; +iac_to_ls(msu) -> + ?M2PA_LS_READY; +iac_to_ls(si_po) -> + ?M2PA_LS_PROC_OUTAGE; +iac_to_ls(si_b) -> + ?M2PA_LS_BUSY. + +% Chapter 4.1.2 of RFC4165 +ls_stream(?M2PA_LS_PROC_OUTAGE) -> + 1; +ls_stream(?M2PA_LS_PROC_RECOVERED) -> + 1; +ls_stream(Foo) when is_integer(Foo) -> + 0. + +send_linkstate(Ls, LoopDat) when is_integer(Ls) -> + Stream = ls_stream(Ls), + M2pa = #m2pa_msg{msg_class = ?M2PA_CLASS_M2PA, + msg_type = ?M2PA_TYPE_LINK, + fwd_seq_nr = LoopDat#m2pa_state.last_fsn_sent, + back_seq_nr = LoopDat#m2pa_state.last_bsn_received, + parameters = [{link_state, Ls}]}, + M2paBin = m2pa_codec:encode_msg(M2pa), + tx_sctp(Stream, M2paBin), + LoopDat. + +tx_sctp(Stream, Payload) when is_integer(Stream), is_binary(Payload) -> + Param = {Stream, ?M2PA_PPID, Payload}, + % sent to 'ourselves' (behaviour master module) + gen_fsm:send_event(self(), osmo_util:make_prim('SCTP','TRANSFER',request,Param)). diff --git a/src/sua_codec.erl b/src/sua_codec.erl new file mode 100644 index 0000000..bec88a5 --- /dev/null +++ b/src/sua_codec.erl @@ -0,0 +1,89 @@ +% RFC 3868 SUA SCCP Adaption Layer coding / decoding + +% (C) 2012 by Harald Welte +% +% 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 . + +-module(sua_codec). +-author('Harald Welte '). +-include("sua.hrl"). + +-export([parse_msg/1, encode_msg/1]). + +parse_msg(DataBin) when is_binary(DataBin) -> + <> = DataBin, + OptList = parse_sua_opts(Remain), + #sua_msg{version = Version, msg_class = MsgClass, msg_type = MsgType, + msg_length = MsgLen-4, payload = OptList}; +parse_msg(Data) when is_list(Data) -> + parse_msg(list_to_binary(Data)). + +parse_sua_opts(OptBin) when is_binary(OptBin) -> + parse_sua_opts(OptBin, []). + +parse_sua_opts(<<>>, OptList) when is_list(OptList) -> + OptList; +parse_sua_opts(OptBin, OptList) when is_binary(OptBin), is_list(OptList) -> + <> = OptBin, + Length = LengthIncHdr - 4, + PadLength = get_num_pad_bytes(Length), + %io:format("Tag ~w, LenInHdr ~w, Len ~w, PadLen ~w, Remain ~w(~p)~n", + % [Tag, LengthIncHdr, Length, PadLength, byte_size(Remain), Remain]), + <> = Remain, + % this is ridiculous, we cannot use "<>" as the last part would not match an + % empty binary <<>> anymore. Without the "0:PadLengh" this works + % perfectly fine. Now we need some complicated construct and check if + % the resulting list would be empty :(( + if + byte_size(PadNextOpts) > PadLength -> + <<0:PadLength/integer-unit:8, NextOpts/binary>> = PadNextOpts; + true -> + NextOpts = <<>> + end, + NewOpt = {Tag, {Length, Value}}, + parse_sua_opts(NextOpts, OptList ++ [NewOpt]). + +parse_sua_opt(Opt, Msg) -> + {Opt, Msg}. + + +encode_msg(#sua_msg{version = Version, msg_class = MsgClass, + msg_type = MsgType, payload = OptList}) -> + OptBin = encode_sua_opts(OptList), + MsgLen = byte_size(OptBin) + 8, + <>. + +encode_sua_opts(OptList) when is_list(OptList) -> + encode_sua_opts(OptList, <<>>). + +encode_sua_opts([], Bin) -> + Bin; +encode_sua_opts([{Iei, Attr}|Tail], Bin) -> + OptBin = encode_sua_opt(Iei, Attr), + encode_sua_opts(Tail, <>). + +encode_sua_opt(Iei, Data) when is_integer(Iei), is_binary(Data) -> + Length = byte_size(Data) + 4, + PadLen = get_num_pad_bytes(Length), + <>. + +% compute the number of pad bits required after a binary parameter +get_num_pad_bytes(BinLenBytes) -> + case BinLenBytes rem 4 of + 0 -> 0; + Val -> 4 - Val + end. -- cgit v1.2.3