blob: 54d38b713e8cee773382d191b15b27067c4921de [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
Harald Welte033cef02010-12-19 22:47:14 +010038tx_prim_to_local_ref(Prim, LocalRef) ->
39 % determine the Pid to which the primitive must be sent
40 ConnTable = get(scoc_by_ref),
41 case ets:lookup(ConnTable, LocalRef) of
Harald Weltea6090962010-12-20 14:09:45 +010042 [{LocalRef, ScocPid}] ->
Harald Welte033cef02010-12-19 22:47:14 +010043 gen_fsm:send_event(ScocPid, Prim);
44 _ ->
45 io:format("Primitive ~p for unknown local reference ~p~n",
46 [Prim, LocalRef])
47 end.
48
49
50start_link(InitData) ->
51 % make sure to store the Pid of the caller in the scrc_state
52 gen_fsm:start_link(sccp_scrc, [{user_pid,self()}|InitData], [{debug, [trace]}]).
53
54init(InitPropList) ->
55 io:format("SCRC Init PropList~p ~n", [InitPropList]),
56 UserPid = proplists:get_value(user_pid, InitPropList),
57 MtpTxAct = proplists:get_value(mtp_tx_action, InitPropList),
58 LoopData = #scrc_state{user_pid = UserPid, mtp_tx_action = MtpTxAct, next_local_ref = 0},
59 TableRef = ets:new(scoc_by_ref, [set]),
60 put(scoc_by_ref, TableRef),
61 {ok, idle, LoopData}.
62
63
Harald Welte30b6eb22011-04-14 21:53:58 +020064terminate(Reason, _State, _LoopDat) ->
65 io:format("SCRC: Terminating with reason ~p~n", [Reason]),
66 Tref = get(scoc_by_ref),
67 ets:delete(Tref),
68 ok.
69
70% helper function to create new SCOC instance
71spawn_new_scoc(LoopDat) ->
72 % create new SCOC instance
73 UserPid = LoopDat#scrc_state.user_pid,
74 % Compute the new local reference
75 LocalRef = LoopDat#scrc_state.next_local_ref + 1,
76 LoopDat1 = LoopDat#scrc_state{next_local_ref = LocalRef},
77 % generate proplist for SCRC initialization
78 ScocPropList = [{scrc_pid, self()}, {user_pid, UserPid}, {local_reference, LocalRef}],
79 {ok, ScocPid} = sccp_scoc:start_link(ScocPropList),
80 % insert SCOC instance in connection table
81 ConnTable = get(scoc_by_ref),
82 ets:insert_new(ConnTable, {LocalRef, ScocPid}),
83 {LoopDat1, ScocPid}.
84
85
86% N-CONNECT.req from user: spawn new SCOC and deliver primitive to it
87idle(P = #primitive{subsystem = 'N', gen_name = 'CONNECT',
88 spec_name = request, parameters = Params}, LoopDat) ->
89 % Start new SCOC instance
90 {LoopDat1, ScocPid} = spawn_new_scoc(LoopDat),
91 % Deliver primitive to new SCOC instance
92 gen_fsm:send_event(ScocPid, P),
93 {next_state, idle, LoopDat1};
94
95% N-UNITDATA.req from user (normally this is SCLC, but we don't have SCLC)
96idle(P= #primitive{subsystem = 'N', gen_name = 'UNITDATA',
97 spec_name = request, parameters = Params}, LoopDat) ->
98 % User needs to specify: Protocol Class, Called Party, Calling Party, Data
99 % FIXME: implement XUDT / LUDT support
100 % encode the actual SCCP message
101 EncMsg = sccp_codec:encode_sccp_msgt(?SCCP_MSGT_UDT, Params),
102 % generate a MTP-TRANSFER.req primitive to the lower layer
103 send_mtp_transfer_down(LoopDat, EncMsg),
104 {next_state, idle, LoopDat};
105
Harald Welteed266892010-12-20 12:45:25 +0100106idle(#primitive{subsystem = 'MTP', gen_name = 'TRANSFER',
107 spec_name = indication, parameters = Params}, LoopDat) ->
Harald Welte30b6eb22011-04-14 21:53:58 +0200108 {ok, Msg} = sccp_codec:parse_sccp_msg(Params#mtp3_msg.payload),
Harald Welte033cef02010-12-19 22:47:14 +0100109 io:format("Parsed Msg: ~p LoopDat ~p ~n", [Msg, LoopDat]),
110 case Msg of
111 % special handling for CR message here in SCRC
112 #sccp_msg{msg_type = ?SCCP_MSGT_CR} ->
Harald Welte30b6eb22011-04-14 21:53:58 +0200113 {LoopDat1, ScocPid} = spawn_new_scoc(LoopDat),
Harald Welte033cef02010-12-19 22:47:14 +0100114 % send a RCOC-CONNECTING.ind primitive to the new SCOC fsm
115 UserPrim = sccp_scoc:make_prim('RCOC','CONNECTION', indication, Msg#sccp_msg.parameters),
116 io:format("Sending ~p to ~p~n", [UserPrim, ScocPid]),
117 gen_fsm:send_event(ScocPid, UserPrim);
Harald Welteed266892010-12-20 12:45:25 +0100118 % T(ias) expired on the other end of the connection
119 %#sccp_msg{msg_type = ?SCCP_MSGT_IT} ->
Harald Welte033cef02010-12-19 22:47:14 +0100120 _ ->
Harald Welte9abbbad2011-04-21 12:19:41 +0200121 IsConnLess = sccp_codec:is_connectionless(Msg),
Harald Welte033cef02010-12-19 22:47:14 +0100122 case IsConnLess of
123 true ->
124 % it would be more proper to send them via SCLC ??
125 %gen_fsm:send(sccp_sclc, ??
126 UserPid = LoopDat#scrc_state.user_pid,
127 % FIXME: N-NOTICE.ind for NOTICE
128 UserPrim = sccp_scoc:make_prim('N','UNITDATA', indication, Msg),
129 UserPid ! {sccp, UserPrim};
130 false ->
131 % connection oriented messages need to go via SCOC instance
132 #sccp_msg{parameters = Opts} = Msg,
133 LocalRef = proplists:get_value(dst_local_ref, Opts),
Harald Weltea6090962010-12-20 14:09:45 +0100134 ScocPrim = sccp_scoc:make_prim('RCOC', 'CONNECTION-MSG', indication, Msg),
Harald Welte033cef02010-12-19 22:47:14 +0100135 case LocalRef of
136 undefined ->
137 % FIXME: send SCCP_MSGT_ERR
138 io:format("Conn-Msg to undefined ref ~p~n", [Msg]);
139 _ ->
Harald Weltea6090962010-12-20 14:09:45 +0100140 tx_prim_to_local_ref(ScocPrim, LocalRef)
Harald Welte033cef02010-12-19 22:47:14 +0100141 end
142 end,
143 LoopDat1 = LoopDat
144 end,
145 {next_state, idle, LoopDat1};
146idle(sclc_scrc_connless_msg, LoopDat) ->
147 % FIXME: get to MTP-TRANSFER.req
148 {next_state, idle, LoopDat};
Harald Welteed266892010-12-20 12:45:25 +0100149% connection oriented messages like N-DATA.req from user
150idle(#primitive{subsystem = 'OCRC', gen_name = 'CONNECTION-MSG',
151 spec_name = request, parameters = Msg}, LoopDat) ->
152 % encode the actual SCCP message
153 EncMsg = sccp_codec:encode_sccp_msg(Msg),
154 % generate a MTP-TRANSFER.req primitive to the lower layer
Harald Welte9ab80102010-12-20 13:34:03 +0100155 send_mtp_transfer_down(LoopDat, EncMsg),
Harald Welte033cef02010-12-19 22:47:14 +0100156 {next_state, idle, LoopDat};
157% SCOC has received confirmation about new incoming connection from user
Harald Welteed266892010-12-20 12:45:25 +0100158idle(#primitive{subsystem = 'OCRC', gen_name = 'CONNECTION',
159 spec_name = confirm, parameters = Params}, LoopDat) ->
Harald Welte033cef02010-12-19 22:47:14 +0100160 % encode the actual SCCP message
161 EncMsg = sccp_codec:encode_sccp_msgt(?SCCP_MSGT_CC, Params),
162 % generate a MTP-TRANSFER.req primitive to the lower layer
Harald Welteed266892010-12-20 12:45:25 +0100163 send_mtp_transfer_down(LoopDat, EncMsg),
Harald Welte033cef02010-12-19 22:47:14 +0100164 {next_state, idle, LoopDat};
165
166
167% triggered by N-CONNECT.req from user to SCOC:
Harald Welteed266892010-12-20 12:45:25 +0100168idle(#primitive{subsystem = 'OCRC', gen_name = 'CONNECTION',
169 spec_name = indication, parameters = Params}, LoopDat) ->
Harald Welte30b6eb22011-04-14 21:53:58 +0200170 % encode the actual SCCP message
171 EncMsg = sccp_codec:encode_sccp_msgt(?SCCP_MSGT_CR, Params),
172 % generate a MTP-TRANSFER.req primitive to the lower layer
173 send_mtp_transfer_down(LoopDat, EncMsg),
Harald Welte033cef02010-12-19 22:47:14 +0100174 {next_state, idle, LoopDat}.
175
Harald Welte033cef02010-12-19 22:47:14 +0100176send_mtp_down(#scrc_state{mtp_tx_action = MtpTxAction}, Prim) ->
177 io:format("MTP Tx ~p, Prim ~p~n", [MtpTxAction, Prim]),
178 case MtpTxAction of
179 {callback_fn, Function, Args} ->
180 Function(Prim, Args);
181 _ ->
182 {error, "Unknown MtpTxAction"}
183 end.
Harald Welteed266892010-12-20 12:45:25 +0100184
185send_mtp_transfer_down(LoopDat, EncMsg) ->
Harald Welte30b6eb22011-04-14 21:53:58 +0200186 Rlbl = #mtp3_routing_label{sig_link_sel = 0, origin_pc = 123, dest_pc = 456},
187 Mtp3 = #mtp3_msg{network_ind = ?MTP3_NETIND_INTERNATIONAL,
188 service_ind = ?MTP3_SERV_SCCP,
189 routing_label = Rlbl, payload = EncMsg},
Harald Welteed266892010-12-20 12:45:25 +0100190 MtpPrim = #primitive{subsystem = 'MTP', gen_name = 'TRANSFER',
Harald Welte30b6eb22011-04-14 21:53:58 +0200191 spec_name = request, parameters = Mtp3},
Harald Welteed266892010-12-20 12:45:25 +0100192 send_mtp_down(LoopDat, MtpPrim).