initial commit of Erlang SCCP implementation

This code is my humble attempt to implement the most important
parts of the Q.71x specifcations in Erlang.  The process tree
is trying to model the SCCP reference model as closely as psosible.

The SCRC and SCOC entities are implemented as OTP gen_fsm behavior.

SCLC is not implemented as separate state machine to reduce the number
of processes and message passing between them

SCMC is not implemented at all.

Each MTP (or other transport link) has one SCRC instance and as many
SCOC instances as there are connection-oriented SCCP sessions on this link.

There is no support for Global Title Translation (GTT) as of now.
This commit is contained in:
Harald Welte 2010-12-19 22:47:14 +01:00
commit 033cef0766
5 changed files with 926 additions and 0 deletions

183
src/sccp_codec.erl Normal file
View File

@ -0,0 +1,183 @@
% ITU-T Q.71x SCCP Message coding / decoding
% (C) 2010 by Harald Welte <laforge@gnumonks.org>
%
% 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 <http://www.gnu.org/licenses/>.
-module(sccp_codec).
-author('Harald Welte <laforge@gnumonks.org>').
-include("sccp.hrl").
-export([parse_sccp_msg/1, encode_sccp_msg/1, encode_sccp_msgt/2]).
-compile(export_all).
% parse SCCP Optional Part
parse_sccp_opt(OptType, OptLen, Content) ->
{OptType, {OptLen, Content}}.
parse_sccp_opts(<<>>, OptList) ->
% empty list
OptList;
parse_sccp_opts(<<0>>, OptList) ->
% end of options
OptList;
parse_sccp_opts(OptBin, OptList) ->
<<OptType, OptLen, Content:OptLen/binary, Remain/binary>> = OptBin,
NewOpt = parse_sccp_opt(OptType, OptLen, Content),
parse_sccp_opts(Remain, [NewOpt|OptList]).
% Parse incoming SCCP message, one function for every message type
parse_sccp_msgt(?SCCP_MSGT_CR, DataBin) ->
% first get the fixed part
<<_:8, SrcLocalRef:24, ProtoClass:8, RemainVar/binary >> = DataBin,
% variable length fixed part
<<PtrVar:8, PtrOpt:8, _/binary>> = RemainVar,
CalledPartyLen = binary:at(RemainVar, PtrVar),
CalledParty = binary:part(RemainVar, PtrVar+1, CalledPartyLen),
% optional part
OptBin = binary:part(RemainVar, 1 + PtrOpt, byte_size(RemainVar)-(1+PtrOpt)),
OptList = parse_sccp_opts(OptBin, []),
%OptList = [],
% build parsed list of message
[{src_local_ref, SrcLocalRef},{protocol_class, ProtoClass},{called_party_addr, CalledParty}|OptList];
parse_sccp_msgt(?SCCP_MSGT_CC, DataBin) ->
% first get the fixed part
<<_:8, DstLocalRef:24, SrcLocalRef:24, ProtoClass:8, Remain/binary >> = DataBin,
% optional part
OptList = parse_sccp_opts(Remain, []),
% build parsed list of message
[{dst_local_ref, DstLocalRef},{src_local_ref, SrcLocalRef},{protocol_class, ProtoClass}|OptList];
parse_sccp_msgt(?SCCP_MSGT_CREF, DataBin) ->
% first get the fixed part
<<_:8, DstLocalRef:24, RefusalCause:8, Remain/binary >> = DataBin,
% optional part
OptList = parse_sccp_opts(Remain, []),
% build parsed list of message
[{dst_local_ref, DstLocalRef},{refusal_cause, RefusalCause}|OptList];
parse_sccp_msgt(?SCCP_MSGT_RLSD, DataBin) ->
<<_:8, DstLocalRef:24, SrcLocalRef:24, ReleaseCause:8, Remain/binary >> = DataBin,
% optional part
OptList = parse_sccp_opts(Remain, []),
% build parsed list of message
[{dst_local_ref, DstLocalRef},{src_local_ref, SrcLocalRef},{release_cause, ReleaseCause}|OptList];
parse_sccp_msgt(?SCCP_MSGT_RLC, DataBin) ->
<<_:8, DstLocalRef:24, SrcLocalRef:24>> = DataBin,
% build parsed list of message
[{dst_local_ref, DstLocalRef},{src_local_ref, SrcLocalRef}];
parse_sccp_msgt(?SCCP_MSGT_DT1, DataBin) ->
<<_:8, DstLocalRef:24, SegmReass:8, DataPtr:8, Remain/binary >> = DataBin,
DataLen = binary:at(Remain, DataPtr-1),
UserData = binary:part(Remain, DataPtr-1+1, DataLen),
% build parsed list of message
[{dst_local_ref, DstLocalRef},{segm_reass, SegmReass},{user_data, UserData}];
parse_sccp_msgt(?SCCP_MSGT_DT2, DataBin) ->
<<_:8, DstLocalRef:24, SeqSegm:16, DataPtr:8, Remain/binary >> = DataBin,
DataLen = binary:at(Remain, DataPtr-1),
UserData = binary:part(Remain, DataPtr-1+1, DataLen),
% build parsed list of message
[{dst_local_ref, DstLocalRef},{seq_segm, SeqSegm},{user_data, UserData}];
parse_sccp_msgt(?SCCP_MSGT_AK, DataBin) ->
<<_:8, DstLocalRef:24, RxSeqnr:8, Credit:8>> = DataBin,
[{dst_local_ref, DstLocalRef},{rx_seq_nr, RxSeqnr},{credit, Credit}];
parse_sccp_msgt(?SCCP_MSGT_UDT, DataBin) ->
<<_:8, ProtoClass:8, CalledPartyPtr:8, CallingPartyPtr:8, DataPtr:8, Remain/binary >> = DataBin,
% variable part
CalledPartyLen = binary:at(Remain, CalledPartyPtr-3),
CalledParty = binary:part(Remain, CalledPartyPtr-3+1, CalledPartyLen),
CallingPartyLen = binary:at(Remain, CallingPartyPtr-2),
CallingParty = binary:part(Remain, CallingPartyPtr-2+1, CallingPartyLen),
DataLen = binary:at(Remain, DataPtr-1),
UserData = binary:part(Remain, DataPtr-1+1, DataLen),
[{protocol_class, ProtoClass},{called_party_addr, CalledParty},
{calling_party_addr, CallingParty},{user_data, UserData}];
parse_sccp_msgt(?SCCP_MSGT_UDTS, DataBin) ->
parse_sccp_msgt(?SCCP_MSGT_UDT, DataBin);
parse_sccp_msgt(?SCCP_MSGT_ED, DataBin) ->
<<_:8, DstLocalRef:24, DataPtr:8, Remain/binary>> = DataBin,
DataLen = binary:at(Remain, DataPtr-1),
UserData = binary:part(Remain, DataPtr-1+1, DataLen),
[{dst_local_ref, DstLocalRef}, {user_data, UserData}];
parse_sccp_msgt(?SCCP_MSGT_EA, DataBin) ->
<<_:8, DstLocalRef:24>> = DataBin,
[{dst_local_ref, DstLocalRef}];
parse_sccp_msgt(?SCCP_MSGT_RSR, DataBin) ->
<<_:8, DstLocalRef:24, SrcLocalRef:24, ResetCause:8>> = DataBin,
[{dst_local_ref, DstLocalRef},{src_local_ref, SrcLocalRef},{reset_cause, ResetCause}];
parse_sccp_msgt(?SCCP_MSGT_RSC, DataBin) ->
<<_:8, DstLocalRef:24, SrcLocalRef:24>> = DataBin,
[{dst_local_ref, DstLocalRef},{src_local_ref, SrcLocalRef}];
parse_sccp_msgt(?SCCP_MSGT_ERR, DataBin) ->
<<_:8, DstLocalRef:24, ErrCause:8>> = DataBin,
[{dst_local_ref, DstLocalRef},{error_cause, ErrCause}];
parse_sccp_msgt(?SCCP_MSGT_IT, DataBin) ->
<<_:8, DstLocalRef:24, SrcLocalRef:24, ProtoClass:8, SegmSeq:16, Credit:8>> = DataBin,
[{dst_local_ref, DstLocalRef},{src_local_ref, SrcLocalRef},
{protocol_class, ProtoClass},{seq_segm, SegmSeq},{credit, Credit}].
% FIXME: XUDT/XUDTS, LUDT/LUDTS
% process one incoming SCCP message
parse_sccp_msg(DataBin) ->
MsgType = binary:first(DataBin),
Parsed = parse_sccp_msgt(MsgType, DataBin),
{ok, #sccp_msg{msg_type = MsgType, parameters = Parsed}}.
% Encoding Part
encode_sccp_opt({OptNum, {DataBinLen, DataBin}}) when is_integer(OptNum) ->
DataBinLen8 = DataBinLen*8,
<<OptNum:8, DataBinLen:8, DataBin:DataBinLen8>>;
encode_sccp_opt({OptAtom,_}) when is_atom(OptAtom) ->
<<>>.
encode_sccp_opts([], OptEnc) ->
% end of options + convert to binary
list_to_binary([OptEnc, ?SCCP_PNC_END_OF_OPTIONAL]);
encode_sccp_opts([CurOpt|OptPropList], OptEnc) ->
CurOptEnc = encode_sccp_opt(CurOpt),
encode_sccp_opts(OptPropList, list_to_binary([OptEnc,CurOptEnc])).
encode_sccp_msgt(?SCCP_MSGT_CR, Params) ->
SrcLocalRef = proplists:get_value(src_local_ref, Params),
ProtoClass = proplists:get_value(protocol_class, Params),
OptBin = encode_sccp_opts(Params, []),
<<?SCCP_MSGT_CR:8, SrcLocalRef:24, ProtoClass:8, OptBin/binary>>;
encode_sccp_msgt(?SCCP_MSGT_CC, Params) ->
SrcLocalRef = proplists:get_value(src_local_ref, Params),
DstLocalRef = proplists:get_value(dst_local_ref, Params),
ProtoClass = proplists:get_value(protocol_class, Params),
OptBin = encode_sccp_opts(Params, []),
<<?SCCP_MSGT_CC:8, DstLocalRef:24, SrcLocalRef:24, ProtoClass:8, OptBin/binary >>;
encode_sccp_msgt(?SCCP_MSGT_CREF, Params) ->
DstLocalRef = proplists:get_value(dst_local_ref, Params),
RefusalCause = proplists:get_value(refusal_cause, Params),
% FIXME
Remain = <<>>,
<<?SCCP_MSGT_CREF:8, DstLocalRef:24, RefusalCause:8, Remain/binary >>;
encode_sccp_msgt(?SCCP_MSGT_RLSD, Params) ->
SrcLocalRef = proplists:get_value(src_local_ref, Params),
DstLocalRef = proplists:get_value(dst_local_ref, Params),
ReleaseCause = proplists:get_value(release_cause, Params),
% FIXME
Remain = <<>>,
<<?SCCP_MSGT_RLSD:8, DstLocalRef:24, SrcLocalRef:24, ReleaseCause:8, Remain/binary >>.
% encode one sccp message data structure into the on-wire format
encode_sccp_msg(#sccp_msg{msg_type = MsgType, parameters = Params}) ->
encode_sccp_msgt(MsgType, Params).

41
src/sccp_sclc.erl Normal file
View File

@ -0,0 +1,41 @@
% SCCP connectionles control (SCLC)
% (C) 2010 by Harald Welte <laforge@gnumonks.org>
%
% 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 <http://www.gnu.org/licenses/>.
-module(sccp_sclc).
-behaviour(gen_fsm).
-export([start_link/1]).
% TODO:
start_link(Init) ->
gen_fsm:start_link({local, sccp_sclc}, sccp_sclc, Init, []).
init(InitData) ->
{ok, idle, {[], InitData}}.
idle(connectionless_msg,
%idle(changes_needed, LoopDat) ->
idle({'N', 'UNITDATA', request, Parms}, LoopDat) ->
% assign SLS
gen_fsm:send_event(sccp_scrc, connectionless_msg
{next_state, idle, LoopDat};
%idle(scmg_msg, LoopDat) ->
idle(routing_failure, LoopDat) ->

474
src/sccp_scoc.erl Normal file
View File

@ -0,0 +1,474 @@
% ITU-T Q.71x SCCP Connection-oriented Control (SCOC)
% (C) 2010 by Harald Welte <laforge@gnumonks.org>
%
% 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 <http://www.gnu.org/licenses/>.
-module(sccp_scoc).
-behaviour(gen_fsm).
-include("sccp.hrl").
-export([start_link/1]).
-export([init/1, handle_event/3]).
-export([idle/2, conn_pend_in/2, conn_pend_out/2, active/2, disconnect_pending/2,
reset_incoming/2, reset_outgoing/2, bothway_reset/2, wait_conn_conf/2]).
-export([make_prim/4, make_prim/3]).
%% gen_fsm callbacks
% Appendix C.4 of Q.714 (all in milliseconds)
-define(CONNECTION_TIMER, 1 *60*100).
-define(TX_INACT_TIMER, 5 *60*100).
-define(RX_INACT_TIMER, 11 *60*100).
-define(RELEASE_TIMER, 10 *100).
-define(RELEASE_REP_TIMER, 10 *100).
-define(INT_TIMER, 1 *60*100).
-define(GUARD_TIMER, 23 *60*100).
-define(RESET_TIMER, 10 *100).
-define(REASSEMBLY_TIMER, 10 *60*100).
-record(state, {
role, % client | server
user_application, % {MonitorRef, pid()}
scrc_pid, % pid()
rx_inact_timer, % TRef
tx_inact_timer, % TRef
local_reference,
remote_reference,
class,
user_pid % pid()
}).
% TODO:
% expedited data
% class 3
% segmentation / reassembly
start_link(InitOpts) ->
gen_fsm:start_link(sccp_scoc, InitOpts, [{debug, [trace]}]).
init(InitOpts) ->
LoopDat = #state{user_pid=proplists:get_value(user_pid, InitOpts),
scrc_pid=proplists:get_value(scrc_pid, InitOpts),
local_reference=proplists:get_value(local_reference, InitOpts)},
io:format("SCOC init Pid=~p LoopDat ~p~n", [self(), LoopDat]),
{ok, idle, LoopDat}.
handle_event(stop, _StateName, LoopDat) ->
io:format("SCOC received stop event~n"),
{stop, normal, LoopDat};
handle_event({timer_expired, tx_inact_timer}, State, LoopDat) ->
% FIXME: T(ias) is expired, send IT message
io:format("FIXME: T(ias) is expired, send IT message~n", []),
{next_state, State, LoopDat};
handle_event({timer_expired, rx_inact_timer}, State, LoopDat) ->
io:format("FIXME: T(iar) is expired, release connection~n", []),
% FIXME: Initiate connection release procedure
{next_state, State, LoopDat}.
% helper function to create a #primitive record
make_prim(Subsys, GenName, SpecName) ->
make_prim(Subsys, GenName, SpecName, []).
make_prim(Subsys, GenName, SpecName, Param) ->
#primitive{subsystem = Subsys, gen_name = GenName,
spec_name = SpecName, parameters = Param}.
% helper function to send a primitive to the user
send_user(LoopDat = #state{user_pid = Pid}, Prim = #primitive{}) ->
Pid ! {sccp, Prim}.
% low-level functions regarding activity timers
restart_tx_inact_timer(LoopDat) ->
Tias = timer:apply_after(?TX_INACT_TIMER, gen_fsm, send_all_state_event,
[self(), {timer_expired, tx_inact_timer}]),
LoopDat#state{tx_inact_timer = Tias}.
restart_rx_inact_timer(LoopDat) ->
Tiar = timer:apply_after(?RX_INACT_TIMER, gen_fsm, send_all_state_event,
[self(), {timer_expired, rx_inact_timer}]),
LoopDat#state{rx_inact_timer = Tiar}.
start_inact_timers(LoopDat) ->
Tias = timer:apply_after(?TX_INACT_TIMER, gen_fsm, send_all_state_event,
[self(), {timer_expired, tx_inact_timer}]),
Tiar = timer:apply_after(?RX_INACT_TIMER, gen_fsm, send_all_state_event,
[self(), {timer_expired, rx_inact_timer}]),
LoopDat#state{rx_inact_timer = Tiar, tx_inact_timer = Tias}.
stop_inact_timers(LoopDat = #state{rx_inact_timer = Tiar, tx_inact_timer = Tias}) ->
timer:cancel(Tiar),
timer:cancel(Tias).
% -spec idle(#primitive{} | ) -> gen_fsm_state_return().
% STATE Idle
% N-CONNECT.req from user
idle(Prim = #primitive{subsystem = 'N', gen_name = 'CONNECT',
spec_name = request, parameters = Param}, LoopDat) ->
% assign local reference and SLS
% determine protocol class and credit
LoopDat1 = LoopDat#state{local_reference = make_ref(), class = 2},
gen_fsm:send_event(LoopDat1#state.scrc_pid,
make_prim('OCRC','CONNECTION', indication, Param)),
% start connection timer
{next_state, conn_pend_out, LoopDat1, ?CONNECTION_TIMER};
% RCOC-CONNECTION.req from SCRC
idle(Prim = #primitive{subsystem = 'RCOC', gen_name = 'CONNECTION',
spec_name = indication, parameters = Params}, LoopDat) ->
% associate remote reference to connection section
RemRef = proplists:get_value(src_local_ref, Params),
% determine protocol class and FIXME: credit
Class = proplists:get_value(protocol_class, Params),
LoopDat1 = LoopDat#state{remote_reference = RemRef, class = Class},
% send N-CONNECT.ind to user
send_user(LoopDat1, make_prim('N', 'CONNECT', indication, [{scoc_pid, self()}|Params])),
%#primitive{subsystem = 'N', gen_name = 'CONNECT', spec_name = indication}
{next_state, conn_pend_in, LoopDat1};
% RCOC-ROUTING_FAILURE.ind from SCRC
idle(Prim = #primitive{subsystem = 'RCOC', gen_name = 'ROUTING FAILURE',
spec_name = indication, parameters = Param}, LoopDat) ->
gen_fsm:send_event(LoopDat#state.scrc_pid,
make_prim('OCRC', 'CONNECTION REFUSED', indication)),
{next_state, idle, LoopDat};
%FIXME: request type 2 ?!?
% RCOC-RELEASED.ind from SCRC
idle(Prim = #primitive{subsystem = 'RCOC', gen_name = 'RELEASED',
spec_name = indication}, LoopDat) ->
gen_fsm:send_event(LoopDat#state.scrc_pid,
make_prim('OCRC', 'RELEASE COMPLETE', indication)),
{next_state, idle, LoopDat};
% RCOC-RELEASE_COMPLETE.ind from SCRC
idle(Prim = #primitive{subsystem = 'RCOC', gen_name = 'RELEASE COMPLETE',
spec_name = indication}, LoopDat) ->
{next_state, idle, LoopDat};
idle(#primitive{subsystem= 'RCOC', gen_name = 'DATA',
spec_name = indication, parameters = Param}, LoopDat) ->
% FIXME: if source reference, send error
send_user(LoopDat, make_prim('N', 'DATA', indication, Param)),
{next_state, idle, LoopDat}.
% STATE Connection pending incoming
conn_pend_in(Prim = #primitive{subsystem = 'N', gen_name = 'CONNECT',
spec_name = response, parameters = Param}, LoopDat) ->
io:format("SCOC N-CONNECT.resp LoopDat ~p~n", [LoopDat]),
% assign local reference, SLS, protocol class and credit for inc section
OutParam = [{dst_local_ref, LoopDat#state.remote_reference},
{src_local_ref, LoopDat#state.local_reference},
{protocol_class, LoopDat#state.class}] ++ Param,
gen_fsm:send_event(LoopDat#state.scrc_pid,
make_prim('OCRC', 'CONNECTION', confirm, OutParam)),
% start inactivity timers
LoopDat1 = start_inact_timers(LoopDat),
{next_state, active, LoopDat1};
conn_pend_in(any_npdu_type, LoopDat) ->
{next_state, conn_pend_in, LoopDat};
conn_pend_in(Prim = #primitive{subsystem = 'N', gen_name = 'DISCONNECT',
spec_name = request, parameters = Param}, LoopDat) ->
% release resourcers (local ref may have to be released an frozen)
gen_fsm:send_event(LoopDat#state.scrc_pid,
make_prim('OCRC', 'CONNECTION REFUSED', indication, Param)),
{next_state, idle, LoopDat}.
disc_ind_stop_rel_3(LoopDat) ->
% send N-DISCONNECT.ind to user
send_user(LoopDat, make_prim('N', 'DISCONNECT',indication)),
% stop inactivity timers
stop_inact_timers(LoopDat),
gen_fsm:send_event(LoopDat#state.scrc_pid,
make_prim('OCRC', 'RELESED', indication)),
% start release timer
{next_state, disconnect_pending, LoopDat, ?RELEASE_TIMER}.
rel_res_disc_ind_idle_2(LoopDat) ->
% release resources and local reference (freeze)
% send N-DISCONNECT.ind to user
send_user(LoopDat, make_prim('N', 'DISCONNECT', indication)),
{next_state, idle, LoopDat}.
% STATE Connection pending outgoing
conn_pend_out(Prim = #primitive{subsystem = 'N', gen_name = 'DISCONNECT',
spec_name = request, parameters = Param}, LoopDat) ->
% FIXME: what about the connection timer ?
{next_state, wait_conn_conf, LoopDat};
conn_pend_out(timeout, LoopDat) ->
rel_res_disc_ind_idle_2(LoopDat);
conn_pend_out(routing_failure, LoopDat) ->
rel_res_disc_ind_idle_2(LoopDat);
conn_pend_out(released, LoopDat) ->
gen_fsm:send_event(LoopDat#state.scrc_pid,
make_prim('OCRC', 'RELEASE COMPLETE', indication)),
rel_res_disc_ind_idle_2(LoopDat);
% other N-PDU Type
conn_pend_out(other_npdu_type, LoopDat) ->
rel_res_disc_ind_idle_2(LoopDat);
conn_pend_out(connection_refused, LoopDat) ->
rel_res_disc_ind_idle_2(LoopDat);
conn_pend_out(connection_confirm, LoopDat) ->
% start inactivity timers
LoopDat1 = start_inact_timers(LoopDat),
% assign protocol class and associate remote reference to connection
% send N-CONNECT.conf to user
send_user(LoopDat1, #primitive{subsystem = 'N', gen_name = 'CONNECT',
spec_name = confirm}),
{next_state, active, LoopDat1}.
stop_c_tmr_rel_idle_5(LoopDat) ->
% stop connection timer (implicit)
% release resources and local reference
{next_state, idle, LoopDat}.
rel_freeze_idle(LoopDat) ->
{next_state, idle, LoopDat}.
% STATE Wait connection confirmed
wait_conn_conf(released, LoopDat) ->
gen_fsm:send_event(LoopDat#state.scrc_pid,
make_prim('OCRC', 'RELEASE COMPLETE', indication)),
stop_c_tmr_rel_idle_5(LoopDat);
wait_conn_conf(connection_confirm, LoopDat) ->
% stop connection timer (implicit)
% associate remote reference to connection
relsd_tmr_disc_pend_6(LoopDat);
wait_conn_conf(other_npdu_type, LoopDat) ->
% stop connection timer (implicit)
rel_freeze_idle(LoopDat);
wait_conn_conf(timeout, LoopDat) ->
stop_c_tmr_rel_idle_5(LoopDat);
wait_conn_conf(connection_refused, LoopDat) ->
stop_c_tmr_rel_idle_5(LoopDat);
wait_conn_conf(routing_failure, LoopDat) ->
stop_c_tmr_rel_idle_5(LoopDat).
relsd_tmr_disc_pend_6(LoopDat) ->
gen_fsm:send_event(LoopDat#state.scrc_pid,
make_prim('OCRC', 'RELEASED', indication)),
% start release timer
{next_state, disconnect_pending, LoopDat, ?RELEASE_TIMER}.
% STATE Active
active(Prim = #primitive{subsystem = 'N', gen_name = 'DISCONNECT',
spec_name = request, parameters = Param}, LoopDat) ->
% stop inactivity timers
start_inact_timers(LoopDat),
relsd_tmr_disc_pend_6(LoopDat);
active(internal_disconnect, LoopDat) ->
disc_ind_stop_rel_3(LoopDat);
active(connection_refused, LoopDat) ->
{next_state, active, LoopDat};
active(connection_confirm, LoopDat) ->
{next_state, active, LoopDat};
active(release_complete, LoopDat) ->
{next_state, active, LoopDat};
active(released, LoopDat) ->
% send N-DISCONNECT.ind to user
send_user(LoopDat, #primitive{subsystem = 'N', gen_name = 'DISCONNECT',
spec_name = indication}),
% release resources and local reference (freeze)
% stop inactivity timers
stop_inact_timers(LoopDat),
gen_fsm:send_event(LoopDat#state.scrc_pid,
make_prim('OCRC', 'RELEASE COMPLETE', indication)),
{next_state, idle, LoopDat};
active(error, LoopDat) ->
% send N-DISCONNECT.ind to user
send_user(LoopDat, #primitive{subsystem = 'N', gen_name = 'DISCONNECT',
spec_name = indication}),
% release resources and local reference (freeze)
% stop inactivity timers
stop_inact_timers(LoopDat),
gen_fsm:send_event(LoopDat#state.scrc_pid,
make_prim('OCRC', 'RELEASE COMPLETE', indication)),
{next_state, idle, LoopDat};
active(rcv_inact_tmr_exp, LoopDat) ->
disc_ind_stop_rel_3(LoopDat);
active(routing_failure, LoopDat) ->
% send N-DISCONNECT.ind to user
send_user(LoopDat, #primitive{subsystem = 'N', gen_name = 'DISCONNECT',
spec_name = indication}),
% stop inactivity timers
stop_inact_timers(LoopDat),
% start release timer
{next_state, disconnect_pending, LoopDat, ?RELEASE_TIMER};
% Connection release procedures at destination node
%active(internal_disconnect) ->
% Data transfer procedures
active(Prim = #primitive{subsystem = 'N', gen_name = 'DATA',
spec_name = request, parameters = Param}, LoopDat) ->
% FIXME Segment NSDU and assign value to bit M
% FIXME handle protocol class 3
gen_fsm:send_event(LoopDat#state.scrc_pid, {dt1, []}),
% restart send inactivity timer
LoopDat1 = restart_tx_inact_timer(LoopDat),
{next_state, active, LoopDat1};
active({dt1, Param}, LoopDat) ->
% restart receive inactivity timer
LoopDat1 = restart_rx_inact_timer(LoopDat),
% FIXME handle protocol class 3
% FIXME check for M-bit=1 and put data in Rx queue
% N-DATA.ind to user
send_user(LoopDat, make_prim('N', 'DATA', indication, Param)),
{next_state, active, LoopDat1};
% Reset procedures
active(Prim = #primitive{subsystem = 'N', gen_name = 'RESET',
spec_name = request, parameters = Param}, LoopDat) ->
gen_fsm:send_event(LoopDat#state.scrc_pid,
make_prim('OCRC', 'RESET', request, Param)),
% start reset timer
% restart send inact timer
LoopDat1 = restart_tx_inact_timer(LoopDat),
% reset variables and discard all queued and unacked msgs
{next_state, reset_outgoing, LoopDat1, ?RESET_TIMER};
active(internal_reset_req, LoopDat) ->
% N-RESET.ind to user
send_user(LoopDat, #primitive{subsystem = 'N', gen_name = 'RESET',
spec_name = indication}),
gen_fsm:send_event(LoopDat#state.scrc_pid,
make_prim('OCRC', 'RESET', request)),
% start reset timer
% restart send inact timer
LoopDat1 = restart_tx_inact_timer(LoopDat),
% reset variables and discard all queued and unacked msgs
{next_state, bothway_reset, LoopDat1, ?RESET_TIMER};
active(reset_confirm, LoopDat) ->
% discard received message
{next_state, active, LoopDat};
active(reset_req, LoopDat) ->
% restart send inactivity timer
LoopDat1 = restart_tx_inact_timer(LoopDat),
% N-RESET.ind to user
send_user(LoopDat, make_prim('N', 'RESET', indication)),
% reset variables and discard all queued and unacked msgs
{next_state, reset_incoming, LoopDat1}.
rel_res_stop_tmr_12(LoopDat) ->
% release resources and local reference (freeze)
% stop release and interval timers
{next_state, idle, LoopDat}.
% STATE Disconnect pending
disconnect_pending(release_complete, LoopDat) ->
rel_res_stop_tmr_12(LoopDat);
disconnect_pending(released_error, LoopDat) ->
rel_res_stop_tmr_12(LoopDat);
disconnect_pending(routing_failure, LoopDat) ->
{next_state, disconnect_pending};
disconnect_pending(other_npdu_type, LoopDat) ->
% discared received message
{next_state, disconnect_pending};
disconnect_pending(timeout, LoopDat) ->
gen_fsm:send_event(LoopDat#state.scrc_pid,
make_prim('OCRC', 'RELEASED', indication)),
% start interval timer
% FIXME start repeat release timer
{next_state, disconnect_pending, ?RELEASE_REP_TIMER};
disconnect_pending(intv_tmr_exp, LoopDat) ->
% inform maintenance
rel_res_stop_tmr_12(LoopDat);
% FIXME: this is currently ending up in normal 'timeout' above
disconnect_pending(repeat_release_tmr_exp, LoopDat) ->
gen_fsm:send_event(LoopDat#state.scrc_pid,
make_prim('OCRC', 'RELEASED', indication)),
% FIXME restart repeat release timer
{next_state, disconnect_pending}.
res_out_res_conf_req(LoopDat) ->
% N-RESET.conf to user
send_user(LoopDat, make_prim('N', 'RESET', confirm)),
% stop reset timer (implicit)
% restart receive inactivity timer
LoopDat1 = restart_rx_inact_timer(LoopDat),
% resume data transfer
{next_state, active, LoopDat1}.
% STATE Reset outgoing
reset_outgoing(Prim = #primitive{subsystem = 'N', gen_name = 'DATA',
spec_name = request, parameters = Params}, LoopDat) ->
% FIXME received information ?!?
{next_state, reset_outgoing, LoopDat};
reset_outgoing(Prim = #primitive{subsystem = 'N', gen_name = 'EXPEDITED DATA',
spec_name = request, parameters = Params}, LoopDat) ->
% FIXME received information ?!?
{next_state, reset_outgoing, LoopDat};
reset_outgoing(timeout, LoopDat) ->
% FIXME check for temporary connection section
% inform maintenance
{next_state, maintenance_Blocking, LoopDat};
%reset_outgoing(error, LoopDat) ->
%reset_outgoing(released, LoopDat) ->
reset_outgoing(other_npdu_type, LoopDat) ->
% discard received message
{next_state, reset_outgoing, LoopDat};
reset_outgoing(reset_confirm, LoopDat) ->
res_out_res_conf_req(LoopDat);
reset_outgoing(reset_request, LoopDat) ->
res_out_res_conf_req(LoopDat).
bway_res_req_resp(LoopDat) ->
{next_state, reset_outgoing, LoopDat}.
bway_res_res_conf_req(LoopDat) ->
% N-RESET.conf to user
send_user(LoopDat, #primitive{subsystem = 'N', gen_name = 'RESET',
spec_name = confirm}),
% stop reset timer (implicit)
% restart receive inactivity timer
LoopDat1 = restart_rx_inact_timer(LoopDat),
{next_state, reset_incoming, LoopDat1}.
% STATE Bothway Reset
bothway_reset(Prim = #primitive{subsystem = 'N', gen_name = 'RESET',
spec_name = request, parameters = Params}, LoopDat) ->
bway_res_req_resp(LoopDat);
bothway_reset(Prim = #primitive{subsystem = 'N', gen_name = 'RESET',
spec_name = response, parameters = Params}, LoopDat) ->
bway_res_req_resp(LoopDat);
bothway_reset(timeout, LoopDat) ->
% FIXME check for temporary connection section
% inform maintenance
{next_state, maintenance_Blocking, LoopDat};
%bothway_reset(error, LoopDat) ->
%bothway_reset(released, LoopDat) ->
bothway_reset(other_npdu_type, LoopDat) ->
% discard received message
{next_state, bothway_reset, LoopDat}.
% STATE Reset incoming
reset_incoming(Prim = #primitive{subsystem = 'N', gen_name = 'RESET',
spec_name = request, parameters = Params}, LoopDat) ->
% received information
{nest_state, reset_incoming, LoopDat};
%reset_incoming(error, LoopDat) ->
%reset_incoming(released, LoopDat) ->
reset_incoming(other_npdu_type, LoopDat) ->
% discard received message
% internal reset request
{next_state, active, LoopDat}.
% FIXME: response or request
%reset_incoming(

149
src/sccp_scrc.erl Normal file
View File

@ -0,0 +1,149 @@
% SCCP routing control procedures (SCRC)
% (C) 2010 by Harald Welte <laforge@gnumonks.org>
%
% 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 <http://www.gnu.org/licenses/>.
-module(sccp_scrc).
-behaviour(gen_fsm).
-export([start_link/1, init/1, idle/2]).
-include("sccp.hrl").
-record(scrc_state, {
scoc_conn_ets,
next_local_ref,
user_pid, % pid() of the user process
mtp_tx_action % action to be performed for MTP-TRANSFER.req
}).
% TODO:
% is the supplied message type a connectionless message?
is_connectionless(MsgType) ->
case MsgType of
?SCCP_MSGT_UDT -> true;
?SCCP_MSGT_UDTS -> true;
?SCCP_MSGT_XUDT -> true;
?SCCP_MSGT_XUDTS -> true;
?SCCP_MSGT_LUDT -> true;
?SCCP_MSGT_LUDTS -> true;
_ -> false
end.
tx_prim_to_local_ref(Prim, LocalRef) ->
% determine the Pid to which the primitive must be sent
ConnTable = get(scoc_by_ref),
case ets:lookup(ConnTable, LocalRef) of
{ok, ScocPid} ->
gen_fsm:send_event(ScocPid, Prim);
_ ->
io:format("Primitive ~p for unknown local reference ~p~n",
[Prim, LocalRef])
end.
start_link(InitData) ->
% make sure to store the Pid of the caller in the scrc_state
gen_fsm:start_link(sccp_scrc, [{user_pid,self()}|InitData], [{debug, [trace]}]).
init(InitPropList) ->
io:format("SCRC Init PropList~p ~n", [InitPropList]),
UserPid = proplists:get_value(user_pid, InitPropList),
MtpTxAct = proplists:get_value(mtp_tx_action, InitPropList),
LoopData = #scrc_state{user_pid = UserPid, mtp_tx_action = MtpTxAct, next_local_ref = 0},
TableRef = ets:new(scoc_by_ref, [set]),
put(scoc_by_ref, TableRef),
{ok, idle, LoopData}.
idle(Prim = #primitive{subsystem = 'MTP', gen_name = 'TRANSFER',
spec_name = indication, parameters = Params}, LoopDat) ->
{ok, Msg} = sccp_codec:parse_sccp_msg(Params),
io:format("Parsed Msg: ~p LoopDat ~p ~n", [Msg, LoopDat]),
case Msg of
% special handling for CR message here in SCRC
#sccp_msg{msg_type = ?SCCP_MSGT_CR} ->
% create new SCOC instance
UserPid = LoopDat#scrc_state.user_pid,
% Compute the new local reference
LocalRef = LoopDat#scrc_state.next_local_ref + 1,
LoopDat1 = LoopDat#scrc_state{next_local_ref = LocalRef},
% generate proplist for SCRC initialization
ScocPropList = [{scrc_pid, self()}, {user_pid, UserPid}, {local_reference, LocalRef}],
{ok, ScocPid} = sccp_scoc:start_link(ScocPropList),
% send a RCOC-CONNECTING.ind primitive to the new SCOC fsm
UserPrim = sccp_scoc:make_prim('RCOC','CONNECTION', indication, Msg#sccp_msg.parameters),
io:format("Sending ~p to ~p~n", [UserPrim, ScocPid]),
gen_fsm:send_event(ScocPid, UserPrim);
_ ->
IsConnLess = is_connectionless(Msg#sccp_msg.msg_type),
case IsConnLess of
true ->
% it would be more proper to send them via SCLC ??
%gen_fsm:send(sccp_sclc, ??
UserPid = LoopDat#scrc_state.user_pid,
% FIXME: N-NOTICE.ind for NOTICE
UserPrim = sccp_scoc:make_prim('N','UNITDATA', indication, Msg),
UserPid ! {sccp, UserPrim};
false ->
% connection oriented messages need to go via SCOC instance
#sccp_msg{parameters = Opts} = Msg,
LocalRef = proplists:get_value(dst_local_ref, Opts),
case LocalRef of
undefined ->
% FIXME: send SCCP_MSGT_ERR
io:format("Conn-Msg to undefined ref ~p~n", [Msg]);
_ ->
tx_prim_to_local_ref(Prim, LocalRef)
end
end,
LoopDat1 = LoopDat
end,
{next_state, idle, LoopDat1};
idle(sclc_scrc_connless_msg, LoopDat) ->
% FIXME: get to MTP-TRANSFER.req
{next_state, idle, LoopDat};
idle(sclc_scrc_conn_msg, LoopDat) ->
{next_state, idle, LoopDat};
% SCOC has received confirmation about new incoming connection from user
idle(Prim = #primitive{subsystem = 'OCRC', gen_name = 'CONNECTION',
spec_name = confirm, parameters = Params}, LoopDat) ->
% encode the actual SCCP message
EncMsg = sccp_codec:encode_sccp_msgt(?SCCP_MSGT_CC, Params),
% generate a MTP-TRANSFER.req primitive to the lower layer
MtpPrim = #primitive{subsystem = 'MTP', gen_name = 'TRANSFER',
spec_name = request, parameters = EncMsg},
send_mtp_down(LoopDat, MtpPrim),
{next_state, idle, LoopDat};
% triggered by N-CONNECT.req from user to SCOC:
idle(Prim = #primitive{subsystem = 'OCRC', gen_name = 'CONNECTION',
spec_name = indication, parameters = Params}, LoopDat) ->
{next_state, idle, LoopDat}.
send_mtp_down(#scrc_state{mtp_tx_action = MtpTxAction}, Prim) ->
io:format("MTP Tx ~p, Prim ~p~n", [MtpTxAction, Prim]),
case MtpTxAction of
{callback_fn, Function, Args} ->
Function(Prim, Args);
_ ->
{error, "Unknown MtpTxAction"}
end.

79
src/sccp_user.erl Normal file
View File

@ -0,0 +1,79 @@
% (C) 2010 by Harald Welte <laforge@gnumonks.org>
%
% 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 <http://www.gnu.org/licenses/>.
-module(sccp_user).
-author('Harald Welte <laforge@gnumonks.org>').
-export([init/3]).
-include("sccp.hrl").
-define(IPA_STREAM_ID_SCCP, 253).
-record(loop_data, {
ipa_stream_id
}).
init(TcpServerPort, IpaStreamId, Opts) ->
ipa_proto:init(),
% Create listening IPA socket
ipa_proto:start_listen(TcpServerPort, 1, Opts),
loop(#loop_data{ipa_stream_id = IpaStreamId}).
% callback function to be called by IPA socket handler if it receives some data
sccp_ipa_adapter_cb(S, IpaStreamID, DataBin, [ScrcPid]) ->
io:format("sccp_ipa_adapter_cb (Socket ~p, Stream ~p), passing data to SCRP~n", [S, IpaStreamID]),
% hand any incoming IPA message off into the SCCP stacks SCRC
gen_fsm:send_event(ScrcPid, sccp_scoc:make_prim('MTP', 'TRANSFER', indication, DataBin)).
% callback function to be called by SCCP if it wants to transmit some data
sccp_to_ipa_cb(#primitive{subsystem = 'MTP', gen_name = 'TRANSFER',
spec_name = request, parameters = DataBin}, [IpaPid, S, IpaStreamID]) ->
%ipa_proto:send(S, IpaStreamID, DataBin).
io:format("sccp_to_ipa_cb: Sending to ~p ~p/~p: ~p~n", [IpaPid, S,IpaStreamID, DataBin]),
IpaPid ! {ipa_send, S, IpaStreamID, DataBin}.
loop(LoopData) ->
receive
{ipa_tcp_accept, S} ->
io:format("sccp_ipa_adapter: ipa_tcp_accept from ~p~n", [inet:peername(S)]),
% hand over the socket into the IPA stack
{ok, IpaPid} = ipa_proto:register_socket(S),
% Start the SCRC FSM for this virtual MTP link
ScrcMtpCb = {callback_fn, fun sccp_to_ipa_cb/2, [IpaPid, S, ?IPA_STREAM_ID_SCCP]},
{ok, ScrcPid} = sccp_scrc:start_link([{mtp_tx_action, ScrcMtpCb}]),
% Register an IPA stream for SCCP
ipa_proto:register_stream(S, ?IPA_STREAM_ID_SCCP,
{callback_fn, fun sccp_ipa_adapter_cb/4, [ScrcPid]}),
ipa_proto:unblock(S),
loop(LoopData);
% this code should later be moved into the actual MSC
{sccp, Prim} ->
io:format("sccp_user has received primitive ~p~n", [Prim]),
handle_sccp_prim(Prim),
loop(LoopData)
end.
handle_sccp_prim(#primitive{subsystem = 'N', gen_name = 'CONNECT',
spec_name = indication, parameters = Params}) ->
%RespPrim = Prim#primitive{spec_name = response},
RespPrim = sccp_scoc:make_prim('N', 'CONNECT', response, []),
ScocPid = proplists:get_value(scoc_pid, Params),
gen_fsm:send_event(ScocPid, RespPrim);
handle_sccp_prim(#primitive{}) ->
ok.