blob: bd8cddce2c331c3bcd250b68820e5d059b0017f3 [file] [log] [blame]
Harald Welte033cef02010-12-19 22:47:14 +01001% SCCP routing control procedures (SCRC)
2
3% (C) 2010 by Harald Welte <laforge@gnumonks.org>
4%
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).
22-export([start_link/1, init/1, idle/2]).
23
Harald Welte0f2f5962011-04-04 15:59:49 +020024-include("osmo_util.hrl").
Harald Welte033cef02010-12-19 22:47:14 +010025-include("sccp.hrl").
26
27
28
29-record(scrc_state, {
30 scoc_conn_ets,
31 next_local_ref,
32 user_pid, % pid() of the user process
33 mtp_tx_action % action to be performed for MTP-TRANSFER.req
34 }).
35% TODO:
36
37% is the supplied message type a connectionless message?
38is_connectionless(MsgType) ->
39 case MsgType of
40 ?SCCP_MSGT_UDT -> true;
41 ?SCCP_MSGT_UDTS -> true;
42 ?SCCP_MSGT_XUDT -> true;
43 ?SCCP_MSGT_XUDTS -> true;
44 ?SCCP_MSGT_LUDT -> true;
45 ?SCCP_MSGT_LUDTS -> true;
46 _ -> false
47 end.
48
49tx_prim_to_local_ref(Prim, LocalRef) ->
50 % determine the Pid to which the primitive must be sent
51 ConnTable = get(scoc_by_ref),
52 case ets:lookup(ConnTable, LocalRef) of
Harald Weltea6090962010-12-20 14:09:45 +010053 [{LocalRef, ScocPid}] ->
Harald Welte033cef02010-12-19 22:47:14 +010054 gen_fsm:send_event(ScocPid, Prim);
55 _ ->
56 io:format("Primitive ~p for unknown local reference ~p~n",
57 [Prim, LocalRef])
58 end.
59
60
61start_link(InitData) ->
62 % make sure to store the Pid of the caller in the scrc_state
63 gen_fsm:start_link(sccp_scrc, [{user_pid,self()}|InitData], [{debug, [trace]}]).
64
65init(InitPropList) ->
66 io:format("SCRC Init PropList~p ~n", [InitPropList]),
67 UserPid = proplists:get_value(user_pid, InitPropList),
68 MtpTxAct = proplists:get_value(mtp_tx_action, InitPropList),
69 LoopData = #scrc_state{user_pid = UserPid, mtp_tx_action = MtpTxAct, next_local_ref = 0},
70 TableRef = ets:new(scoc_by_ref, [set]),
71 put(scoc_by_ref, TableRef),
72 {ok, idle, LoopData}.
73
74
Harald Welteed266892010-12-20 12:45:25 +010075idle(#primitive{subsystem = 'MTP', gen_name = 'TRANSFER',
76 spec_name = indication, parameters = Params}, LoopDat) ->
Harald Welte033cef02010-12-19 22:47:14 +010077 {ok, Msg} = sccp_codec:parse_sccp_msg(Params),
78 io:format("Parsed Msg: ~p LoopDat ~p ~n", [Msg, LoopDat]),
79 case Msg of
80 % special handling for CR message here in SCRC
81 #sccp_msg{msg_type = ?SCCP_MSGT_CR} ->
82 % create new SCOC instance
83 UserPid = LoopDat#scrc_state.user_pid,
84 % Compute the new local reference
85 LocalRef = LoopDat#scrc_state.next_local_ref + 1,
86 LoopDat1 = LoopDat#scrc_state{next_local_ref = LocalRef},
87 % generate proplist for SCRC initialization
88 ScocPropList = [{scrc_pid, self()}, {user_pid, UserPid}, {local_reference, LocalRef}],
89 {ok, ScocPid} = sccp_scoc:start_link(ScocPropList),
Harald Welte95a79dc2010-12-19 23:07:42 +010090 % insert SCOC instance in connection table
91 ConnTable = get(scoc_by_ref),
Harald Weltea813fe02010-12-20 13:26:46 +010092 ets:insert_new(ConnTable, {LocalRef, ScocPid}),
Harald Welte033cef02010-12-19 22:47:14 +010093 % send a RCOC-CONNECTING.ind primitive to the new SCOC fsm
94 UserPrim = sccp_scoc:make_prim('RCOC','CONNECTION', indication, Msg#sccp_msg.parameters),
95 io:format("Sending ~p to ~p~n", [UserPrim, ScocPid]),
96 gen_fsm:send_event(ScocPid, UserPrim);
Harald Welteed266892010-12-20 12:45:25 +010097 % T(ias) expired on the other end of the connection
98 %#sccp_msg{msg_type = ?SCCP_MSGT_IT} ->
Harald Welte033cef02010-12-19 22:47:14 +010099 _ ->
Harald Welte033cef02010-12-19 22:47:14 +0100100 IsConnLess = is_connectionless(Msg#sccp_msg.msg_type),
101 case IsConnLess of
102 true ->
103 % it would be more proper to send them via SCLC ??
104 %gen_fsm:send(sccp_sclc, ??
105 UserPid = LoopDat#scrc_state.user_pid,
106 % FIXME: N-NOTICE.ind for NOTICE
107 UserPrim = sccp_scoc:make_prim('N','UNITDATA', indication, Msg),
108 UserPid ! {sccp, UserPrim};
109 false ->
110 % connection oriented messages need to go via SCOC instance
111 #sccp_msg{parameters = Opts} = Msg,
112 LocalRef = proplists:get_value(dst_local_ref, Opts),
Harald Weltea6090962010-12-20 14:09:45 +0100113 ScocPrim = sccp_scoc:make_prim('RCOC', 'CONNECTION-MSG', indication, Msg),
Harald Welte033cef02010-12-19 22:47:14 +0100114 case LocalRef of
115 undefined ->
116 % FIXME: send SCCP_MSGT_ERR
117 io:format("Conn-Msg to undefined ref ~p~n", [Msg]);
118 _ ->
Harald Weltea6090962010-12-20 14:09:45 +0100119 tx_prim_to_local_ref(ScocPrim, LocalRef)
Harald Welte033cef02010-12-19 22:47:14 +0100120 end
121 end,
122 LoopDat1 = LoopDat
123 end,
124 {next_state, idle, LoopDat1};
125idle(sclc_scrc_connless_msg, LoopDat) ->
126 % FIXME: get to MTP-TRANSFER.req
127 {next_state, idle, LoopDat};
Harald Welteed266892010-12-20 12:45:25 +0100128% connection oriented messages like N-DATA.req from user
129idle(#primitive{subsystem = 'OCRC', gen_name = 'CONNECTION-MSG',
130 spec_name = request, parameters = Msg}, LoopDat) ->
131 % encode the actual SCCP message
132 EncMsg = sccp_codec:encode_sccp_msg(Msg),
133 % generate a MTP-TRANSFER.req primitive to the lower layer
Harald Welte9ab80102010-12-20 13:34:03 +0100134 send_mtp_transfer_down(LoopDat, EncMsg),
Harald Welte033cef02010-12-19 22:47:14 +0100135 {next_state, idle, LoopDat};
136% SCOC has received confirmation about new incoming connection from user
Harald Welteed266892010-12-20 12:45:25 +0100137idle(#primitive{subsystem = 'OCRC', gen_name = 'CONNECTION',
138 spec_name = confirm, parameters = Params}, LoopDat) ->
Harald Welte033cef02010-12-19 22:47:14 +0100139 % encode the actual SCCP message
140 EncMsg = sccp_codec:encode_sccp_msgt(?SCCP_MSGT_CC, Params),
141 % generate a MTP-TRANSFER.req primitive to the lower layer
Harald Welteed266892010-12-20 12:45:25 +0100142 send_mtp_transfer_down(LoopDat, EncMsg),
Harald Welte033cef02010-12-19 22:47:14 +0100143 {next_state, idle, LoopDat};
144
145
146% triggered by N-CONNECT.req from user to SCOC:
Harald Welteed266892010-12-20 12:45:25 +0100147idle(#primitive{subsystem = 'OCRC', gen_name = 'CONNECTION',
148 spec_name = indication, parameters = Params}, LoopDat) ->
Harald Welte033cef02010-12-19 22:47:14 +0100149 {next_state, idle, LoopDat}.
150
151
152send_mtp_down(#scrc_state{mtp_tx_action = MtpTxAction}, Prim) ->
153 io:format("MTP Tx ~p, Prim ~p~n", [MtpTxAction, Prim]),
154 case MtpTxAction of
155 {callback_fn, Function, Args} ->
156 Function(Prim, Args);
157 _ ->
158 {error, "Unknown MtpTxAction"}
159 end.
Harald Welteed266892010-12-20 12:45:25 +0100160
161send_mtp_transfer_down(LoopDat, EncMsg) ->
162 MtpPrim = #primitive{subsystem = 'MTP', gen_name = 'TRANSFER',
163 spec_name = request, parameters = EncMsg},
164 send_mtp_down(LoopDat, MtpPrim).