Skip to content

Instantly share code, notes, and snippets.

@commandodev
Created July 26, 2012 09:12

Revisions

  1. Ben Ford revised this gist Jul 26, 2012. 1 changed file with 6 additions and 1 deletion.
    7 changes: 6 additions & 1 deletion Data.Pcap.Source.hs
    Original file line number Diff line number Diff line change
    @@ -7,6 +7,7 @@ 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
    @@ -33,8 +34,12 @@ hdrCB :: PktHdr -> DateTime
    hdrCB = todt. toRational . hdrDiffTime

    packetCB :: ByteString -> Either String Quote
    packetCB = parseOnly parseQuote
    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
  2. Ben Ford created this gist Jul 26, 2012.
    44 changes: 44 additions & 0 deletions Data.Pcap.Source.hs
    Original file line number Diff line number Diff line change
    @@ -0,0 +1,44 @@
    {-# 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.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

    parsePcap fh = sourcePcap fh hdrCB packetCB >+> matches

    matches = CL.filter isRight

    isRight (a, b) = case b of
    (Right _) -> True
    otherwise -> False