blob: 0d56487744f907934d987e7d4c98923b5f69fef7 [file] [log] [blame]
Harald Welte033cef02010-12-19 22:47:14 +01001% SCCP routing control procedures (SCRC)
2
Harald Welte30b6eb22011-04-14 21:53:58 +02003% (C) 2010-2011 by Harald Welte <laforge@gnumonks.org>
Harald Welte033cef02010-12-19 22:47:14 +01004%
5% All Rights Reserved
6%
7% This program is free software; you can redistribute it and/or modify
8% it under the terms of the GNU Affero General Public License as
9% published by the Free Software Foundation; either version 3 of the
10% License, or (at your option) any later version.
11%
12% This program is distributed in the hope that it will be useful,
13% but WITHOUT ANY WARRANTY; without even the implied warranty of
14% MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
15% GNU General Public License for more details.
16%
17% You should have received a copy of the GNU Affero General Public License
18% along with this program. If not, see <http://www.gnu.org/licenses/>.
19
20-module(sccp_scrc).
21-behaviour(gen_fsm).
Harald Welte30b6eb22011-04-14 21:53:58 +020022-export([start_link/1, init/1, terminate/3, idle/2]).
Harald Welte033cef02010-12-19 22:47:14 +010023
Harald Welte0f2f5962011-04-04 15:59:49 +020024-include("osmo_util.hrl").
Harald Welte033cef02010-12-19 22:47:14 +010025-include("sccp.hrl").
Harald Welte30b6eb22011-04-14 21:53:58 +020026-include("mtp3.hrl").
Harald Welte033cef02010-12-19 22:47:14 +010027
28
29
30-record(scrc_state, {
31 scoc_conn_ets,
32 next_local_ref,
33 user_pid, % pid() of the user process
34 mtp_tx_action % action to be performed for MTP-TRANSFER.req
35 }).
36% TODO:
37
38% is the supplied message type a connectionless message?
39is_connectionless(MsgType) ->
40 case MsgType of
41 ?SCCP_MSGT_UDT -> true;
42 ?SCCP_MSGT_UDTS -> true;
43 ?SCCP_MSGT_XUDT -> true;
44 ?SCCP_MSGT_XUDTS -> true;
45 ?SCCP_MSGT_LUDT -> true;
46 ?SCCP_MSGT_LUDTS -> true;
47 _ -> false
48 end.
49
50tx_prim_to_local_ref(Prim, LocalRef) ->
51 % determine the Pid to which the primitive must be sent
52 ConnTable = get(scoc_by_ref),
53 case ets:lookup(ConnTable, LocalRef) of
Harald Weltea6090962010-12-20 14:09:45 +010054 [{LocalRef, ScocPid}] ->
Harald Welte033cef02010-12-19 22:47:14 +010055 gen_fsm:send_event(ScocPid, Prim);
56 _ ->
57 io:format("Primitive ~p for unknown local reference ~p~n",
58 [Prim, LocalRef])
59 end.
60
61
62start_link(InitData) ->
63 % make sure to store the Pid of the caller in the scrc_state
64 gen_fsm:start_link(sccp_scrc, [{user_pid,self()}|InitData], [{debug, [trace]}]).
65
66init(InitPropList) ->
67 io:format("SCRC Init PropList~p ~n", [InitPropList]),
68 UserPid = proplists:get_value(user_pid, InitPropList),
69 MtpTxAct = proplists:get_value(mtp_tx_action, InitPropList),
70 LoopData = #scrc_state{user_pid = UserPid, mtp_tx_action = MtpTxAct, next_local_ref = 0},
71 TableRef = ets:new(scoc_by_ref, [set]),
72 put(scoc_by_ref, TableRef),
73 {ok, idle, LoopData}.
74
75
Harald Welte30b6eb22011-04-14 21:53:58 +020076terminate(Reason, _State, _LoopDat) ->
77 io:format("SCRC: Terminating with reason ~p~n", [Reason]),
78 Tref = get(scoc_by_ref),
79 ets:delete(Tref),
80 ok.
81
82% helper function to create new SCOC instance
83spawn_new_scoc(LoopDat) ->
84 % create new SCOC instance
85 UserPid = LoopDat#scrc_state.user_pid,
86 % Compute the new local reference
87 LocalRef = LoopDat#scrc_state.next_local_ref + 1,
88 LoopDat1 = LoopDat#scrc_state{next_local_ref = LocalRef},
89 % generate proplist for SCRC initialization
90 ScocPropList = [{scrc_pid, self()}, {user_pid, UserPid}, {local_reference, LocalRef}],
91 {ok, ScocPid} = sccp_scoc:start_link(ScocPropList),
92 % insert SCOC instance in connection table
93 ConnTable = get(scoc_by_ref),
94 ets:insert_new(ConnTable, {LocalRef, ScocPid}),
95 {LoopDat1, ScocPid}.
96
97
98% N-CONNECT.req from user: spawn new SCOC and deliver primitive to it
99idle(P = #primitive{subsystem = 'N', gen_name = 'CONNECT',
100 spec_name = request, parameters = Params}, LoopDat) ->
101 % Start new SCOC instance
102 {LoopDat1, ScocPid} = spawn_new_scoc(LoopDat),
103 % Deliver primitive to new SCOC instance
104 gen_fsm:send_event(ScocPid, P),
105 {next_state, idle, LoopDat1};
106
107% N-UNITDATA.req from user (normally this is SCLC, but we don't have SCLC)
108idle(P= #primitive{subsystem = 'N', gen_name = 'UNITDATA',
109 spec_name = request, parameters = Params}, LoopDat) ->
110 % User needs to specify: Protocol Class, Called Party, Calling Party, Data
111 % FIXME: implement XUDT / LUDT support
112 % encode the actual SCCP message
113 EncMsg = sccp_codec:encode_sccp_msgt(?SCCP_MSGT_UDT, Params),
114 % generate a MTP-TRANSFER.req primitive to the lower layer
115 send_mtp_transfer_down(LoopDat, EncMsg),
116 {next_state, idle, LoopDat};
117
Harald Welteed266892010-12-20 12:45:25 +0100118idle(#primitive{subsystem = 'MTP', gen_name = 'TRANSFER',
119 spec_name = indication, parameters = Params}, LoopDat) ->
Harald Welte30b6eb22011-04-14 21:53:58 +0200120 {ok, Msg} = sccp_codec:parse_sccp_msg(Params#mtp3_msg.payload),
Harald Welte033cef02010-12-19 22:47:14 +0100121 io:format("Parsed Msg: ~p LoopDat ~p ~n", [Msg, LoopDat]),
122 case Msg of
123 % special handling for CR message here in SCRC
124 #sccp_msg{msg_type = ?SCCP_MSGT_CR} ->
Harald Welte30b6eb22011-04-14 21:53:58 +0200125 {LoopDat1, ScocPid} = spawn_new_scoc(LoopDat),
Harald Welte033cef02010-12-19 22:47:14 +0100126 % send a RCOC-CONNECTING.ind primitive to the new SCOC fsm
127 UserPrim = sccp_scoc:make_prim('RCOC','CONNECTION', indication, Msg#sccp_msg.parameters),
128 io:format("Sending ~p to ~p~n", [UserPrim, ScocPid]),
129 gen_fsm:send_event(ScocPid, UserPrim);
Harald Welteed266892010-12-20 12:45:25 +0100130 % T(ias) expired on the other end of the connection
131 %#sccp_msg{msg_type = ?SCCP_MSGT_IT} ->
Harald Welte033cef02010-12-19 22:47:14 +0100132 _ ->
Harald Welte033cef02010-12-19 22:47:14 +0100133 IsConnLess = is_connectionless(Msg#sccp_msg.msg_type),
134 case IsConnLess of
135 true ->
136 % it would be more proper to send them via SCLC ??
137 %gen_fsm:send(sccp_sclc, ??
138 UserPid = LoopDat#scrc_state.user_pid,
139 % FIXME: N-NOTICE.ind for NOTICE
140 UserPrim = sccp_scoc:make_prim('N','UNITDATA', indication, Msg),
141 UserPid ! {sccp, UserPrim};
142 false ->
143 % connection oriented messages need to go via SCOC instance
144 #sccp_msg{parameters = Opts} = Msg,
145 LocalRef = proplists:get_value(dst_local_ref, Opts),
Harald Weltea6090962010-12-20 14:09:45 +0100146 ScocPrim = sccp_scoc:make_prim('RCOC', 'CONNECTION-MSG', indication, Msg),
Harald Welte033cef02010-12-19 22:47:14 +0100147 case LocalRef of
148 undefined ->
149 % FIXME: send SCCP_MSGT_ERR
150 io:format("Conn-Msg to undefined ref ~p~n", [Msg]);
151 _ ->
Harald Weltea6090962010-12-20 14:09:45 +0100152 tx_prim_to_local_ref(ScocPrim, LocalRef)
Harald Welte033cef02010-12-19 22:47:14 +0100153 end
154 end,
155 LoopDat1 = LoopDat
156 end,
157 {next_state, idle, LoopDat1};
158idle(sclc_scrc_connless_msg, LoopDat) ->
159 % FIXME: get to MTP-TRANSFER.req
160 {next_state, idle, LoopDat};
Harald Welteed266892010-12-20 12:45:25 +0100161% connection oriented messages like N-DATA.req from user
162idle(#primitive{subsystem = 'OCRC', gen_name = 'CONNECTION-MSG',
163 spec_name = request, parameters = Msg}, LoopDat) ->
164 % encode the actual SCCP message
165 EncMsg = sccp_codec:encode_sccp_msg(Msg),
166 % generate a MTP-TRANSFER.req primitive to the lower layer
Harald Welte9ab80102010-12-20 13:34:03 +0100167 send_mtp_transfer_down(LoopDat, EncMsg),
Harald Welte033cef02010-12-19 22:47:14 +0100168 {next_state, idle, LoopDat};
169% SCOC has received confirmation about new incoming connection from user
Harald Welteed266892010-12-20 12:45:25 +0100170idle(#primitive{subsystem = 'OCRC', gen_name = 'CONNECTION',
171 spec_name = confirm, parameters = Params}, LoopDat) ->
Harald Welte033cef02010-12-19 22:47:14 +0100172 % encode the actual SCCP message
173 EncMsg = sccp_codec:encode_sccp_msgt(?SCCP_MSGT_CC, Params),
174 % generate a MTP-TRANSFER.req primitive to the lower layer
Harald Welteed266892010-12-20 12:45:25 +0100175 send_mtp_transfer_down(LoopDat, EncMsg),
Harald Welte033cef02010-12-19 22:47:14 +0100176 {next_state, idle, LoopDat};
177
178
179% triggered by N-CONNECT.req from user to SCOC:
Harald Welteed266892010-12-20 12:45:25 +0100180idle(#primitive{subsystem = 'OCRC', gen_name = 'CONNECTION',
181 spec_name = indication, parameters = Params}, LoopDat) ->
Harald Welte30b6eb22011-04-14 21:53:58 +0200182 % encode the actual SCCP message
183 EncMsg = sccp_codec:encode_sccp_msgt(?SCCP_MSGT_CR, Params),
184 % generate a MTP-TRANSFER.req primitive to the lower layer
185 send_mtp_transfer_down(LoopDat, EncMsg),
Harald Welte033cef02010-12-19 22:47:14 +0100186 {next_state, idle, LoopDat}.
187
Harald Welte033cef02010-12-19 22:47:14 +0100188send_mtp_down(#scrc_state{mtp_tx_action = MtpTxAction}, Prim) ->
189 io:format("MTP Tx ~p, Prim ~p~n", [MtpTxAction, Prim]),
190 case MtpTxAction of
191 {callback_fn, Function, Args} ->
192 Function(Prim, Args);
193 _ ->
194 {error, "Unknown MtpTxAction"}
195 end.
Harald Welteed266892010-12-20 12:45:25 +0100196
197send_mtp_transfer_down(LoopDat, EncMsg) ->
Harald Welte30b6eb22011-04-14 21:53:58 +0200198 Rlbl = #mtp3_routing_label{sig_link_sel = 0, origin_pc = 123, dest_pc = 456},
199 Mtp3 = #mtp3_msg{network_ind = ?MTP3_NETIND_INTERNATIONAL,
200 service_ind = ?MTP3_SERV_SCCP,
201 routing_label = Rlbl, payload = EncMsg},
Harald Welteed266892010-12-20 12:45:25 +0100202 MtpPrim = #primitive{subsystem = 'MTP', gen_name = 'TRANSFER',
Harald Welte30b6eb22011-04-14 21:53:58 +0200203 spec_name = request, parameters = Mtp3},
Harald Welteed266892010-12-20 12:45:25 +0100204 send_mtp_down(LoopDat, MtpPrim).