blob: 806723fed6a21012612d4dfdb25a3011d4030d37 [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/>.
20
21-module(osmo_ss7_pcap).
22-author("Harald Welte <laforge@gnumonks.org>").
23-export([pcap_apply/3]).
24
25-define(NODEBUG, 1).
26
27-include_lib("eunit/include/eunit.hrl").
28-include_lib("epcap/include/epcap_net.hrl").
29
Harald Welteeba9e252011-03-11 18:21:53 +010030-record(loop_data, {
31 args,
32 pkt_nr
33 }).
34
Harald Welte48213102011-03-11 15:50:13 +010035pcap_apply(File, Filter, Args) ->
36 epcap:start([{file, File}, {filter, Filter}]),
Harald Welteeba9e252011-03-11 18:21:53 +010037 loop(#loop_data{args = Args, pkt_nr = 1}).
Harald Welte48213102011-03-11 15:50:13 +010038
Harald Welteeba9e252011-03-11 18:21:53 +010039loop(L = #loop_data{args=Args, pkt_nr = PktNr}) ->
Harald Welte48213102011-03-11 15:50:13 +010040 receive
41 [{pkthdr, {_,_,_,{datalink,Datalink}}}, {packet, Packet}] ->
42 Decaps = epcap_net:decapsulate_dlt(Datalink, Packet),
Harald Welteeba9e252011-03-11 18:21:53 +010043 handle_pkt_cb(PktNr, Decaps, Args),
44 loop(L#loop_data{pkt_nr = PktNr+1});
Harald Welte48213102011-03-11 15:50:13 +010045 {epcap, eof} ->
46 ?debugFmt("EOF from PCAP~n", []),
Harald Welteeba9e252011-03-11 18:21:53 +010047 epcap:stop(),
48 {ok, PktNr-1};
49 _Default ->
Harald Welte48213102011-03-11 15:50:13 +010050 ?debugFmt("Unknown ~p from PCAP~n", [Default])
51 end.
52
Harald Welteeba9e252011-03-11 18:21:53 +010053handle_pkt_cb(PktNr, [Ether, IP, Hdr, Payload], Args) ->
Harald Welte48213102011-03-11 15:50:13 +010054 ?debugFmt("~p:~n ~p/~p~n", [IP, Hdr, Payload]),
55 case Hdr of
56 #sctp{chunks = Chunks} ->
Harald Welteeba9e252011-03-11 18:21:53 +010057 Path = [{epcap_pkt_nr, PktNr}, Ether, IP, Hdr],
58 handle_sctp_chunks(Chunks, Path, Args);
Harald Welte48213102011-03-11 15:50:13 +010059 _ ->
60 ok
61 end.
62
63handle_sctp_chunks([], _Path, _Args) ->
64 ok;
65handle_sctp_chunks([Head|Tail], Path, Args) ->
66 RewriteFn = proplists:get_value(rewrite_fn, Args),
67 case Head of
68 #sctp_chunk{type = 0, payload=#sctp_chunk_data{ppi=2, data=Data}} ->
69 %mgw_nat:mangle_rx_data(l, from_stp, Data, fun handle_rewrite_cb/5);
70 put(rewrite_cb, RewriteFn),
71 shim_rw_actor(sctp, from_msc, Path, 2, Data);
72 _ ->
73 ok
74 end,
75 handle_sctp_chunks(Tail, Path, Args).
76
77shim_rw_actor(Proto, From, Path, MsgType, Msg) ->
78 ?debugFmt(" IN:~p:~p:~p~n", [Proto, From, Msg]),
79 Fn = get(rewrite_cb),
80 MsgOut = Fn(Proto, From, Path, MsgType, Msg),
81 case MsgOut of
82 Msg ->
83 MsgOut;
84 _ ->
85 %io:format("OUT:~p:~p:~p~n", [Proto, From, MsgOut]),
86 MsgOut
87 end.