
Hello all I was going through wireshark and read this pcaphttp://wiki.wireshark.org/SampleCaptures?action=AttachFile&do=view&target=udp_lite_full_coverage_0.pcapfile in wireshark. I wrote a simple haskell file which reads the pcap file displays its contents however it looks completely different from wireshark. When i run this program . it does not produce any thing and when i press ^C ( CTRL - C ) it produce output. output for given file ^C*0xd4 0xc3 0xb2 0xa1 0x02 0x00 0x04 0x00 0x00 0x00 0x00 0x00 0x00 0x00 0x00 0x00 0xff 0xff 0x00 0x00 0x01 0x00 0x00 0x00 0x0b 0xd4 0x9e 0x43 0x41 0x38 0x01 0x00 0x3c 0x00 0x00 0x00 0x3c 0x00 0x00 0x00 *0x00* *0x04 0x76 0xdd 0xbb 0x3a 0x00 0x04 0x75 0xc7 0x87 0x49 0x08 0x00 0x45 0x00 0x00 0x28 0x1a 0x6a 0x40 0x00 0x40 0x88 0x6f 0x71 0x8b 0x85 0xcc 0xb0 0x8b 0x85 0xcc 0xb7 0x80 0x00 0x04 0xd2 0x00 0x00 0x38 0x45 0x68 0x65 0x6c 0x6c 0x6f 0x20 0x77 0x6f 0x72 0x6c 0x64 0x00 0x00 0x00 0x00 0x00 0x00 The values displayed in wireshark 0000 00 04 76 dd bb 3a 00 04 75 c7 87 49 08 00 45 00 ..v..:.. u..I..E. 0010 00 28 1a 6a 40 00 40 88 6f 71 8b 85 cc b0 8b 85 .(.j@.@. oq...... 0020 cc b7 80 00 04 d2 00 00 38 45 68 65 6c 6c 6f 20 ........ 8Ehello 0030 77 6f 72 6c 64 0a 00 00 00 00 00 00 world... .... import Data.Char import Data.List import Text.Printf import Control.Monad fileReader :: Handle -> IO () fileReader h = do t <- hIsEOF h if t then return () else do tmp <- hGetLine h forM_ tmp ( printf "0x%02x " ) fileReader h main = do l <- openBinaryFile "udp_lite_full_coverage_0.pcap" ReadMode fileReader l print "end" I am simply trying to write a haskell script which produce interpretation of pcap packet same as wireshark ( At least for UDP packet ) . Could some one please tell me a guide map to approach for this . A general guide line for this project like What to read which could be helpful for this project , which haskell library or any thing which you think is useful . Regards Mukesh Tiwari

