summaryrefslogtreecommitdiff
path: root/readpackets.hs
diff options
context:
space:
mode:
Diffstat (limited to 'readpackets.hs')
-rw-r--r--readpackets.hs82
1 files changed, 82 insertions, 0 deletions
diff --git a/readpackets.hs b/readpackets.hs
new file mode 100644
index 00000000..f02df538
--- /dev/null
+++ b/readpackets.hs
@@ -0,0 +1,82 @@
1{-# LANGUAGE PackageImports #-}
2module Main where
3
4import Data.Binary.Get (runGet)
5import qualified Data.ByteString as BS
6import qualified Data.ByteString as B
7import qualified Data.ByteString.Lazy as LZ
8import qualified Data.ByteString.Lazy.Char8 as L8
9import Data.IORef
10import Data.List
11import Debug.Trace
12import Text.Printf
13import Text.Show.Pretty as PP
14import "network-house" Net.Packet
15import qualified "network-house" Net.IPv4 as IP4
16import qualified "network-house" Net.IPv6 as IP6
17import "network-house" Net.PacketParsing
18import "network-house" Net.UDP as UDP
19import "pcap" Network.Pcap
20import qualified Data.Serialize as S
21import qualified Network.Socket as HS
22import Control.Applicative
23
24import Crypto.Tox
25import Network.Tox.DHT.Transport as Tox
26import Data.BEncode as BE
27import Data.BEncode.Pretty
28-- import Data.IKE.Message
29
30-- traceM string = trace string $ return ()
31
32bs2chunk :: BS.ByteString -> UArray Int Word8
33bs2chunk bs = listArray (0,subtract 33 $ BS.length bs) $ drop 32 $ BS.unpack bs
34
35hex :: BS.ByteString -> String
36hex = concatMap (printf "%02x") . B.unpack
37
38hexlines :: BS.ByteString -> [String]
39hexlines bs = ss
40 where xs = zip [0..] $ hex bs
41 ls = groupBy (\(n,_) (m,_)-> n `div` 32 == m `div` 32) xs
42 ss = map (map snd) ls
43
44parsePacket :: IORef Int -> PktHdr -> BS.ByteString -> IO ()
45parsePacket cnt hdr buf = do
46 print hdr
47 let -- mb :: Maybe (BS.ByteString, Message Encrypted)
48 mb = do
49 udp <- doParse $ toInPack $ bs2chunk buf
50 -- traceM $ "got udp: " ++ show udp
51 -- traceM $ "got udp content: " ++ show (content udp)
52 let plen = Net.Packet.len $ content udp
53 bs <- fmap BS.pack . parseInPacket (bytes plen) $ content udp
54 -- traceM $ "Got bs " ++ show bs
55 let (checksum,blob) = BS.splitAt 2 bs -- extra 2 bytes in pcap capture, i'm assuming its a checksum
56-- (first4,truncated) = BS.splitAt 4 blob
57-- -- First 4 bytes being zero is how we distinguish between
58-- -- ESP and IKEv2 packets on port 4500.
59-- dta = if destPort udp /= Port 500 && first4==BS.pack [0,0,0,0]
60-- then truncated
61-- else blob
62 dta = blob
63 let d = BE.decode {- runGet getMessage $ LZ.fromStrict -} dta
64 saddr = HS.SockAddrInet 0 0 -- TODO
65 -- e = S.decode dta :: Either String (DHTMessage Encrypted8)
66 e = case Tox.parseDHTAddr (dta,saddr) :: Either (DHTMessage Encrypted8,NodeInfo) (BS.ByteString,HS.SockAddr) of
67 Left toxpkt -> Right toxpkt
68 Right _ -> Left "tox parse fail"
69 return $ (udp, bs, fmap Left d <|> fmap Right e)
70 flip (maybe $ return ()) mb $ \(udp, bs,m) -> do
71 putStrLn $ show udp
72 mapM_ putStrLn $ hexlines bs
73 -- putStrLn $ PP.ppShow m
74 either putStrLn (L8.putStrLn . either showBEncode (L8.pack . show)) m
75 modifyIORef' cnt (+1)
76
77main = do
78 cnt <- newIORef 0
79 pcap <- openOffline "packets.pcap"
80 loopResult <- loopBS pcap (-1) $ parsePacket cnt
81 pktcnt <- readIORef cnt
82 putStrLn $ "read "++show pktcnt ++" packets."