blob: 9523b92e2f4c534e8afeebdc62377966f32a91d1 [file] [log] [blame]
Harald Welte033cef02010-12-19 22:47:14 +01001
2% (C) 2010 by Harald Welte <laforge@gnumonks.org>
3%
4% All Rights Reserved
5%
6% This program is free software; you can redistribute it and/or modify
7% it under the terms of the GNU Affero General Public License as
8% published by the Free Software Foundation; either version 3 of the
9% License, or (at your option) any later version.
10%
11% This program is distributed in the hope that it will be useful,
12% but WITHOUT ANY WARRANTY; without even the implied warranty of
13% MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
14% GNU General Public License for more details.
15%
16% You should have received a copy of the GNU Affero General Public License
17% along with this program. If not, see <http://www.gnu.org/licenses/>.
18
19-module(sccp_user).
20-author('Harald Welte <laforge@gnumonks.org>').
21-export([init/3]).
22
23-include("sccp.hrl").
24
25-define(IPA_STREAM_ID_SCCP, 253).
26
27-record(loop_data, {
28 ipa_stream_id
29 }).
30
31init(TcpServerPort, IpaStreamId, Opts) ->
32 ipa_proto:init(),
33 % Create listening IPA socket
34 ipa_proto:start_listen(TcpServerPort, 1, Opts),
35 loop(#loop_data{ipa_stream_id = IpaStreamId}).
36
37% callback function to be called by IPA socket handler if it receives some data
38sccp_ipa_adapter_cb(S, IpaStreamID, DataBin, [ScrcPid]) ->
39 io:format("sccp_ipa_adapter_cb (Socket ~p, Stream ~p), passing data to SCRP~n", [S, IpaStreamID]),
40 % hand any incoming IPA message off into the SCCP stacks SCRC
41 gen_fsm:send_event(ScrcPid, sccp_scoc:make_prim('MTP', 'TRANSFER', indication, DataBin)).
42
43% callback function to be called by SCCP if it wants to transmit some data
44sccp_to_ipa_cb(#primitive{subsystem = 'MTP', gen_name = 'TRANSFER',
45 spec_name = request, parameters = DataBin}, [IpaPid, S, IpaStreamID]) ->
46 %ipa_proto:send(S, IpaStreamID, DataBin).
47 io:format("sccp_to_ipa_cb: Sending to ~p ~p/~p: ~p~n", [IpaPid, S,IpaStreamID, DataBin]),
48 IpaPid ! {ipa_send, S, IpaStreamID, DataBin}.
49
50loop(LoopData) ->
51 receive
52 {ipa_tcp_accept, S} ->
53 io:format("sccp_ipa_adapter: ipa_tcp_accept from ~p~n", [inet:peername(S)]),
54 % hand over the socket into the IPA stack
55 {ok, IpaPid} = ipa_proto:register_socket(S),
56 % Start the SCRC FSM for this virtual MTP link
57 ScrcMtpCb = {callback_fn, fun sccp_to_ipa_cb/2, [IpaPid, S, ?IPA_STREAM_ID_SCCP]},
58 {ok, ScrcPid} = sccp_scrc:start_link([{mtp_tx_action, ScrcMtpCb}]),
59 % Register an IPA stream for SCCP
60 ipa_proto:register_stream(S, ?IPA_STREAM_ID_SCCP,
61 {callback_fn, fun sccp_ipa_adapter_cb/4, [ScrcPid]}),
62 ipa_proto:unblock(S),
63 loop(LoopData);
64 % this code should later be moved into the actual MSC
65 {sccp, Prim} ->
66 io:format("sccp_user has received primitive ~p~n", [Prim]),
67 handle_sccp_prim(Prim),
68 loop(LoopData)
69 end.
70
71
72handle_sccp_prim(#primitive{subsystem = 'N', gen_name = 'CONNECT',
73 spec_name = indication, parameters = Params}) ->
74 %RespPrim = Prim#primitive{spec_name = response},
75 RespPrim = sccp_scoc:make_prim('N', 'CONNECT', response, []),
76 ScocPid = proplists:get_value(scoc_pid, Params),
77 gen_fsm:send_event(ScocPid, RespPrim);
78handle_sccp_prim(#primitive{}) ->
79 ok.