erlang
/
osmo-map-masq
Archived
4
0
Fork 0

example code to work with epcap (erlang pcap)

This commit is contained in:
Harald Welte 2010-08-07 19:31:52 +02:00
parent 2e50e402e1
commit aed61bf02a
1 changed files with 66 additions and 0 deletions

66
src/pcap_test.erl Normal file
View File

@ -0,0 +1,66 @@
% Test program for epcap (http://github.com/msantos/epcap)
%
-module(pcap_test).
-include("include/epcap_net.hrl").
-export([init/1]).
-define(SCTP_PPI_M3UA, 3).
-define(M3UA_MSG_CLASS_TRANSFER, 1).
-define(M3UA_MSG_TYPE_DATA, 1).
-record(loop_data, {udpSock, udpDstIP, udpDstPort}).
% handle a M3UA "prototol data" tag and send its contents off through UDP
handle_m3ua_tag(#loop_data{}=LD, ?M3UA_MSG_CLASS_TRANSFER, ?M3UA_MSG_TYPE_DATA,
528, Len, <<OPC:4/bytes, DPC:4/bytes, SI:1/bytes, NI:1/bytes,
MP:1/bytes, SLS:1/bytes, SCCP/binary>>) ->
io:write("Sending SCCP Message of ~p bytes via UDP: ~p~n", Len, SCCP),
gen_udp:send(LD#loop_data.udpSock, LD#loop_data.udpDstIP, LD#loop_data.udpDstPort, SCCP);
handle_m3ua_tag(#loop_data{}=_LD, Class, Type, Tag, Len, _Bin) ->
io:write("Unknown M3UA Tag ~p of Length ~p in Msg class ~p type ~p~n", [Tag, Len, Class, Type]).
% loop over M3UA parameters and call handle_m3ua_tag() for each of them
handle_m3ua_param(#loop_data{}=_LD, _Class, _Type, <<>>) ->
ok;
handle_m3ua_param(#loop_data{}=LD, Class, Type,
<<Tag:2/bytes, Len:2/bytes, Remainder/binary>>) ->
Payload = binary:part(Remainder, 0, Len-4),
Tail = binary:part(Remainder, Len-4, byte_size(Remainder)-(Len-4)),
handle_m3ua_tag(LD, Class, Type, Tag, Len, Payload),
handle_m3ua_param(LD, Class, Type, Tail).
handle_m3ua(LD, <<Release:1/bytes, _Reserved:1/bytes, MsgClass:1/bytes,
MsgType:1/bytes, _MsgLen:4/bytes, Remainder/binary>>) ->
handle_m3ua_param(LD, MsgClass, MsgType, Remainder).
handle_sctp_data_chunk(LD, #sctp_chunk_data{ppi=?SCTP_PPI_M3UA}=ChunkData) ->
handle_m3ua(LD, ChunkData#sctp_chunk_data.data).
handle_sctp_chunk(LD, #sctp_chunk{type=0}=Chunk) ->
DataChunk = Chunk#sctp_chunk.payload,
handle_sctp_data_chunk(LD, DataChunk);
handle_sctp_chunk(_LD, #sctp_chunk{type=Type}=_Chunk) ->
io:write("Ignoring SCTP chunk type ~p~n", [Type]).
handle_sctp_chunks(_LD, []) ->
ok;
handle_sctp_chunks(LD, [Chunk|List]) ->
handle_sctp_chunk(LD, Chunk),
handle_sctp_chunks(LD, List).
handle_packet(LD, #ether{}=_Ether, _IP, #sctp{}=Hdr) ->
handle_sctp_chunks(LD, Hdr#sctp.chunks).
init(Filename) ->
epcap:start([{file, Filename},{filter,""}]),
{ok, Socket} = gen_udp:open(0),
loop(#loop_data{udpSock=Socket, udpDstIP="127.0.0.1", udpDstPort=4242}).
loop(#loop_data{}=LD) ->
receive
[{pkthdr, _}, {packet, Packet}] ->
[Ether, IP, Hdr, _Payload] = epcap_net:decapsulate(Packet),
handle_packet(LD, Ether, IP, Hdr),
loop(LD)
end.