Did you try using the pcap library on Hackage? http://hackage.haskell.org/package/pcap -md begin mukesh tiwari quotation:
Hello all I was going through wireshark and read this pcaphttp://wiki.wireshark.org/SampleCaptures?action=AttachFile&do=view&target=udp_lite_full_coverage_0.pcapfile in wireshark. I wrote a simple haskell file which reads the pcap file displays its contents however it looks completely different from wireshark. When i run this program . it does not produce any thing and when i press ^C ( CTRL - C ) it produce output.
output for given file ^C*0xd4 0xc3 0xb2 0xa1 0x02 0x00 0x04 0x00 0x00 0x00 0x00 0x00 0x00 0x00 0x00 0x00 0xff 0xff 0x00 0x00 0x01 0x00 0x00 0x00 0x0b 0xd4 0x9e 0x43 0x41 0x38 0x01 0x00 0x3c 0x00 0x00 0x00 0x3c 0x00 0x00 0x00 *0x00* *0x04 0x76 0xdd 0xbb 0x3a 0x00 0x04 0x75 0xc7 0x87 0x49 0x08 0x00 0x45 0x00 0x00 0x28 0x1a 0x6a 0x40 0x00 0x40 0x88 0x6f 0x71 0x8b 0x85 0xcc 0xb0 0x8b 0x85 0xcc 0xb7 0x80 0x00 0x04 0xd2 0x00 0x00 0x38 0x45 0x68 0x65 0x6c 0x6c 0x6f 0x20 0x77 0x6f 0x72 0x6c 0x64 0x00 0x00 0x00 0x00 0x00 0x00
The values displayed in wireshark 0000 00 04 76 dd bb 3a 00 04 75 c7 87 49 08 00 45 00 ..v..:.. u..I..E. 0010 00 28 1a 6a 40 00 40 88 6f 71 8b 85 cc b0 8b 85 .(.j@.@. oq...... 0020 cc b7 80 00 04 d2 00 00 38 45 68 65 6c 6c 6f 20 ........ 8Ehello 0030 77 6f 72 6c 64 0a 00 00 00 00 00 00 world... ....
import Data.Char import Data.List import Text.Printf import Control.Monad
fileReader :: Handle -> IO () fileReader h = do t <- hIsEOF h if t then return () else do tmp <- hGetLine h forM_ tmp ( printf "0x%02x " ) fileReader h
main = do l <- openBinaryFile "udp_lite_full_coverage_0.pcap" ReadMode fileReader l print "end"
I am simply trying to write a haskell script which produce interpretation of pcap packet same as wireshark ( At least for UDP packet ) . Could some one please tell me a guide map to approach for this . A general guide line for this project like What to read which could be helpful for this project , which haskell library or any thing which you think is useful .
Regards Mukesh Tiwari
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Its the byte ordering being different between the pcap file and the machine on which the haskell is running On 12 Oct 2011, at 16:38, mukesh tiwari wrote:
Hello all I was going through wireshark and read this pcap file in wireshark. I wrote a simple haskell file which reads the pcap file displays its contents however it looks completely different from wireshark. When i run this program . it does not produce any thing and when i press ^C ( CTRL - C ) it produce output.
output for given file ^C0xd4 0xc3 0xb2 0xa1 0x02 0x00 0x04 0x00 0x00 0x00 0x00 0x00 0x00 0x00 0x00 0x00 0xff 0xff 0x00 0x00 0x01 0x00 0x00 0x00 0x0b 0xd4 0x9e 0x43 0x41 0x38 0x01 0x00 0x3c 0x00 0x00 0x00 0x3c 0x00 0x00 0x00 0x00 0x04 0x76 0xdd 0xbb 0x3a 0x00 0x04 0x75 0xc7 0x87 0x49 0x08 0x00 0x45 0x00 0x00 0x28 0x1a 0x6a 0x40 0x00 0x40 0x88 0x6f 0x71 0x8b 0x85 0xcc 0xb0 0x8b 0x85 0xcc 0xb7 0x80 0x00 0x04 0xd2 0x00 0x00 0x38 0x45 0x68 0x65 0x6c 0x6c 0x6f 0x20 0x77 0x6f 0x72 0x6c 0x64 0x00 0x00 0x00 0x00 0x00 0x00
The values displayed in wireshark 0000 00 04 76 dd bb 3a 00 04 75 c7 87 49 08 00 45 00 ..v..:.. u..I..E. 0010 00 28 1a 6a 40 00 40 88 6f 71 8b 85 cc b0 8b 85 .(.j@.@. oq...... 0020 cc b7 80 00 04 d2 00 00 38 45 68 65 6c 6c 6f 20 ........ 8Ehello 0030 77 6f 72 6c 64 0a 00 00 00 00 00 00 world... ....
import Data.Char import Data.List import Text.Printf import Control.Monad
fileReader :: Handle -> IO () fileReader h = do t <- hIsEOF h if t then return () else do tmp <- hGetLine h forM_ tmp ( printf "0x%02x " ) fileReader h
main = do l <- openBinaryFile "udp_lite_full_coverage_0.pcap" ReadMode fileReader l print "end"
I am simply trying to write a haskell script which produce interpretation of pcap packet same as wireshark ( At least for UDP packet ) . Could some one please tell me a guide map to approach for this . A general guide line for this project like What to read which could be helpful for this project , which haskell library or any thing which you think is useful .
Regards Mukesh Tiwari _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

There is a pcap library - it is a bit of overkill if all you are trying to do is read pcap files. I have an (internal - could be made external to the company) library that does this sort of thing and reads using Binary the pcap file and does the appropriate re-ordering of the bytes within the words depending on the pcap endianness Neil On 12 Oct 2011, at 16:38, mukesh tiwari wrote:
Hello all I was going through wireshark and read this pcap file in wireshark. I wrote a simple haskell file which reads the pcap file displays its contents however it looks completely different from wireshark. When i run this program . it does not produce any thing and when i press ^C ( CTRL - C ) it produce output.
output for given file ^C0xd4 0xc3 0xb2 0xa1 0x02 0x00 0x04 0x00 0x00 0x00 0x00 0x00 0x00 0x00 0x00 0x00 0xff 0xff 0x00 0x00 0x01 0x00 0x00 0x00 0x0b 0xd4 0x9e 0x43 0x41 0x38 0x01 0x00 0x3c 0x00 0x00 0x00 0x3c 0x00 0x00 0x00 0x00 0x04 0x76 0xdd 0xbb 0x3a 0x00 0x04 0x75 0xc7 0x87 0x49 0x08 0x00 0x45 0x00 0x00 0x28 0x1a 0x6a 0x40 0x00 0x40 0x88 0x6f 0x71 0x8b 0x85 0xcc 0xb0 0x8b 0x85 0xcc 0xb7 0x80 0x00 0x04 0xd2 0x00 0x00 0x38 0x45 0x68 0x65 0x6c 0x6c 0x6f 0x20 0x77 0x6f 0x72 0x6c 0x64 0x00 0x00 0x00 0x00 0x00 0x00
The values displayed in wireshark 0000 00 04 76 dd bb 3a 00 04 75 c7 87 49 08 00 45 00 ..v..:.. u..I..E. 0010 00 28 1a 6a 40 00 40 88 6f 71 8b 85 cc b0 8b 85 .(.j@.@. oq...... 0020 cc b7 80 00 04 d2 00 00 38 45 68 65 6c 6c 6f 20 ........ 8Ehello 0030 77 6f 72 6c 64 0a 00 00 00 00 00 00 world... ....
import Data.Char import Data.List import Text.Printf import Control.Monad
fileReader :: Handle -> IO () fileReader h = do t <- hIsEOF h if t then return () else do tmp <- hGetLine h forM_ tmp ( printf "0x%02x " ) fileReader h
main = do l <- openBinaryFile "udp_lite_full_coverage_0.pcap" ReadMode fileReader l print "end"
I am simply trying to write a haskell script which produce interpretation of pcap packet same as wireshark ( At least for UDP packet ) . Could some one please tell me a guide map to approach for this . A general guide line for this project like What to read which could be helpful for this project , which haskell library or any thing which you think is useful .
Regards Mukesh Tiwari _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Thank you all for your valuable comments.
@ MD no , i haven't tried but i am looking forward .
@ Neil Davis It would be great if you can make this library
external .
@ Malcolm Does this mean that pcap files don't have any EOF file
character.
One last question
The values which were not visible in wireshark
0xd4 0xc3 0xb2 0xa1 0x02 0x00 0x04 0x00 0x00 0x00 0x00 0x00 0x00 0x00
0x00 0x00 0xff 0xff 0x00 0x00 0x01 0x00 0x00 0x00 0x0b 0xd4 0x9e 0x43
0x41
0x38 0x01 0x00 0x3c 0x00 0x00 0x00 0x3c 0x00 0x00 0x00
Are these hex bytes value of this pcap header ?
struct pcap_pkthdr {
struct timeval ts; /* time stamp */
bpf_u_int32 caplen; /* length of portion present */
bpf_u_int32 len; /* length this packet (off wire) */
};
If yes then how can i deduce ts , caplen and len from these hex
values.
Regards
Mukesh Tiwari
On Oct 12, 8:49 pm, "malcolm.wallace"
On 12 Oct, 2011,at 04:39 PM, mukesh tiwari
wrote: When i run this program . it does not produce any thing and when i press ^C ( CTRL - C ) it produce output.
This is because you use hGetLine, which blocks until it sees either a newline character, or EOF.
Regards, Malcolm
_______________________________________________ Haskell-Cafe mailing list Haskell-C...@haskell.orghttp://www.haskell.org/mailman/listinfo/haskell-cafe

Finally i wrote it using pcap as suggested by Mike
import Network.Pcap
import System.IO
import Control.Monad
callfun f = do
( p , q ) <- next f
print $ hdrSeconds p
print $ hdrCaptureLength p
print $ hdrWireLength p
print q
when ( hdrWireLength p /= 0 ) $ callfun f
main = do
f <- openOffline "udp_lite_full_coverage_0.pcap"
callfun f
Output
[user@haskell Programming]$ ./ReadfilePcap
1134482443
60
60
0x0000000001c7c9a0
0
0
0
0x0000000000000000
How can i convert time return by hdrSeconds into same as wireshark
[ Date : Month : Year hour:min: sec ] and hex data return by variable
q into Ascii characters.
Regards
Mukesh Tiwari
On Oct 12, 11:33 pm, mukesh tiwari
Thank you all for your valuable comments. @ MD no , i haven't tried but i am looking forward . @ Neil Davis It would be great if you can make this library external . @ Malcolm Does this mean that pcap files don't have any EOF file character.
One last question The values which were not visible in wireshark 0xd4 0xc3 0xb2 0xa1 0x02 0x00 0x04 0x00 0x00 0x00 0x00 0x00 0x00 0x00 0x00 0x00 0xff 0xff 0x00 0x00 0x01 0x00 0x00 0x00 0x0b 0xd4 0x9e 0x43 0x41 0x38 0x01 0x00 0x3c 0x00 0x00 0x00 0x3c 0x00 0x00 0x00
Are these hex bytes value of this pcap header ? struct pcap_pkthdr { struct timeval ts; /* time stamp */ bpf_u_int32 caplen; /* length of portion present */ bpf_u_int32 len; /* length this packet (off wire) */ };
If yes then how can i deduce ts , caplen and len from these hex values.
Regards Mukesh Tiwari On Oct 12, 8:49 pm, "malcolm.wallace"
wrote: On 12 Oct, 2011,at 04:39 PM, mukesh tiwari
wrote: When i run this program . it does not produce any thing and when i press ^C ( CTRL - C ) it produce output.
This is because you use hGetLine, which blocks until it sees either a newline character, or EOF.
Regards, Malcolm
_______________________________________________ Haskell-Cafe mailing list Haskell-C...@haskell.orghttp://www.haskell.org/mailman/listinfo/haskell-cafe
_______________________________________________ Haskell-Cafe mailing list Haskell-C...@haskell.orghttp://www.haskell.org/mailman/listinfo/haskell-cafe

Hello everyone I started writing this application but there is some thing missing. I read this file http://www.viste.com/Linux/Server/WireShark/libpcapformat.pdf and it say that first 24 bytes are global headers , after that every packet contains pcap local header . What i am trying to do is , first trying to get the bytes of data in each packet by reading the third field incl_len in local header but my code is not behaving as it suppose . My test libcap file is http://wiki.wireshark.org/SampleCaptures?action=AttachFile&do=view&target=udp_lite_normal_coverage_8-20.pcap --http://www.viste.com/Linux/Server/WireShark/libpcapformat.pdf --http://hackage.haskell.org/packages/archive/bytestring/0.9.0.4/doc/ html/Data-ByteString-Lazy.html import Data.List import qualified Data.ByteString.Lazy as BS import qualified Data.ByteString.Lazy.Char8 as B import Control.Monad import Text.Printf import Data.Word import Data.Char import System.Time import Numeric import System.Environment hexTodec :: BS.ByteString -> Integer hexTodec lst = read $ "0x" ++ ( concatMap ( \x -> showHex x "" ) $ BS.unpack lst ) parseFile :: BS.ByteString -> Bool -> IO [ BS.ByteString ] parseFile xs revflag | BS.null xs = return [] | otherwise = do let ind =if revflag then hexTodec . BS.reverse . BS.take 4 . BS.drop 8 $ xs else hexTodec . BS.take 4 . BS.drop 8 $ xs print ind let ( x , ys ) = BS.splitAt ( fromIntegral ind ) xs --BS.putStrLn $ x tmp <- parseFile ys revflag return $ x : tmp main = do [ file ] <- getArgs contents <- BS.readFile file let ( a , rest ) = BS.splitAt 24 contents --strip global header let revflag = case BS.unpack $ BS.take 4 a of [ 0xd4 , 0xc3 , 0xb2 , 0xa1 ] -> True _ -> False p <- parseFile rest revflag print $ p !! 0 BS.putStr $ p !! 0 Regards Mukesh Tiwari
participants (4)
-
malcolm.wallace
-
Mike Dillon
-
mukesh tiwari
-
Neil Davies