blob: 9ca3705729bdc1686b45569cc9abb693d61fad78 [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
24-include("sccp.hrl").
25
26
27
28-record(scrc_state, {
29 scoc_conn_ets,
30 next_local_ref,
31 user_pid, % pid() of the user process
32 mtp_tx_action % action to be performed for MTP-TRANSFER.req
33 }).
34% TODO:
35
36% is the supplied message type a connectionless message?
37is_connectionless(MsgType) ->
38 case MsgType of
39 ?SCCP_MSGT_UDT -> true;
40 ?SCCP_MSGT_UDTS -> true;
41 ?SCCP_MSGT_XUDT -> true;
42 ?SCCP_MSGT_XUDTS -> true;
43 ?SCCP_MSGT_LUDT -> true;
44 ?SCCP_MSGT_LUDTS -> true;
45 _ -> false
46 end.
47
48tx_prim_to_local_ref(Prim, LocalRef) ->
49 % determine the Pid to which the primitive must be sent
50 ConnTable = get(scoc_by_ref),
51 case ets:lookup(ConnTable, LocalRef) of
Harald Weltea6090962010-12-20 14:09:45 +010052 [{LocalRef, ScocPid}] ->
Harald Welte033cef02010-12-19 22:47:14 +010053 gen_fsm:send_event(ScocPid, Prim);
54 _ ->
55 io:format("Primitive ~p for unknown local reference ~p~n",
56 [Prim, LocalRef])
57 end.
58
59
60start_link(InitData) ->
61 % make sure to store the Pid of the caller in the scrc_state
62 gen_fsm:start_link(sccp_scrc, [{user_pid,self()}|InitData], [{debug, [trace]}]).
63
64init(InitPropList) ->
65 io:format("SCRC Init PropList~p ~n", [InitPropList]),
66 UserPid = proplists:get_value(user_pid, InitPropList),
67 MtpTxAct = proplists:get_value(mtp_tx_action, InitPropList),
68 LoopData = #scrc_state{user_pid = UserPid, mtp_tx_action = MtpTxAct, next_local_ref = 0},
69 TableRef = ets:new(scoc_by_ref, [set]),
70 put(scoc_by_ref, TableRef),
71 {ok, idle, LoopData}.
72
73
Harald Welteed266892010-12-20 12:45:25 +010074idle(#primitive{subsystem = 'MTP', gen_name = 'TRANSFER',
75 spec_name = indication, parameters = Params}, LoopDat) ->
Harald Welte033cef02010-12-19 22:47:14 +010076 {ok, Msg} = sccp_codec:parse_sccp_msg(Params),
77 io:format("Parsed Msg: ~p LoopDat ~p ~n", [Msg, LoopDat]),
78 case Msg of
79 % special handling for CR message here in SCRC
80 #sccp_msg{msg_type = ?SCCP_MSGT_CR} ->
81 % create new SCOC instance
82 UserPid = LoopDat#scrc_state.user_pid,
83 % Compute the new local reference
84 LocalRef = LoopDat#scrc_state.next_local_ref + 1,
85 LoopDat1 = LoopDat#scrc_state{next_local_ref = LocalRef},
86 % generate proplist for SCRC initialization
87 ScocPropList = [{scrc_pid, self()}, {user_pid, UserPid}, {local_reference, LocalRef}],
88 {ok, ScocPid} = sccp_scoc:start_link(ScocPropList),
Harald Welte95a79dc2010-12-19 23:07:42 +010089 % insert SCOC instance in connection table
90 ConnTable = get(scoc_by_ref),
Harald Weltea813fe02010-12-20 13:26:46 +010091 ets:insert_new(ConnTable, {LocalRef, ScocPid}),
Harald Welte033cef02010-12-19 22:47:14 +010092 % send a RCOC-CONNECTING.ind primitive to the new SCOC fsm
93 UserPrim = sccp_scoc:make_prim('RCOC','CONNECTION', indication, Msg#sccp_msg.parameters),
94 io:format("Sending ~p to ~p~n", [UserPrim, ScocPid]),
95 gen_fsm:send_event(ScocPid, UserPrim);
Harald Welteed266892010-12-20 12:45:25 +010096 % T(ias) expired on the other end of the connection
97 %#sccp_msg{msg_type = ?SCCP_MSGT_IT} ->
Harald Welte033cef02010-12-19 22:47:14 +010098 _ ->
Harald Welte033cef02010-12-19 22:47:14 +010099 IsConnLess = is_connectionless(Msg#sccp_msg.msg_type),
100 case IsConnLess of
101 true ->
102 % it would be more proper to send them via SCLC ??
103 %gen_fsm:send(sccp_sclc, ??
104 UserPid = LoopDat#scrc_state.user_pid,
105 % FIXME: N-NOTICE.ind for NOTICE
106 UserPrim = sccp_scoc:make_prim('N','UNITDATA', indication, Msg),
107 UserPid ! {sccp, UserPrim};
108 false ->
109 % connection oriented messages need to go via SCOC instance
110 #sccp_msg{parameters = Opts} = Msg,
111 LocalRef = proplists:get_value(dst_local_ref, Opts),
Harald Weltea6090962010-12-20 14:09:45 +0100112 ScocPrim = sccp_scoc:make_prim('RCOC', 'CONNECTION-MSG', indication, Msg),
Harald Welte033cef02010-12-19 22:47:14 +0100113 case LocalRef of
114 undefined ->
115 % FIXME: send SCCP_MSGT_ERR
116 io:format("Conn-Msg to undefined ref ~p~n", [Msg]);
117 _ ->
Harald Weltea6090962010-12-20 14:09:45 +0100118 tx_prim_to_local_ref(ScocPrim, LocalRef)
Harald Welte033cef02010-12-19 22:47:14 +0100119 end
120 end,
121 LoopDat1 = LoopDat
122 end,
123 {next_state, idle, LoopDat1};
124idle(sclc_scrc_connless_msg, LoopDat) ->
125 % FIXME: get to MTP-TRANSFER.req
126 {next_state, idle, LoopDat};
Harald Welteed266892010-12-20 12:45:25 +0100127% connection oriented messages like N-DATA.req from user
128idle(#primitive{subsystem = 'OCRC', gen_name = 'CONNECTION-MSG',
129 spec_name = request, parameters = Msg}, LoopDat) ->
130 % encode the actual SCCP message
131 EncMsg = sccp_codec:encode_sccp_msg(Msg),
132 % generate a MTP-TRANSFER.req primitive to the lower layer
Harald Welte9ab80102010-12-20 13:34:03 +0100133 send_mtp_transfer_down(LoopDat, EncMsg),
Harald Welte033cef02010-12-19 22:47:14 +0100134 {next_state, idle, LoopDat};
135% SCOC has received confirmation about new incoming connection from user
Harald Welteed266892010-12-20 12:45:25 +0100136idle(#primitive{subsystem = 'OCRC', gen_name = 'CONNECTION',
137 spec_name = confirm, parameters = Params}, LoopDat) ->
Harald Welte033cef02010-12-19 22:47:14 +0100138 % encode the actual SCCP message
139 EncMsg = sccp_codec:encode_sccp_msgt(?SCCP_MSGT_CC, Params),
140 % generate a MTP-TRANSFER.req primitive to the lower layer
Harald Welteed266892010-12-20 12:45:25 +0100141 send_mtp_transfer_down(LoopDat, EncMsg),
Harald Welte033cef02010-12-19 22:47:14 +0100142 {next_state, idle, LoopDat};
143
144
145% triggered by N-CONNECT.req from user to SCOC:
Harald Welteed266892010-12-20 12:45:25 +0100146idle(#primitive{subsystem = 'OCRC', gen_name = 'CONNECTION',
147 spec_name = indication, parameters = Params}, LoopDat) ->
Harald Welte033cef02010-12-19 22:47:14 +0100148 {next_state, idle, LoopDat}.
149
150
151send_mtp_down(#scrc_state{mtp_tx_action = MtpTxAction}, Prim) ->
152 io:format("MTP Tx ~p, Prim ~p~n", [MtpTxAction, Prim]),
153 case MtpTxAction of
154 {callback_fn, Function, Args} ->
155 Function(Prim, Args);
156 _ ->
157 {error, "Unknown MtpTxAction"}
158 end.
Harald Welteed266892010-12-20 12:45:25 +0100159
160send_mtp_transfer_down(LoopDat, EncMsg) ->
161 MtpPrim = #primitive{subsystem = 'MTP', gen_name = 'TRANSFER',
162 spec_name = request, parameters = EncMsg},
163 send_mtp_down(LoopDat, MtpPrim).