re-structure SS7 code and MGW NAT code into separate modules

This repository now only contains the SS7 code
This commit is contained in:
Harald Welte 2011-02-07 20:48:41 +01:00
parent f2d112edec
commit 78474ae3e2
17 changed files with 518 additions and 650 deletions

18
ebin/osmo_ss7.app Normal file
View File

@ -0,0 +1,18 @@
{application, osmo_ss7,
[{description, "Osmocom SS7 code"},
{vsn, "1"},
{modules, [ osmo_util,
ipa_proto,
bssmap_codec,
isup_codec,
m2ua_codec,
mtp3_codec,
sccp_codec, sccp_scoc, sccp_scrc,
sctp_handler
]},
{registered, []},
{mod, {ipa_proto, []}},
{applications, []},
{env, [
]}
]}.

8
ebin/osmo_ss7.rel Normal file
View File

@ -0,0 +1,8 @@
{release,
{"osmo_ss7", "1"},
{erts, "5.8"},
[{kernel, "2.14"},
{stdlib, "1.17"},
{sasl, "2.1.9.2"},
{osmo_ss7, "1"}]
}.

263
include/bssmap.hrl Normal file
View File

@ -0,0 +1,263 @@
% From libosmocore gsm_08_08.h
% this is from GSM 03.03 CGI but is copied in GSM 08.08
% in § 3.2.2.27 for Cell Identifier List
-define(CELL_ID_WHOLE_GLOBAL, 0).
-define(CELL_ID_LAC_AND_CI, 1).
-define(CELL_ID_CI, 2).
-define(CELL_ID_NO_CELL, 3).
-define(CELL_ID_LAI_AND_LAC, 4).
-define(CELL_ID_LAC, 5).
-define(CELL_ID_BSS, 6).
-define(CELL_ID_UTRAN_PLMN_LAC_RNC, 8).
-define(CELL_ID_UTRAN_RNC, 9).
-define(CELL_ID_UTRAN_LAC_RNC, 10).
% GSM 08.06 § 6.3
-define(BSSAP_MSG_BSS_MANAGEMENT, 16#0).
-define(BSSAP_MSG_DTAP, 16#1).
% enum BSSMAP_MSG_TYPE {
-define(BSSMAP_MSG_RESERVED_0, 0).
% ASSIGNMENT MESSAGES
-define(BSSMAP_MSG_ASS_RQST, 1).
-define(BSSMAP_MSG_ASS_COMPL, 2).
-define(BSSMAP_MSG_ASS_FAILURE, 3).
% HANDOVER MESSAGES
-define(BSSMAP_MSG_HO_REQ, 16).
-define(BSSMAP_MSG_HO_REQUIRED, 17).
-define(BSSMAP_MSG_HO_REQ_ACK, 18).
-define(BSSMAP_MSG_HO_CMD, 19).
-define(BSSMAP_MSG_HO_COMPL, 20).
-define(BSSMAP_MSG_HO_SUCCEEDED, 21).
-define(BSSMAP_MSG_HO_FAILURE, 22).
-define(BSSMAP_MSG_HO_PERFORMED, 23).
-define(BSSMAP_MSG_HO_CAND_ENQ, 24).
-define(BSSMAP_MSG_HO_CAND_RESP, 25).
-define(BSSMAP_MSG_HO_REQUIRED_REJ, 26).
-define(BSSMAP_MSG_HO_DETECT, 27).
% RELEASE MESSAGES
-define(BSSMAP_MSG_CLEAR_CMD, 32).
-define(BSSMAP_MSG_CLEAR_COMPL, 33).
-define(BSSMAP_MSG_CLEAR_RQST, 34).
-define(BSSMAP_MSG_RESERVED_1, 35).
-define(BSSMAP_MSG_RESERVED_2, 36).
-define(BSSMAP_MSG_SAPI_N_REJ, 37).
-define(BSSMAP_MSG_CONFUSION, 38).
% OTHER CONNECTION RELATED MESSAGES
-define(BSSMAP_MSG_SUSPEND, 40).
-define(BSSMAP_MSG_RESUME, 41).
-define(BSSMAP_MSG_CONN_ORIENT_INFO, 42).
-define(BSSMAP_MSG_PERFORM_LOC_RQST, 43).
-define(BSSMAP_MSG_LSA_INFORMATION, 44).
-define(BSSMAP_MSG_PERFORM_LOC_RESPONSE, 45).
-define(BSSMAP_MSG_PERFORM_LOC_ABORT, 46).
-define(BSSMAP_MSG_COMMON_ID, 47).
% GENERAL MESSAGES
-define(BSSMAP_MSG_RESET, 48).
-define(BSSMAP_MSG_RESET_ACK, 49).
-define(BSSMAP_MSG_OVERLOAD, 50).
-define(BSSMAP_MSG_RESERVED_3, 51).
-define(BSSMAP_MSG_RESET_CIRC, 52).
-define(BSSMAP_MSG_RESET_CIRC_ACK, 53).
-define(BSSMAP_MSG_MSC_INVOKE_TRACE, 54).
-define(BSSMAP_MSG_BSS_INVOKE_TRACE, 55).
-define(BSSMAP_MSG_CONN_LESS_INFO, 58).
% TERRESTRIAL RESOURCE MESSAGES
-define(BSSMAP_MSG_BLOCK, 64).
-define(BSSMAP_MSG_BLOCKING_ACK, 65).
-define(BSSMAP_MSG_UNBLOCK, 66).
-define(BSSMAP_MSG_UNBLOCKING_ACK, 67).
-define(BSSMAP_MSG_CIRC_GROUP_BLOCK, 68).
-define(BSSMAP_MSG_CIRC_GROUP_BLOCKING_ACK, 69).
-define(BSSMAP_MSG_CIRC_GROUP_UNBLOCK, 70).
-define(BSSMAP_MSG_CIRC_GROUP_UNBLOCKING_ACK, 71).
-define(BSSMAP_MSG_UNEQUIPPED_CIRCUIT, 72).
-define(BSSMAP_MSG_CHANGE_CIRCUIT, 78).
-define(BSSMAP_MSG_CHANGE_CIRCUIT_ACK, 79).
% RADIO RESOURCE MESSAGES
-define(BSSMAP_MSG_RESOURCE_RQST, 80).
-define(BSSMAP_MSG_RESOURCE_INDICATION, 81).
-define(BSSMAP_MSG_PAGING, 82).
-define(BSSMAP_MSG_CIPHER_MODE_CMD, 83).
-define(BSSMAP_MSG_CLASSMARK_UPDATE, 84).
-define(BSSMAP_MSG_CIPHER_MODE_COMPL, 85).
-define(BSSMAP_MSG_QUEUING_INDICATION, 86).
-define(BSSMAP_MSG_COMPL_LAYER_3, 87).
-define(BSSMAP_MSG_CLASSMARK_RQST, 88).
-define(BSSMAP_MSG_CIPHER_MODE_REJ, 89).
-define(BSSMAP_MSG_LOAD_INDICATION, 90).
% VGCS/VBS
-define(BSSMAP_MSG_VGCS_VBS_SETUP, 4).
-define(BSSMAP_MSG_VGCS_VBS_SETUP_ACK, 5).
-define(BSSMAP_MSG_VGCS_VBS_SETUP_REFUSE, 6).
-define(BSSMAP_MSG_VGCS_VBS_ASS_RQST, 7).
-define(BSSMAP_MSG_VGCS_VBS_ASS_RESULT, 28).
-define(BSSMAP_MSG_VGCS_VBS_ASS_FAILURE, 29).
-define(BSSMAP_MSG_VGCS_VBS_QUEUING_INDICATION, 30).
-define(BSSMAP_MSG_UPLINK_RQST, 31).
-define(BSSMAP_MSG_UPLINK_RQST_ACK, 39).
-define(BSSMAP_MSG_UPLINK_RQST_CONFIRMATION, 73).
-define(BSSMAP_MSG_UPLINK_RELEASE_INDICATION, 74).
-define(BSSMAP_MSG_UPLINK_REJ_CMD, 75).
-define(BSSMAP_MSG_UPLINK_RELEASE_CMD, 76).
-define(BSSMAP_MSG_UPLINK_SEIZED_CMD, 77).
% enum BSSMAP_IE_CODING {
-define(BSSMAP_IE_CIRC_ID_CODE, 1). % TV16
%-define(BSSMAP_IE_RESERVED_0, 2).
-define(BSSMAP_IE_RES_AVAIL, 3). % TVf
-define(BSSMAP_IE_CAUSE, 4). % TLV
-define(BSSMAP_IE_CELL_ID, 5). % TLV
-define(BSSMAP_IE_PRIORITY, 6). % TLV
-define(BSSMAP_IE_L3_HDR_INFO, 7). % TLV
-define(BSSMAP_IE_IMSI, 8). % TLV
-define(BSSMAP_IE_TMSI, 9). % TLV
-define(BSSMAP_IE_ENCR_INFO, 10). % TLV
-define(BSSMAP_IE_CHANNEL_TYPE, 11). % TLV
-define(BSSMAP_IE_PERIODICITY, 12). % TV
-define(BSSMAP_IE_EXTD_RES_IND, 13). % TV
-define(BSSMAP_IE_NUMBER_OF_MSS, 14). % TV
%-define(BSSMAP_IE_RESERVED_1, 15).
%-define(BSSMAP_IE_RESERVED_2, 16).
%-define(BSSMAP_IE_RESERVED_3, 17).
-define(BSSMAP_IE_CM_INFO_T2, 18). % TLV
-define(BSSMAP_IE_CM_INFO_T3, 19). % TLV
-define(BSSMAP_IE_INTERF_BAND_TO_USE, 20). % TV
-define(BSSMAP_IE_RR_CAUSE, 21). % TV
%-define(BSSMAP_IE_RESERVED_4, 22).
-define(BSSMAP_IE_L3_INFO, 23). % TLV
-define(BSSMAP_IE_DLCI, 24). % TV
-define(BSSMAP_IE_DOWNLINK_DTX_FLAG, 25). % TV
-define(BSSMAP_IE_CELL_ID_LIST, 26). % TLV
-define(BSSMAP_IE_RESPONSE_RQST, 27). % TV
-define(BSSMAP_IE_RES_IND_METHOD, 28). % TV
-define(BSSMAP_IE_CM_INFO_T1, 29). % TV
-define(BSSMAP_IE_CIRC_ID_CODE_LIST, 30). % TLV
-define(BSSMAP_IE_DIAGNOSTIC, 31). % TLV
-define(BSSMAP_IE_L3_MSG_CONTENTS, 32). % TLV
-define(BSSMAP_IE_CHOSEN_CHANNEL, 33). % TV
-define(BSSMAP_IE_TOT_RES_ACCESS, 34). % TVf
-define(BSSMAP_IE_CIPH_RESP_MODE, 35). % TV
-define(BSSMAP_IE_CHANNEL_NEEDED, 36). % TV
-define(BSSMAP_IE_TRACE_TYPE, 37). % TV
-define(BSSMAP_IE_TRIGGERID, 38). % TLV
-define(BSSMAP_IE_TRACE_REFERENCE, 39). % TV
-define(BSSMAP_IE_TRANSACTIONID, 40). % TLV
-define(BSSMAP_IE_MOBILE_IDENTITY, 41). % TLV
-define(BSSMAP_IE_OMCID, 42). % TLV
-define(BSSMAP_IE_FORWARD_INDICATOR, 43). % TV
-define(BSSMAP_IE_CHOSEN_ENCR_ALG, 44). % TV
-define(BSSMAP_IE_CIRCUIT_POOL, 45). % TV
-define(BSSMAP_IE_CIRCUIT_POOL_LIST, 46). % TLV
-define(BSSMAP_IE_TIME_INDICATION, 47). % TV
-define(BSSMAP_IE_RESOURCE_SITUATION, 48). % TLV
-define(BSSMAP_IE_CUR_CHAN_TYPE_1, 49). % TV
-define(BSSMAP_IE_QUEUEING_IND, 50). % TV
-define(BSSMAP_IE_SPEECH_VERSION, 64). % TV
-define(BSSMAP_IE_ASS_REQUIREMENT, 51). % TV
-define(BSSMAP_IE_TALKER_FLAG, 53). % T
-define(BSSMAP_IE_CONN_REL_RQSTED, 54). % T
-define(BSSMAP_IE_GROUP_CALL_REFERENCE, 55). % TLV
-define(BSSMAP_IE_EMLPP_PRIORITY, 56). % TV
-define(BSSMAP_IE_CONFIG_EVO_INDI, 57). % TV
-define(BSSMAP_IE_OLD_TO_NEW_BSS_INFO, 58). % TLV
-define(BSSMAP_IE_LSA_IDENTIFIER, 59). % TLV
-define(BSSMAP_IE_LSA_IDENTIFIER_LIST, 60). % TLV
-define(BSSMAP_IE_LSA_INFORMATION, 61). % TLV
-define(BSSMAP_IE_LCS_QOS, 62). % TLV
-define(BSSMAP_IE_LSA_ACCESS_CTRL_SUPPR, 63). % TV
-define(BSSMAP_IE_LCS_PRIORITY, 67). % TLV
-define(BSSMAP_IE_LOCATION_TYPE, 68). % TLV
-define(BSSMAP_IE_LOCATION_ESTIMATE, 69). % TLV
-define(BSSMAP_IE_POSITIONING_DATA, 70). % TLV
-define(BSSMAP_IE_LCS_CAUSE, 71). % TLV
-define(BSSMAP_IE_LCS_CLIENT_TYPE, 72). % TLV
-define(BSSMAP_IE_APDU, 73). % TLV
-define(BSSMAP_IE_NETWORK_ELEMENT_ID, 74). % TLV
-define(BSSMAP_IE_GPS_ASSISTANCE_DATA, 75). % TLV
-define(BSSMAP_IE_DECIPHERING_KEYS, 76). % TLV
-define(BSSMAP_IE_RETURN_ERROR_RQST, 77). % TLV
-define(BSSMAP_IE_RETURN_ERROR_CAUSE, 78). % TLV
-define(BSSMAP_IE_SEGMENTATION, 79). % TLV
-define(BSSMAP_IE_SERVICE_HANDOVER, 80). % TLV
-define(BSSMAP_IE_SRC_TGT_RNC_TRANSP_UMTS, 81). % TLV
-define(BSSMAP_IE_SRC_TGT_RNC_TRANSP_CDMA2K, 82). % TLV
%-define(BSSMAP_IE_RESERVED_5, 65).
%-define(BSSMAP_IE_RESERVED_6, 66).
% enum gsm0808_cause {
-define(BSSMAP_CAUSE_RIF_MSG_FAILURE, 0).
-define(BSSMAP_CAUSE_RIF_FAILURE, 1).
-define(BSSMAP_CAUSE_UPLINK_QUALITY, 2).
-define(BSSMAP_CAUSE_UPLINK_STRENGTH, 3).
-define(BSSMAP_CAUSE_DOWNLINK_QUALITY, 4).
-define(BSSMAP_CAUSE_DOWNLINK_STRENGTH, 5).
-define(BSSMAP_CAUSE_DISTANCE, 6).
-define(BSSMAP_CAUSE_O_AND_M_INTERVENTION, 7).
-define(BSSMAP_CAUSE_RESPONSE_TO_MSC_INVOCATION, 8).
-define(BSSMAP_CAUSE_CALL_CONTROL, 9).
-define(BSSMAP_CAUSE_RIF_FAILURE_REVERSION, 10).
-define(BSSMAP_CAUSE_HO_SUCCESSFUL, 11).
-define(BSSMAP_CAUSE_BETTER_CELL, 12).
-define(BSSMAP_CAUSE_DIRECTED_RETRY, 13).
-define(BSSMAP_CAUSE_JOINED_GROUP_CALL_CHANNEL, 14).
-define(BSSMAP_CAUSE_TRAFFIC, 15).
-define(BSSMAP_CAUSE_EQUIPMENT_FAILURE, 32).
-define(BSSMAP_CAUSE_NO_RR_AVAILABLE, 33).
-define(BSSMAP_CAUSE_RQSTED_TERR_RES_UNAVAIL, 34).
-define(BSSMAP_CAUSE_CCCH_OVERLOAD, 35).
-define(BSSMAP_CAUSE_PROCESSOR_OVERLOAD, 36).
-define(BSSMAP_CAUSE_BSS_NOT_EQUIPPED, 37).
-define(BSSMAP_CAUSE_MS_NOT_EQUIPPED, 38).
-define(BSSMAP_CAUSE_INVALID_CELL, 39).
-define(BSSMAP_CAUSE_TRAFFIC_LOAD, 40).
-define(BSSMAP_CAUSE_PREEMPTION, 41).
-define(BSSMAP_CAUSE_RQSTED_TRANSC_RA_UNAVAIL, 48).
-define(BSSMAP_CAUSE_CIRCUIT_POOL_MISMATCH, 49).
-define(BSSMAP_CAUSE_SWITCH_CIRCUIT_POOL, 50).
-define(BSSMAP_CAUSE_RQSTED_SPEECH_V_UNAVAIL, 51).
-define(BSSMAP_CAUSE_LSA_NOT_ALLOWED, 52).
-define(BSSMAP_CAUSE_CIPH_ALG_NOT_SUPPORTED, 64).
-define(BSSMAP_CAUSE_TERR_CIRC_ALLOCATED, 80).
-define(BSSMAP_CAUSE_INV_MSG_CONTENTS, 81).
-define(BSSMAP_CAUSE_IE_OR_FIELD_MISSING, 82).
-define(BSSMAP_CAUSE_INCORRECT_VALUE, 83).
-define(BSSMAP_CAUSE_UNKNOWN_MSG_TYPE, 84).
-define(BSSMAP_CAUSE_UNKNOWN_IE, 85).
-define(BSSMAP_CAUSE_PROT_ERR_BSS_AND_MSC, 96).
% GSM 08.08 3.2.2.11 Channel Type
% enum gsm0808_chan_indicator {
-define(BSSMAP_CHAN_SPEECH, 1).
-define(BSSMAP_CHAN_DATA, 2).
-define(BSSMAP_CHAN_SIGN, 3).
% enum gsm0808_chan_rate_type_data {
-define(BSSMAP_DATA_FULL_BM, 16#8).
-define(BSSMAP_DATA_HALF_LM, 16#9).
-define(BSSMAP_DATA_FULL_RPREF, 16#a).
-define(BSSMAP_DATA_HALF_PREF, 16#b).
-define(BSSMAP_DATA_FULL_PREF_NO_CHANGE, 16#1a).
-define(BSSMAP_DATA_HALF_PREF_NO_CHANGE, 16#1b).
-define(BSSMAP_DATA_MULTI_MASK, 16#20).
-define(BSSMAP_DATA_MULTI_MASK_NO_CHANGE, 16#30).
% enum gsm0808_chan_rate_type_speech {
-define(BSSMAP_SPEECH_FULL_BM, 16#8).
-define(BSSMAP_SPEECH_HALF_LM, 16#9).
-define(BSSMAP_SPEECH_FULL_PREF, 16#a).
-define(BSSMAP_SPEECH_HALF_PREF, 16#b).
-define(BSSMAP_SPEECH_FULL_PREF_NO_CHANGE, 16#1a).
-define(BSSMAP_SPEECH_HALF_PREF_NO_CHANGE, 16#1b).
-define(BSSMAP_SPEECH_PERM, 16#f).
-define(BSSMAP_SPEECH_PERM_NO_CHANGE, 16#1f).
% enum gsm0808_permitted_speech {
-define(BSSMAP_PERM_FR1, 16#01).
-define(BSSMAP_PERM_FR2, 16#11).
-define(BSSMAP_PERM_FR3, 16#21).
% BSSMAP_PERM_HR1 = BSSMAP_PERM_FR1 | 16#4,
% BSSMAP_PERM_HR2 = BSSMAP_PERM_FR2 | 16#4,
% BSSMAP_PERM_HR3 = BSSMAP_PERM_FR3 | 16#4,
%};

View File

@ -1,29 +0,0 @@
{application, mgw_nat,
[{description, "Media Gateway NAT"},
{vsn, "1"},
{modules, [mgw_nat_app, mgw_nat_sup, mgw_nat_usr, mgw_nat]},
{mod, {mgw_nat_app, []}},
{env, [
% SCCP static rewrite rules
{sccp_rewrite_tbl, [
{ 12340000, 98760000, "HLR" },
{ 12340001, 98760001, "VLR" }
]},
% SCCP source masquerading pool
{sccp_masq_gt_base, 12340000},
{sccp_masq_gt_max, 9999},
% ISUP rewrite
{msrn_pfx_msc, 35489099},
{msrn_pfx_stp, 6392994200},
{intern_pfx, 63},
% SCTP / IP config
{msc_local_ip, any},
{msc_local_port, 2904},
{msc_remote_ip, {172,16,1,81}},
{stp_remote_ip, {172,16,249,20}},
{stp_remote_port, 2904}
]}
]}.

1
rebar.config Normal file
View File

@ -0,0 +1 @@
{sub_dirs, ["rel"]}.

31
rel/reltool.config Normal file
View File

@ -0,0 +1,31 @@
{sys, [
{lib_dirs, ["../../"]},
{rel, "osmo", "1",
[
kernel,
stdlib,
sasl
]},
{rel, "start_clean", "",
[
kernel,
stdlib
]},
{boot_rel, "osmo"},
{profile, embedded},
{excl_sys_filters, ["^bin/.*",
"^erts.*/bin/(dialyzer|typer)"]},
{app, sasl, [{incl_cond, include}]},
{app, osmo_ss7, [{incl_cond, include}]}
]}.
{target_dir, "osmo"}.
{overlay, [
{mkdir, "log/sasl"},
{copy, "files/erl", "{{erts_vsn}}/bin/erl"},
{copy, "files/nodetool", "{{erts_vsn}}/bin/nodetool"},
{copy, "files/osmo", "bin/osmo"},
{copy, "files/app.config", "etc/app.config"},
{copy, "files/vm.args", "etc/vm.args"}
]}.

197
src/bssmap_codec.erl Normal file
View File

@ -0,0 +1,197 @@
% GSM TS 08.08 / 3GPP TS 48.008 BSSMAP
% (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(bssmap_codec).
-author('Harald Welte <laforge@gnumonks.org>').
-include("bssmap.hrl").
-export([parse_bssmap_msg/1, encode_bssmap_msg/1]).
parse_bssmap_msg(<<MsgType:8, Remain/binary>>) ->
parse_bssmap_msgt(MsgType, Remain).
parse_bssmap_msgt(MsgType, Msg) when is_integer(MsgType), is_binary(Msg) ->
IeList = parse_ies(Msg, []),
{bssmap_msg, MsgType, IeList}.
parse_ies(<<>>, ParsedIeList) ->
ParsedIeList;
parse_ies(Msg, ParsedIeList) when is_binary(Msg) ->
CurIe = binary:first(Msg),
% Parse current IE and append it to list of Parsed IEs
case is_tv_ie(CurIe) of
true ->
Res = parse_ie_tv(CurIe, Msg);
false ->
Res = parse_ie(CurIe, Msg)
end,
{ok, BytesConsumed, ParsedIe} = Res,
{CurIe, Payload} = ParsedIe,
DecodedIe = decode_ie(CurIe, Payload),
ParsedIeList1 = ParsedIeList ++ [DecodedIe],
%ParsedIeList1 = ParsedIeList ++ [ParsedIe],
RemainMsg = binary:part(Msg, BytesConsumed, byte_size(Msg)-BytesConsumed),
parse_ies(RemainMsg, ParsedIeList1).
% check if this element is of TV type
is_tv_ie(T) when
T == ?BSSMAP_IE_NUMBER_OF_MSS;
T == ?BSSMAP_IE_PERIODICITY;
T == ?BSSMAP_IE_EXTD_RES_IND;
T == ?BSSMAP_IE_INTERF_BAND_TO_USE;
T == ?BSSMAP_IE_RR_CAUSE;
T == ?BSSMAP_IE_DLCI;
T == ?BSSMAP_IE_DOWNLINK_DTX_FLAG;
T == ?BSSMAP_IE_RESPONSE_RQST;
T == ?BSSMAP_IE_RES_IND_METHOD;
T == ?BSSMAP_IE_CM_INFO_T1;
T == ?BSSMAP_IE_CHOSEN_CHANNEL;
T == ?BSSMAP_IE_CIPH_RESP_MODE;
T == ?BSSMAP_IE_TRACE_TYPE;
T == ?BSSMAP_IE_TRACE_REFERENCE;
T == ?BSSMAP_IE_FORWARD_INDICATOR;
T == ?BSSMAP_IE_CHOSEN_ENCR_ALG;
T == ?BSSMAP_IE_CIRCUIT_POOL;
T == ?BSSMAP_IE_TIME_INDICATION;
T == ?BSSMAP_IE_CUR_CHAN_TYPE_1;
T == ?BSSMAP_IE_QUEUEING_IND;
T == ?BSSMAP_IE_SPEECH_VERSION;
T == ?BSSMAP_IE_ASS_REQUIREMENT;
T == ?BSSMAP_IE_EMLPP_PRIORITY;
T == ?BSSMAP_IE_CONFIG_EVO_INDI;
T == ?BSSMAP_IE_LSA_ACCESS_CTRL_SUPPR ->
true;
is_tv_ie(_T) ->
false.
% Parser for any non-TLV and non-TV IEs
parse_ie(?BSSMAP_IE_CIRC_ID_CODE, Msg) ->
<<?BSSMAP_IE_CIRC_ID_CODE:8, Cic:16/big>> = Msg,
{ok, 3, {?BSSMAP_IE_CIRC_ID_CODE, Cic}};
parse_ie(?BSSMAP_IE_CONN_REL_RQSTED, Msg) ->
<<?BSSMAP_IE_CONN_REL_RQSTED:8>> = Msg,
{ok, 1, {?BSSMAP_IE_CONN_REL_RQSTED, 1}};
parse_ie(?BSSMAP_IE_RES_AVAIL, Msg) ->
<<?BSSMAP_IE_RES_AVAIL:8, ResAvail:8/binary>> = Msg,
{ok, 9, {?BSSMAP_IE_RES_AVAIL, ResAvail}};
parse_ie(?BSSMAP_IE_TOT_RES_ACCESS, Msg) ->
<<?BSSMAP_IE_TOT_RES_ACCESS:8, ResAvail:4/binary>> = Msg,
{ok, 5, {?BSSMAP_IE_TOT_RES_ACCESS, ResAvail}};
parse_ie(?BSSMAP_IE_TALKER_FLAG, Msg) ->
<<?BSSMAP_IE_TALKER_FLAG:8>> = Msg,
{ok, 1, {?BSSMAP_IE_TALKER_FLAG, 1}};
% Default: Parser for TLV IE
parse_ie(MsgType, Msg) ->
<<MsgType:8, Length:8, Value:Length/binary, _/binary>> = Msg,
{ok, 2+Length, {MsgType, Value}}.
% Parser for simple Tag-Value IE
parse_ie_tv(IeType, Msg) ->
<<IeType:8, Par:8>> = Msg,
{ok, 2, {IeType, Par}}.
% FIXME
encode_bssmap_msg(_) ->
ok.
decode_ie(?BSSMAP_IE_CIRC_ID_CODE, <<Pcm:11, Ts:5>>) ->
{circuit_id, Pcm, Ts};
decode_ie(?BSSMAP_IE_IMSI, Remain) ->
{imsi, bin_bcd2str(Remain)};
decode_ie(?BSSMAP_IE_TMSI, <<Tmsi:32>>) ->
{tmsi, Tmsi};
decode_ie(?BSSMAP_IE_L3_HDR_INFO, <<Pdisc:8, Tid:8>>) ->
{l3_hdr_info, Pdisc, Tid};
decode_ie(?BSSMAP_IE_ENCR_INFO, <<Algos:8, Key/binary>>) ->
{encr_info, Algos, Key};
decode_ie(?BSSMAP_IE_CHANNEL_TYPE, <<_:4, Spdi:4, RateType:8, Remain/binary>>) ->
{chan_type, Spdi, RateType, Remain};
decode_ie(?BSSMAP_IE_EXTD_RES_IND, Ri) ->
<<_:6, Sm:1, Tarr:1>> = <<Ri>>,
{extended_ri, Sm, Tarr};
decode_ie(?BSSMAP_IE_TOT_RES_ACCESS, <<NumFr:16/big, NumHr:16/big>>) ->
{tot_res_access, NumFr, NumHr};
decode_ie(?BSSMAP_IE_CELL_ID, <<_Spare:4, Discr:4, Remain/binary>>) ->
{cell_id, decode_cid_ie(Discr, Remain)};
decode_ie(?BSSMAP_IE_PRIORITY, <<_:1, Pci:1, Prio:4, Qa:1, Pvi:1>>) ->
{priority, Pci, Prio, Qa, Pvi};
decode_ie(?BSSMAP_IE_CELL_ID_LIST, <<_Spare:4, Discr:4, Remain/binary>>) ->
{cell_id_list, decode_cid_list(Discr, Remain, [])};
decode_ie(?BSSMAP_IE_DIAGNOSTIC, <<ErrPtr:8, _:4, BitPtr:4, MsgRecv/binary>>) ->
{diagnostic, ErrPtr, BitPtr, MsgRecv};
decode_ie(?BSSMAP_IE_CHOSEN_CHANNEL, Int) ->
<<Mode:4, Chan:4>> = <<Int:8>>,
{chosen_channel, Mode, Chan};
decode_ie(?BSSMAP_IE_MOBILE_IDENTITY, Data) ->
% FIXME
fixme;
% Default: don't decode
decode_ie(IeI, Data) ->
{IeI, Data}.
decode_cid_ie(?CELL_ID_WHOLE_GLOBAL, Remain) ->
<<Mcc2:4, Mcc1:4, Mnc3:4, Mcc3:4, Mnc2:4, Mnc1:4, Lac:16/big, Ci:16/big>> = Remain,
[{mcc, [Mcc1, Mcc2, Mcc3]}, {mnc, [Mnc1, Mnc2, Mnc3]}, {lac, Lac}, {cid, Ci}];
decode_cid_ie(?CELL_ID_LAC_AND_CI, Remain) ->
<<Lac:16/big, Ci:16/big>> = Remain,
[{lac, Lac}, {cid, Ci}];
decode_cid_ie(?CELL_ID_CI, Remain) ->
<<Ci:16/big>> = Remain,
[{cid, Ci}];
decode_cid_ie(?CELL_ID_NO_CELL, _Remain) ->
[];
decode_cid_ie(?CELL_ID_UTRAN_PLMN_LAC_RNC, Remain) ->
<<Mcc2:4, Mcc1:4, Mnc3:4, Mcc3:4, Mnc2:4, Mnc1:4, Lac:16/big, Rnc:16/big>> = Remain,
[{mcc, [Mcc1, Mcc2, Mcc3]}, {mnc, [Mnc1, Mnc2, Mnc3]}, {lac, Lac}, {rnc_id, Rnc}];
decode_cid_ie(?CELL_ID_UTRAN_RNC, Remain) ->
<<Rnc:16/big>> = Remain,
[{rnc_id, Rnc}];
decode_cid_ie(?CELL_ID_UTRAN_LAC_RNC, Remain) ->
<<Lac:16/big, Rnc:16/big>> = Remain,
[{lac, Lac}, {rnc_id, Rnc}].
decode_cid_list(Discr, Data, List) ->
case Discr of
?CELL_ID_WHOLE_GLOBAL -> Len = 7;
?CELL_ID_LAC_AND_CI -> Len = 4;
?CELL_ID_CI -> Len = 2;
?CELL_ID_NO_CELL -> Len = 0;
?CELL_ID_UTRAN_PLMN_LAC_RNC -> Len = 7;
?CELL_ID_UTRAN_RNC -> Len = 2;
?CELL_ID_UTRAN_LAC_RNC -> Len = 4
end,
<<Subset:Len/binary, Remain/binary>> = Data,
Elem = {cell_id, decode_cid_ie(Discr, Subset)},
decode_cid_list(Discr, Remain, List ++ [Elem]).
bin_bcd2str(BcdBin) when is_binary(BcdBin) ->
bin_bcd2str(BcdBin, []).
bin_bcd2str(<<>>, List) ->
List;
bin_bcd2str(BcdBin, List) ->
<<Nibble:4, Remain/bitstring>> = BcdBin,
Char = "0" + Nibble,
bin_bcd2str(Remain, List ++ [Char]).

View File

@ -1,294 +0,0 @@
%
% (C) 2011 by Harald Welte <laforge@gnumonks.org>
% (C) 2011 OnWaves
%
% 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(mgw_nat).
-author("Harald Welte <laforge@gnumonks.org>").
-export([mangle_rx_data/3]).
%-include_lib("kernel/include/inet.hrl").
%-include_lib("kernel/include/inet_sctp.hrl").
-include("m2ua.hrl").
-include("mtp3.hrl").
-include("isup.hrl").
-include("sccp.hrl").
% mangle the received data
mangle_rx_data(L, From, Data) when is_binary(Data) ->
{ok, M2ua} = m2ua_codec:parse_m2ua_msg(Data),
%io:format("M2UA Decode: ~p~n", [M2ua]),
case M2ua of
#m2ua_msg{msg_class = ?M2UA_MSGC_MAUP,
msg_type = ?M2UA_MAUP_MSGT_DATA} ->
M2ua_out = mangle_rx_m2ua_maup(L, From, M2ua);
#m2ua_msg{} ->
% simply pass it along unmodified
M2ua_out = M2ua
end,
% re-encode the data
%io:format("M2UA Encode: ~p~n", [M2ua_out]),
m2ua_codec:encode_m2ua_msg(M2ua_out).
% mangle the received M2UA
mangle_rx_m2ua_maup(L, From, M2ua = #m2ua_msg{parameters = Params}) ->
{_Len, M2uaPayload} = proplists:get_value(16#300, Params),
Mtp3 = mtp3_codec:parse_mtp3_msg(M2uaPayload),
%io:format("MTP3 Decode: ~p~n", [Mtp3]),
Mtp3_out = mangle_rx_mtp3(L, From, Mtp3),
%io:format("MTP3 Encode: ~p~n", [Mtp3_out]),
Mtp3OutBin = mtp3_codec:encode_mtp3_msg(Mtp3_out),
Params2 = proplists:delete(16#300, Params),
ParamsNew = Params2 ++ [{16#300, {byte_size(Mtp3OutBin), Mtp3OutBin}}],
% return mangled parsed m2ua msg
M2ua#m2ua_msg{parameters = ParamsNew}.
% mangle the MTP3 payload
mangle_rx_mtp3(L, From, Mtp3 = #mtp3_msg{service_ind = Service}) ->
mangle_rx_mtp3_serv(L, From, Service, Mtp3).
% mangle the ISUP content
mangle_rx_mtp3_serv(_L, From, ?MTP3_SERV_ISUP, Mtp3 = #mtp3_msg{payload = Payload}) ->
io:format("ISUP In: ~p~n", [Payload]),
Isup = isup_codec:parse_isup_msg(Payload),
io:format("ISUP Decode: ~p~n", [Isup]),
% FIXME
IsupMangled = mangle_rx_isup(From, Isup#isup_msg.msg_type, Isup),
if IsupMangled == Isup ->
Mtp3;
true ->
io:format("ISUP Encode In: ~p~n", [IsupMangled]),
Payload_out = isup_codec:encode_isup_msg(IsupMangled),
io:format("ISUP Encode Out: ~p~n", [Payload_out]),
% return modified MTP3 payload
Mtp3#mtp3_msg{payload = Payload_out}
end;
% mangle the SCCP content
mangle_rx_mtp3_serv(_L, From, ?MTP3_SERV_SCCP, Mtp3 = #mtp3_msg{payload = Payload}) ->
io:format("SCCP In: ~p~n", [Payload]),
{ok, Sccp} = sccp_codec:parse_sccp_msg(Payload),
io:format("SCCP Decode: ~p~n", [Sccp]),
SccpMangled = mangle_rx_sccp(From, Sccp#sccp_msg.msg_type, Sccp),
SccpMasqued = sccp_masq:sccp_masq_msg(From, SccpMangled#sccp_msg.msg_type,
SccpMangled),
if SccpMasqued == Sccp ->
Mtp3;
true ->
io:format("SCCP Encode In: ~p~n", [SccpMasqued]),
Payload_out = sccp_codec:encode_sccp_msg(SccpMasqued),
io:format("SCCP Encode Out: ~p~n", [Payload_out]),
% return modified MTP3 payload
Mtp3#mtp3_msg{payload = Payload_out}
end;
% default: do nothing
mangle_rx_mtp3_serv(_L, _From, _, Mtp3) ->
Mtp3.
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
% Actual mangling of the decoded SCCP messages
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
% iterate over list of rewrite tuples and apply translation if there is a match
do_sccp_gt_rewrite(GT, _From, []) ->
GT;
do_sccp_gt_rewrite(GT = #global_title{phone_number = PhoneNum}, from_stp, [Head|List]) ->
{MscSide, StpSide, Comment} = Head,
if PhoneNum == StpSide ->
NewPhoneNum = MscSide,
io:format("SCCP STP->MSC rewrite (~p) ~p -> ~p~n",
[Comment, PhoneNum, NewPhoneNum]),
GT#global_title{phone_number = NewPhoneNum};
true ->
do_sccp_gt_rewrite(GT, from_stp, List)
end;
do_sccp_gt_rewrite(GT = #global_title{phone_number = PhoneNum}, from_msc, [Head|List]) ->
{MscSide, StpSide, Comment} = Head,
if PhoneNum == MscSide ->
NewPhoneNum = StpSide,
io:format("SCCP MSC->STP rewrite (~p) ~p -> ~p~n",
[Comment, PhoneNum, NewPhoneNum]),
GT#global_title{phone_number = NewPhoneNum};
true ->
do_sccp_gt_rewrite(GT, from_msc, List)
end.
% mangle called address
mangle_rx_called(from_stp, Addr = #sccp_addr{global_title = GT}) ->
{ok, RewriteTbl} = application:get_env(sccp_rewrite_tbl),
GTout = do_sccp_gt_rewrite(GT, from_stp, RewriteTbl),
Addr#sccp_addr{global_title = GTout};
mangle_rx_called(_From, Addr) ->
Addr.
% mangle calling address
mangle_rx_calling(from_msc, Addr = #sccp_addr{global_title = GT}) ->
{ok, RewriteTbl} = application:get_env(sccp_rewrite_tbl),
GTout = do_sccp_gt_rewrite(GT, from_msc, RewriteTbl),
Addr#sccp_addr{global_title = GTout};
mangle_rx_calling(_From, Addr) ->
Addr.
mangle_rx_sccp(From, ?SCCP_MSGT_UDT, Msg = #sccp_msg{parameters = Opts}) ->
CalledParty = proplists:get_value(called_party_addr, Opts),
CalledPartyNew = mangle_rx_called(From, CalledParty),
CallingParty = proplists:get_value(calling_party_addr, Opts),
CallingPartyNew = mangle_rx_calling(From, CallingParty),
Opts1 = lists:keyreplace(called_party_addr, 1, Opts,
{called_party_addr, CalledPartyNew}),
Opts2 = lists:keyreplace(calling_party_addr, 1, Opts1,
{calling_party_addr, CallingPartyNew}),
Msg#sccp_msg{parameters = Opts2};
mangle_rx_sccp(_From, _MsgType, Msg) ->
Msg.
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
% Actual mangling of the decoded ISUP messages
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
% iterate over list of parameters and call mangle_rx_isup_par() for each one
mangle_rx_isup_params(_From, _MsgType, _Msg, ParListOut, []) ->
ParListOut;
mangle_rx_isup_params(From, MsgType, Msg, ParListOut, [Par|ParList]) ->
ParOut = mangle_rx_isup_par(From, MsgType, Msg, Par),
mangle_rx_isup_params(From, MsgType, Msg, ParListOut++[ParOut], ParList).
% manipulate phone numbers
mangle_rx_isup_par(From, MsgType, _Msg, {ParType, ParBody}) when
ParType == ?ISUP_PAR_CALLED_P_NUM;
ParType == ?ISUP_PAR_CONNECTED_NUM;
ParType == ?ISUP_PAR_CALLING_P_NUM ->
NewParBody = mangle_isup_number(From, MsgType, ParType, ParBody),
{ParType, NewParBody};
% defauly case: do not mangle this parameter
mangle_rx_isup_par(_From, _MsgType, _Msg, Par) ->
Par.
% mangle an incoming ISUP message
mangle_rx_isup(From, MsgType, Msg = #isup_msg{parameters = Params}) ->
ParamsOut = mangle_rx_isup_params(From, MsgType, Msg, [], Params),
% return message with modified parameter list
Msg#isup_msg{parameters = ParamsOut}.
% STP->MSC: Mangle a Party Number in IAM
mangle_isup_number(from_stp, ?ISUP_MSGT_IAM, NumType, PartyNum) ->
case NumType of
?ISUP_PAR_CALLED_P_NUM ->
% First convert to international number, if it is national
Num1 = isup_party_internationalize(PartyNum,
application:get_env(intern_pfx)),
io:format("IAM MSRN rewrite (STP->MSC): "),
isup_party_replace_prefix(Num1,
application:get_env(msrn_pfx_stp),
application:get_env(msrn_pfx_msc));
_ ->
PartyNum
end;
% MSC->STP: Mangle connected number in response to IAM
mangle_isup_number(from_msc, MsgT, NumType, PartyNum) when MsgT == ?ISUP_MSGT_CON;
MsgT == ?ISUP_MSGT_ANM ->
case NumType of
?ISUP_PAR_CONNECTED_NUM ->
io:format("CON MSRN rewrite (MSC->STP): "),
Num1 = isup_party_replace_prefix(PartyNum,
application:get_env(msrn_pfx_msc),
application:get_env(msrn_pfx_stp)),
% Second: convert to national number, if it is international
isup_party_nationalize(Num1,
application:get_env(intern_pfx));
_ ->
PartyNum
end;
% MAC->STP: Mangle IAM international -> national
mangle_isup_number(from_msc, ?ISUP_MSGT_IAM, NumType, PartyNum) ->
case NumType of
?ISUP_PAR_CALLED_P_NUM ->
isup_party_nationalize(PartyNum,
applicaiton:get_env(intern_pfx));
_ ->
PartyNum
end;
% STP->MSC: Mangle connected number in response to IAM (national->international)
mangle_isup_number(from_stp, MsgT, NumType, PartyNum) when MsgT == ?ISUP_MSGT_CON;
MsgT == ?ISUP_MSGT_ANM ->
case NumType of
?ISUP_PAR_CONNECTED_NUM ->
isup_party_internationalize(PartyNum,
application:get_env(intern_pfx));
_ ->
PartyNum
end;
% default case: no rewrite
mangle_isup_number(from_msc, _, _, PartyNum) ->
PartyNum.
% replace the prefix of PartyNum with NewPfx _if_ the current prefix matches MatchPfx
isup_party_replace_prefix(PartyNum, MatchPfx, NewPfxInt) ->
IntIn = PartyNum#party_number.phone_number,
DigitsIn = osmo_util:int2digit_list(IntIn),
NewPfx = osmo_util:int2digit_list(NewPfxInt),
MatchPfxLen = length(MatchPfx),
Pfx = lists:sublist(DigitsIn, 1, MatchPfxLen),
if Pfx == MatchPfx ->
Trailer = lists:sublist(DigitsIn, MatchPfxLen+1, length(DigitsIn)-MatchPfxLen),
DigitsOut = NewPfx ++ Trailer,
io:format("Prefix rewrite: ~p -> ~p~n", [DigitsIn, DigitsOut]);
true ->
io:format("Prefix rewrite: NO MATCH (~p != ~p)~n", [Pfx, MatchPfx]),
DigitsOut = DigitsIn
end,
IntOut = osmo_util:digit_list2int(DigitsOut),
PartyNum#party_number{phone_number = IntOut}.
isup_party_internationalize(PartyNum, CountryCode) ->
#party_number{phone_number = IntIn, nature_of_addr_ind = Nature} = PartyNum,
DigitsIn = osmo_util:int2digit_list(IntIn),
case Nature of
?ISUP_ADDR_NAT_NATIONAL ->
DigitsOut = CountryCode ++ DigitsIn,
NatureOut = ?ISUP_ADDR_NAT_INTERNATIONAL,
io:format("Internationalize: ~p -> ~p~n", [DigitsIn, DigitsOut]);
_ ->
DigitsOut = DigitsIn,
NatureOut = Nature
end,
IntOut = osmo_util:digit_list2int(DigitsOut),
PartyNum#party_number{phone_number = IntOut, nature_of_addr_ind = NatureOut}.
isup_party_nationalize(PartyNum, CountryCode) ->
#party_number{phone_number = IntIn, nature_of_addr_ind = Nature} = PartyNum,
DigitsIn = osmo_util:int2digit_list(IntIn),
CountryCodeLen = length(CountryCode),
case Nature of
?ISUP_ADDR_NAT_INTERNATIONAL ->
Pfx = lists:sublist(DigitsIn, CountryCodeLen),
if Pfx == CountryCode ->
DigitsOut = lists:sublist(DigitsIn, CountryCodeLen+1,
length(DigitsIn)-CountryCodeLen),
NatureOut = ?ISUP_ADDR_NAT_NATIONAL,
io:format("Nationalize: ~p -> ~p~n", [DigitsIn, DigitsOut]);
true ->
DigitsOut = DigitsIn,
NatureOut = Nature
end;
_ ->
DigitsOut = DigitsIn,
NatureOut = Nature
end,
IntOut = osmo_util:digit_list2int(DigitsOut),
PartyNum#party_number{phone_number = IntOut, nature_of_addr_ind = NatureOut}.

View File

@ -1,16 +0,0 @@
-module(mgw_nat_app).
-behavior(application).
-export([start/2, stop/1]).
-export([reload_config/0]).
start(_Type, _Args) ->
Sup = mgw_nat_sup:start_link(),
io:format("Sup ~p~n", [Sup]),
Sup.
stop(_State) ->
ok.
reload_config() ->
osmo_util:reload_config().

View File

@ -1,40 +0,0 @@
% OTP Supervisor for MGW NAT
% (C) 2011 by Harald Welte <laforge@gnumonks.org>
% (C) 2011 OnWaves
%
% 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(mgw_nat_sup).
-behavior(supervisor).
-export([start_link/0]).
-export([init/1]).
start_link() ->
supervisor:start_link({local, ?MODULE}, ?MODULE, []).
init(_Arg) ->
{ok, MscLocalIp} = application:get_env(msc_local_ip),
{ok, MscLocalPort} = application:get_env(msc_local_port),
{ok, MscRemoteIp} = application:get_env(msc_remote_ip),
{ok, StpRemoteIp} = application:get_env(stp_remote_ip),
{ok, StpRemotePort} = application:get_env(stp_remote_port),
SctpHdlrArgs = [MscLocalIp, MscLocalPort, MscRemoteIp,
StpRemoteIp, StpRemotePort],
MgwChild = {mgw_nat_usr, {mgw_nat_usr, start_link, [SctpHdlrArgs]},
permanent, 2000, worker, [mgw_nat_usr, sctp_handler, mgw_nat]},
{ok,{{one_for_all,1,1}, [MgwChild]}}.

View File

@ -1,59 +0,0 @@
% Wrapper code, wrapping sctp_handler.erl into OTP gen_server
% (C) 2011 by Harald Welte <laforge@gnumonks.org>
% (C) 2011 OnWaves
%
% 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(mgw_nat_usr).
-author("Harald Welte <laforge@gnumonks.org>").
-behavior(gen_server).
-export([start_link/1, stop/0, sccp_masq_reset/0]).
-export([init/1, handle_cast/2, handle_info/2, terminate/2]).
start_link(Params) ->
gen_server:start_link({local, ?MODULE}, ?MODULE, Params, []).
stop() ->
gen_server:cast(?MODULE, stop).
sccp_masq_reset() ->
gen_server:cast(?MODULE, sccp_masq_reset).
%% Callback functions of the OTP behavior
init(Params) ->
sccp_masq:init(),
apply(sctp_handler, init, Params).
handle_cast(stop, LoopData) ->
{stop, normal, LoopData};
handle_cast(sccp_masq_reset, LoopData) ->
sccp_masq:reset(),
{noreply, LoopData}.
terminate(_Reason, _LoopData) ->
ok.
% callback for other events like incoming SCTP message
handle_info({sctp, Sock, Ip, Port, Data}, LoopData) ->
NewL = sctp_handler:handle_sctp(LoopData, {sctp, Sock, Ip, Port, Data}),
{noreply, NewL}.

View File

@ -1,132 +0,0 @@
% ITU-T Q.71x SCCP UDT stateful masquerading
% (C) 2011 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_masq).
-author('Harald Welte <laforge@gnumonks.org>').
-include("sccp.hrl").
-export([sccp_masq_msg/3, init/0, reset/0]).
-compile([export_all]).
-record(sccp_masq_rec, {
digits_in, % list of GT digits
digits_out, % list of GT digits
last_access % timestamp of last usage
}).
% alloc + insert a new masquerade state record in our tables
masq_alloc(DigitsOrig) ->
{ok, Base} = application:get_env(sccp_masq_gt_base),
{ok, Max} = application:get_env(sccp_masq_gt_max),
masq_try_alloc(DigitsOrig, Base, Max, 0).
masq_try_alloc(_DigitsOrig, _Base, Max, Offset) when Offset > Max ->
undef;
masq_try_alloc(DigitsOrig, Base, Max, Offset) ->
Try = Base + Offset,
EtsRet = ets:insert_new(get(sccp_masq_orig),
#sccp_masq_rec{digits_in = DigitsOrig,
digits_out = Try}),
case EtsRet of
false ->
masq_try_alloc(DigitsOrig, Base, Max, Offset+1);
_ ->
ets:insert(get(sccp_masq_rev),
#sccp_masq_rec{digits_in = Try,
digits_out = DigitsOrig}),
Try
end.
% lookup a masqerade state record
lookup_masq_addr(orig, GtDigits) ->
case ets:lookup(get(sccp_masq_orig), GtDigits) of
[#sccp_masq_rec{digits_out = DigitsOut}] ->
DigitsOut;
_ ->
% allocate a new masq GT
masq_alloc(GtDigits)
end;
lookup_masq_addr(rev, GtDigits) ->
case ets:lookup(get(sccp_masq_rev), GtDigits) of
[#sccp_masq_rec{digits_out = DigitsOut}] ->
DigitsOut;
_ ->
% we do not allocate entries in the reverse direction
undef
end.
% Masquerade the CALLING address in first STP(G-MSC) -> HLR/VLR/MSC dir
mangle_rx_calling(from_stp, Addr = #sccp_addr{global_title = GT}) ->
GtOrig = GT#global_title.phone_number,
GtReplace = lookup_masq_addr(orig, GtOrig),
case GtReplace of
undef ->
io:format("SCCP MASQ: Unable to rewrite in original direction (out of GT addrs?)~n"),
Addr;
_ ->
io:format("SCCP MASQ (STP->MSC) rewrite ~p->~p~n", [GtOrig, GtReplace]),
GTout = GT#global_title{phone_number = GtReplace},
Addr#sccp_addr{global_title = GTout}
end;
mangle_rx_calling(_From, Addr) ->
Addr.
mangle_rx_called(from_msc, Addr = #sccp_addr{global_title = GT}) ->
GtOrig = GT#global_title.phone_number,
GtReplace = lookup_masq_addr(rev, GtOrig),
case GtReplace of
undef ->
io:format("SCCP MASQ: Unable to rewrite in original direction (unknown GT ~p)~n", [GT]),
Addr;
_ ->
io:format("SCCP MASQ (MSC->STP) rewrite ~p->~p~n", [GtOrig, GtReplace]),
GTout = GT#global_title{phone_number = GtReplace},
Addr#sccp_addr{global_title = GTout}
end;
mangle_rx_called(_From, Addr) ->
Addr.
sccp_masq_msg(From, ?SCCP_MSGT_UDT, Msg = #sccp_msg{parameters = Opts}) ->
CalledParty = proplists:get_value(called_party_addr, Opts),
CalledPartyNew = mangle_rx_called(From, CalledParty),
CallingParty = proplists:get_value(calling_party_addr, Opts),
CallingPartyNew = mangle_rx_calling(From, CallingParty),
Opts1 = lists:keyreplace(called_party_addr, 1, Opts,
{called_party_addr, CalledPartyNew}),
Opts2 = lists:keyreplace(calling_party_addr, 1, Opts1,
{calling_party_addr, CallingPartyNew}),
Msg#sccp_msg{parameters = Opts2};
sccp_masq_msg(_From, _MsgType, Msg) ->
Msg.
init() ->
Orig = ets:new(sccp_masq_orig, [ordered_set,
{keypos, #sccp_masq_rec.digits_in}]),
Rev = ets:new(sccp_masq_rev, [ordered_set,
{keypos, #sccp_masq_rec.digits_in}]),
put(sccp_masq_orig, Orig),
put(sccp_masq_rev, Rev),
ok.
reset() ->
io:format("SCCP MASQ: Deleting all MASQ state records~n"),
ets:delete_all_objects(get(sccp_masq_orig)),
ets:delete_all_objects(get(sccp_masq_rev)).

View File

@ -1,80 +0,0 @@
% (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)]),
IpaStreamId = LoopData#loop_data.ipa_stream_id,
% 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, IpaStreamId]},
{ok, ScrcPid} = sccp_scrc:start_link([{mtp_tx_action, ScrcMtpCb}]),
% Register an IPA stream for SCCP
ipa_proto:register_stream(S, IpaStreamId,
{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.