summaryrefslogtreecommitdiff
path: root/readpackets.hs
blob: f02df538805df63ef1a79eb7a02546ddb5ad83e0 (plain)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
{-# LANGUAGE PackageImports #-}
module Main where

import           Data.Binary.Get      (runGet)
import qualified Data.ByteString      as BS
import qualified Data.ByteString      as B
import qualified Data.ByteString.Lazy as LZ
import qualified Data.ByteString.Lazy.Char8 as L8
import           Data.IORef
import           Data.List
import           Debug.Trace
import           Text.Printf
import           Text.Show.Pretty     as PP
import "network-house" Net.Packet
import qualified "network-house" Net.IPv4 as IP4
import qualified "network-house" Net.IPv6 as IP6
import "network-house" Net.PacketParsing
import "network-house" Net.UDP as UDP
import "pcap"          Network.Pcap
import qualified Data.Serialize as S
import qualified Network.Socket as HS
import Control.Applicative

import Crypto.Tox
import Network.Tox.DHT.Transport as Tox
import Data.BEncode as BE
import Data.BEncode.Pretty
-- import Data.IKE.Message

-- traceM string = trace string $ return ()

bs2chunk :: BS.ByteString -> UArray Int Word8
bs2chunk bs = listArray (0,subtract 33 $ BS.length bs) $ drop 32 $ BS.unpack bs

hex :: BS.ByteString -> String
hex = concatMap (printf "%02x") . B.unpack

hexlines :: BS.ByteString -> [String]
hexlines bs = ss
    where xs = zip [0..] $ hex bs
          ls = groupBy (\(n,_) (m,_)-> n `div` 32 == m `div` 32) xs
          ss = map (map snd) ls

parsePacket :: IORef Int -> PktHdr -> BS.ByteString -> IO ()
parsePacket cnt hdr buf = do
    print hdr
    let -- mb :: Maybe (BS.ByteString, Message Encrypted)
        mb = do
            udp <- doParse $ toInPack $ bs2chunk buf
            -- traceM $ "got udp: " ++ show udp
            -- traceM $ "got udp content: " ++ show (content udp)
            let plen = Net.Packet.len $ content udp
            bs <- fmap BS.pack . parseInPacket (bytes plen) $ content udp
            -- traceM $ "Got bs " ++ show bs
            let (checksum,blob) = BS.splitAt 2 bs -- extra 2 bytes in pcap capture, i'm assuming its a checksum
--                 (first4,truncated) = BS.splitAt 4 blob
--                 -- First 4 bytes being zero is how we distinguish between
--                 -- ESP and IKEv2 packets on port 4500.
--                 dta = if destPort udp /= Port 500 && first4==BS.pack [0,0,0,0]
--                         then truncated
--                         else blob
                dta = blob
            let d = BE.decode {- runGet getMessage $ LZ.fromStrict -} dta
                saddr = HS.SockAddrInet 0 0 -- TODO
                -- e = S.decode dta :: Either String (DHTMessage Encrypted8)
                e = case Tox.parseDHTAddr (dta,saddr) :: Either (DHTMessage Encrypted8,NodeInfo) (BS.ByteString,HS.SockAddr) of
                        Left toxpkt -> Right toxpkt
                        Right _     -> Left "tox parse fail"
            return $ (udp, bs, fmap Left d <|> fmap Right e)
    flip (maybe $ return ()) mb $ \(udp, bs,m) -> do
        putStrLn $ show udp
        mapM_ putStrLn $ hexlines bs
        -- putStrLn $ PP.ppShow m
        either putStrLn (L8.putStrLn . either showBEncode (L8.pack . show)) m
    modifyIORef' cnt (+1)

main = do
    cnt <- newIORef 0
    pcap <- openOffline "packets.pcap"
    loopResult <- loopBS pcap (-1) $ parsePacket cnt
    pktcnt <- readIORef cnt
    putStrLn $ "read "++show pktcnt ++" packets."