blob: f3e954c0ae37a89a30042aaa15b407e0abf77715 [file] [log] [blame]
Harald Welteb25d8782011-12-04 21:46:57 +01001% wrapper code between signerl/TCAP and osmo_ss7/SCCP
2
3-module(osmo_sccp_tcap).
4
5-copyright('Copyright (C) 2011 by Harald Welte <laforge@gnumonks.org>').
6-author('Harald Welte <laforge@gnumonks.org>').
7
8-behaviour(tcap_tco_server).
9
10-include_lib("osmo_ss7/include/osmo_util.hrl").
11-include_lib("osmo_ss7/include/sccp.hrl").
12-include_lib("TCAP/include/sccp.hrl").
13
14%% callbacks needed for gen_server behaviour
15-export([init/1, handle_call/3, handle_cast/2, handle_info/2,
16 terminate/2, code_change/3]).
17
18%% callbacks needed for tcap_tco_server
19-export([send_primitive/2, start_user/3]).
20
21%% our published API functions
22-export([start_link/1, stop/1]).
23
24start_link(SSN) ->
25 Ourname = list_to_atom("sccp_ssn" ++ integer_to_list(SSN)),
Harald Weltef6259f42013-06-10 13:39:51 +020026 gen_server:start_link({local, Ourname}, ?MODULE, [SSN],[{debug,trace}]).
Harald Welteb25d8782011-12-04 21:46:57 +010027
Harald Welteadff8752012-01-28 14:43:27 +010028init([SSN]) when is_integer(SSN) ->
29 init(SSN);
30init(SSN) when is_integer(SSN) ->
Harald Welteb25d8782011-12-04 21:46:57 +010031 ok = sccp_user:bind_ssn(SSN, undefined),
32 State = 1,
33 {ok, State}.
34
35handle_call(stop, _From, State) ->
36 {stop, shutdown, State}.
37
38handle_cast(Request, State) ->
39 error_logger:error_report(["unknown handle_cast",
Harald Welte31300012011-12-13 19:20:08 +010040 {module, ?MODULE},
Harald Welteb25d8782011-12-04 21:46:57 +010041 {request, Request}, {state, State}]),
42 {noreply, State}.
43
44osmo_prim2signerl(#primitive{subsystem='N', gen_name='UNITDATA',
45 spec_name=Spec, parameters=Msg}) ->
46 Params = Msg#sccp_msg.parameters,
47 CalledAddr = proplists:get_value(called_party_addr, Params),
48 CallingAddr = proplists:get_value(calling_party_addr, Params),
49 UserData = proplists:get_value(user_data, Params),
Harald Weltef6259f42013-06-10 13:39:51 +020050 % FIXME: doesn't always exist!
51 %{PC, Opt} = proplists:get_value(protocol_class, Params),
Harald Welteb25d8782011-12-04 21:46:57 +010052 Rec = #'N-UNITDATA'{calledAddress = CalledAddr,
53 callingAddress = CallingAddr,
54 sequenceControl = undefined,
55 returnOption = undefined,
56 importance = undefined,
57 userData = UserData},
58 {'N','UNITDATA', Spec, Rec}.
59
60% incoming message from
61handle_info({sccp, P= #primitive{subsystem='N',
62 gen_name='UNITDATA',
63 spec_name=indication}}, State) ->
64 % this is really ugly, we need to make TCO understand #primitives
65 gen_server:cast(self(), osmo_prim2signerl(P)),
66 {noreply, State};
Harald Weltef6259f42013-06-10 13:39:51 +020067handle_info({sccp, P= #primitive{subsystem='N',
68 gen_name='NOTICE',
69 spec_name=indication}}, State) ->
70 % this is really ugly, we need to make TCO understand #primitives
71 %gen_server:cast(self(), osmo_prim2signerl(P)),
72 error_logger:error_report(["unimplemented N-NOTICE.ind",
73 {module, ?MODULE},
74 {sccp, P}, {state, State}]),
75 {noreply, State};
Harald Welteb25d8782011-12-04 21:46:57 +010076handle_info(Info, State) ->
77 error_logger:error_report(["unknown handle_info",
Harald Welte31300012011-12-13 19:20:08 +010078 {module, ?MODULE},
Harald Welteb25d8782011-12-04 21:46:57 +010079 {info, Info}, {state, State}]),
80 {noreply, State}.
81
82terminate(Reason, State) ->
Harald Welte31300012011-12-13 19:20:08 +010083 io:format("osmo_sccp_tcap terminating with Reason ~w", [Reason]),
Harald Welteb25d8782011-12-04 21:46:57 +010084 ok.
85
86%% @spec (NSAP) -> ok
87%% NSAP = pid()
88%%
89%% @doc Stop an sccp server.
90%% <p>Closes an SCCP service access point (SAP).</p>
91%% <p><tt>NSAP</tt> is a pid returned from a previous call to
92%% <tt>start_link/2,3,7</tt>.</p>
93%%
94stop(NSAP) ->
95 gen_server:call(NSAP, stop).
96
97% UNITDATA.req
98
99% message coming down from TCO to SCCP, to be transmitted
100send_primitive({'N', 'UNITDATA', request, #'N-UNITDATA'{calledAddress = Called,
101 callingAddress = Calling,
102 sequenceControl = Seq,
103 returnOption = RetOpt,
104 importance = Imp,
105 userData = UserData}=Par}, State) ->
106 io:format("N-UNITDATA.req (~w,~w)~n", [Par, State]),
107 ClassOut = protocol_class(tcap_to_osmo, {Seq, RetOpt}),
108 UserDataOut = iolist_to_binary(UserData),
109 % Build an osmo_ss7 primitive
110 Prim = osmo_util:make_prim('N', 'UNITDATA', request,
111 [{called_party_addr, Called},
112 {calling_party_addr, Calling},
113 {protocol_class, ClassOut},
114 {user_data, UserDataOut}]),
115 % send primitive to SCCP code
116 gen_fsm:send_event(sccp_scrc, Prim).
117
118
119% TCAP has received the start of a new dialogue, return pid() of new user
120start_user({DhaPid, CcoPid}, DialogueID, State) ->
121 tcap_test_user:start_link({DhaPid,CcoPid}, DialogueID).
122
123
124% convert signerl format to osmo format
125protocol_class(tcap_to_osmo, {SeqIn, ReturnIn}) ->
126 case SeqIn of
127 true ->
128 Class = 1;
129 _ ->
130 Class = 0
131 end,
132 case ReturnIn of
133 true ->
134 {Class, 8};
135 _ ->
136 {Class, 0}
137 end.
138
139
140code_change(_OldVsn, State, _Extra) ->
141 {ok, State}.