blob: ffa9d594c470d5284202cba5cf2de2b2c076a159 [file] [log] [blame]
Harald Welte48213102011-03-11 15:50:13 +01001% MGW Nat testing code
2
3% (C) 2011 by Harald Welte <laforge@gnumonks.org>
4% (C) 2011 OnWaves
5%
6% All Rights Reserved
7%
8% This program is free software; you can redistribute it and/or modify
9% it under the terms of the GNU Affero General Public License as
10% published by the Free Software Foundation; either version 3 of the
11% License, or (at your option) any later version.
12%
13% This program is distributed in the hope that it will be useful,
14% but WITHOUT ANY WARRANTY; without even the implied warranty of
15% MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
16% GNU General Public License for more details.
17%
18% You should have received a copy of the GNU Affero General Public License
19% along with this program. If not, see <http://www.gnu.org/licenses/>.
Harald Weltef8bf0322012-04-16 13:10:47 +020020%
21% Additional Permission under GNU AGPL version 3 section 7:
22%
23% If you modify this Program, or any covered work, by linking or
24% combining it with runtime libraries of Erlang/OTP as released by
25% Ericsson on http://www.erlang.org (or a modified version of these
26% libraries), containing parts covered by the terms of the Erlang Public
27% License (http://www.erlang.org/EPLICENSE), the licensors of this
28% Program grant you additional permission to convey the resulting work
29% without the need to license the runtime libraries of Erlang/OTP under
30% the GNU Affero General Public License. Corresponding Source for a
31% non-source form of such a combination shall include the source code
32% for the parts of the runtime libraries of Erlang/OTP used as well as
33% that of the covered work.
Harald Welte48213102011-03-11 15:50:13 +010034
35-module(osmo_ss7_pcap).
36-author("Harald Welte <laforge@gnumonks.org>").
37-export([pcap_apply/3]).
38
39-define(NODEBUG, 1).
40
41-include_lib("eunit/include/eunit.hrl").
Harald Weltec9f31782019-08-11 15:33:18 +020042-include_lib("pkt/include/pkt.hrl").
Harald Welte48213102011-03-11 15:50:13 +010043
Harald Welteeba9e252011-03-11 18:21:53 +010044-record(loop_data, {
45 args,
46 pkt_nr
47 }).
48
Harald Welte48213102011-03-11 15:50:13 +010049pcap_apply(File, Filter, Args) ->
50 epcap:start([{file, File}, {filter, Filter}]),
Harald Welteeba9e252011-03-11 18:21:53 +010051 loop(#loop_data{args = Args, pkt_nr = 1}).
Harald Welte48213102011-03-11 15:50:13 +010052
Harald Welteeba9e252011-03-11 18:21:53 +010053loop(L = #loop_data{args=Args, pkt_nr = PktNr}) ->
Harald Welte48213102011-03-11 15:50:13 +010054 receive
55 [{pkthdr, {_,_,_,{datalink,Datalink}}}, {packet, Packet}] ->
56 Decaps = epcap_net:decapsulate_dlt(Datalink, Packet),
Harald Welteeba9e252011-03-11 18:21:53 +010057 handle_pkt_cb(PktNr, Decaps, Args),
58 loop(L#loop_data{pkt_nr = PktNr+1});
Harald Welte48213102011-03-11 15:50:13 +010059 {epcap, eof} ->
60 ?debugFmt("EOF from PCAP~n", []),
Harald Welteeba9e252011-03-11 18:21:53 +010061 epcap:stop(),
62 {ok, PktNr-1};
Harald Welte7629ced2011-04-03 01:14:41 +020063 Default ->
Harald Welte48213102011-03-11 15:50:13 +010064 ?debugFmt("Unknown ~p from PCAP~n", [Default])
65 end.
66
Harald Welteeba9e252011-03-11 18:21:53 +010067handle_pkt_cb(PktNr, [Ether, IP, Hdr, Payload], Args) ->
Harald Welte48213102011-03-11 15:50:13 +010068 ?debugFmt("~p:~n ~p/~p~n", [IP, Hdr, Payload]),
69 case Hdr of
70 #sctp{chunks = Chunks} ->
Harald Welteeba9e252011-03-11 18:21:53 +010071 Path = [{epcap_pkt_nr, PktNr}, Ether, IP, Hdr],
72 handle_sctp_chunks(Chunks, Path, Args);
Harald Welte48213102011-03-11 15:50:13 +010073 _ ->
74 ok
75 end.
76
77handle_sctp_chunks([], _Path, _Args) ->
78 ok;
79handle_sctp_chunks([Head|Tail], Path, Args) ->
80 RewriteFn = proplists:get_value(rewrite_fn, Args),
81 case Head of
Harald Welte7629ced2011-04-03 01:14:41 +020082 #sctp_chunk{type = 0, payload=#sctp_chunk_data{ppi=Ppi, data=Data}} ->
Harald Welte48213102011-03-11 15:50:13 +010083 %mgw_nat:mangle_rx_data(l, from_stp, Data, fun handle_rewrite_cb/5);
84 put(rewrite_cb, RewriteFn),
Harald Welte7629ced2011-04-03 01:14:41 +020085 shim_rw_actor(sctp, from_msc, Path, Ppi, Data);
Harald Welte48213102011-03-11 15:50:13 +010086 _ ->
87 ok
88 end,
89 handle_sctp_chunks(Tail, Path, Args).
90
91shim_rw_actor(Proto, From, Path, MsgType, Msg) ->
92 ?debugFmt(" IN:~p:~p:~p~n", [Proto, From, Msg]),
93 Fn = get(rewrite_cb),
94 MsgOut = Fn(Proto, From, Path, MsgType, Msg),
95 case MsgOut of
96 Msg ->
97 MsgOut;
98 _ ->
99 %io:format("OUT:~p:~p:~p~n", [Proto, From, MsgOut]),
100 MsgOut
101 end.