Skip to content

Instantly share code, notes, and snippets.

@commandodev
Created July 26, 2012 09:12
Show Gist options
  • Star 0 You must be signed in to star a gist
  • Fork 0 You must be signed in to fork a gist
  • Save commandodev/3181144 to your computer and use it in GitHub Desktop.
Save commandodev/3181144 to your computer and use it in GitHub Desktop.
Pcap Conduit
{-# LANGUAGE NoMonomorphismRestriction #-}
module Data.Pcap.Source (
sourcePcap
, parsePcap
) where
import Control.Monad.IO.Class
import qualified Data.ByteString as BS
import Data.Conduit
import qualified Data.Conduit.List as CL
import Data.DateTime
import Data.Void
import Network.Pcap
import System.IO
import Data.Kospi.Parser
type HeaderHandler a = (PktHdr -> a)
type BodyHandler a = (BS.ByteString -> a)
sourcePcap :: FilePath -> (HeaderHandler h) -> (BodyHandler b) -> Pipe Void () (h, b) () IO Int
sourcePcap fh fhdr fbody = do
liftIO (openOffline fh) >>= loopPcap 0
where
loopPcap cnt hdl = do
(hdr, bs) <- liftIO $ nextBS hdl
if (not $ BS.null bs) then
yield (cb hdr bs) >> loopPcap (cnt + 1) hdl
else
return cnt
cb hdr body = (fhdr hdr, fbody body)
hdrCB :: PktHdr -> DateTime
hdrCB = todt. toRational . hdrDiffTime
packetCB :: ByteString -> Either String Quote
packetCB = parseOnly parseQuote -- parseQuote :: Parser Quote
(parsePcap)
:: FilePath
-> Pipe
Void () (DateTime, Either String Quote) () IO Int
parsePcap fh = sourcePcap fh hdrCB packetCB >+> matches
matches = CL.filter isRight
isRight (a, b) = case b of
(Right _) -> True
otherwise -> False
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment