-- Hoogle documentation, generated by Haddock -- See Hoogle, http://www.haskell.org/hoogle/ -- | A system-independent interface for user-level packet capture -- -- A system-independent interface for user-level packet capture @package pcap @version 0.4.5 -- | The Network.Pcap.Base module is a low-level binding to all of -- the functions in libpcap. See http://www.tcpdump.org -- for more information. -- -- Only a minimum of marshaling is done. For a higher-level interface -- that's more friendly, use the Network.Pcap module. -- -- To convert captured packet data to a list, extract the length of the -- captured buffer from the packet header record and use peekArray -- to convert the captured data to a list. For illustration: -- --
--   import Network.Pcap.Base
--   import Foreign.Marshal.Array (peekArray)
--   
--   main = do
--          let printIt :: PktHdr -> Ptr Word8 -> IO ()
--   	printIt ph bytep = do
--             a <- peekArray (fromIntegral (hdrCaptureLength ph)) bytep 
--          	  print a
--   
--       p <- openLive "em0" 100 True 10000
--       s <- withForeignPtr p $ \ptr -> do
--              dispatch ptr (-1) printIt
--       return ()
--   
-- -- Note that the SockAddr exported here is not the -- SockAddr from Network.Socket. The SockAddr -- from Network.Socket corresponds to struct -- sockaddr_in in BSD terminology. The SockAddr record here -- is BSD's struct sockaddr. See W.R.Stevens, TCP Illustrated, -- volume 2, for further elucidation. -- -- This binding should be portable across systems that can use the -- libpcap library from tcpdump.org. It will not work -- with Winpcap, a similar library for Windows, although adapting it -- should not prove difficult. module Network.Pcap.Base data PcapTag -- | packet capture descriptor data PcapDumpTag -- | dump file descriptor type Pdump = ForeignPtr PcapDumpTag -- | Compiled Berkeley Packet Filter program type BpfProgram = ForeignPtr BpfProgramTag data BpfProgramTag -- | the type of the callback function passed to dispatch or -- loop. type Callback = PktHdr -> Ptr Word8 -> IO () -- | The direction in which packets are to be captured. See -- setDirection. data Direction -- | incoming and outgoing packets (the default InOut :: Direction -- | incoming packets In :: Direction -- | outgoing packets Out :: Direction -- | Datalink types. -- -- This covers all of the datalink types defined in bpf.h. Types defined -- on your system may vary. data Link -- | no link layer encapsulation DLT_NULL :: Link -- | unknown encapsulation DLT_UNKNOWN :: Int -> Link -- | 10 Mbit per second (or faster) ethernet DLT_EN10MB :: Link -- | original 3 Mbit per second ethernet DLT_EN3MB :: Link -- | amateur radio AX.25 DLT_AX25 :: Link -- | Proteon ProNET Token Ring DLT_PRONET :: Link -- | Chaos DLT_CHAOS :: Link -- | IEEE 802 networks DLT_IEEE802 :: Link -- | ARCNET DLT_ARCNET :: Link -- | Serial line IP DLT_SLIP :: Link -- | Point-to-point protocol DLT_PPP :: Link -- | FDDI DLT_FDDI :: Link -- | LLC SNAP encapsulated ATM DLT_ATM_RFC1483 :: Link -- | raw IP DLT_RAW :: Link -- | BSD OS serial line IP DLT_SLIP_BSDOS :: Link -- | BSD OS point-to-point protocol DLT_PPP_BSDOS :: Link -- | Linux classical IP over ATM DLT_ATM_CLIP :: Link -- | Redback SmartEdge 400/800 DLT_REDBACK_SMARTEDGE :: Link -- | PPP over serial with HDLC encapsulation DLT_PPP_SERIAL :: Link -- | PPP over ethernet DLT_PPP_ETHER :: Link -- | Symantec Enterprise Firewall DLT_SYMANTEC_FIREWALL :: Link -- | Cisco HDLC DLT_C_HDLC :: Link -- | IEEE 802.11 wireless DLT_IEEE802_11 :: Link -- | Frame Relay DLT_FRELAY :: Link -- | OpenBSD loopback device DLT_LOOP :: Link -- | Encapsulated packets for IPsec DLT_ENC :: Link -- | Linux cooked sockets DLT_LINUX_SLL :: Link -- | Apple LocalTalk DLT_LTALK :: Link -- | Acorn Econet DLT_ECONET :: Link -- | OpenBSD's old ipfilter DLT_IPFILTER :: Link -- | OpenBSD's pflog DLT_PFLOG :: Link -- | Cisco IOS DLT_CISCO_IOS :: Link -- | Intersil Prism II wireless chips DLT_PRISM_HEADER :: Link -- | Aironet (Cisco) 802.11 wireless DLT_AIRONET_HEADER :: Link -- | Siemens HiPath HDLC DLT_HHDLC :: Link -- | RFC 2625 IP-over-Fibre Channel DLT_IP_OVER_FC :: Link -- | Full Frontal ATM on Solaris with SunATM DLT_SUNATM :: Link -- |
    --
  1. 11 plus a number of bits of link-layer information
  2. --
DLT_IEEE802_11_RADIO :: Link -- | Linux ARCNET header DLT_ARCNET_LINUX :: Link -- | Apple IP-over-IEEE 1394 DLT_APPLE_IP_OVER_IEEE1394 :: Link -- | SS7, C7 MTP2 with pseudo-header DLT_MTP2_WITH_PHDR :: Link -- | SS7, C7 Message Transfer Part 2 (MPT2) DLT_MTP2 :: Link -- | SS7, C7 Message Transfer Part 3 (MPT3) DLT_MTP3 :: Link -- | SS7, C7 SCCP DLT_SCCP :: Link -- | DOCSIS MAC frame DLT_DOCSIS :: Link -- | Linux IrDA packet DLT_LINUX_IRDA :: Link -- | Reserved for private use DLT_USER0 :: Link -- | Reserved for private use DLT_USER1 :: Link -- | Reserved for private use DLT_USER2 :: Link -- | Reserved for private use DLT_USER3 :: Link -- | Reserved for private use DLT_USER4 :: Link -- | Reserved for private use DLT_USER5 :: Link -- | Reserved for private use DLT_USER6 :: Link -- | Reserved for private use DLT_USER7 :: Link -- | Reserved for private use DLT_USER8 :: Link -- | Reserved for private use DLT_USER9 :: Link -- | Reserved for private use DLT_USER10 :: Link -- | Reserved for private use DLT_USER11 :: Link -- | Reserved for private use DLT_USER12 :: Link -- | Reserved for private use DLT_USER13 :: Link -- | Reserved for private use DLT_USER14 :: Link -- | Reserved for private use DLT_USER15 :: Link -- | Outgoing packets for ppp daemon DLT_PPP_PPPD :: Link -- | GPRS LLC DLT_GPRS_LLC :: Link -- | GPF-T (ITU-T G.7041/Y.1303) DLT_GPF_T :: Link -- | GPF-F (ITU-T G.7041/Y.1303) DLT_GPF_F :: Link -- | Raw LAPD for vISDN (not generic LAPD) DLT_LINUX_LAPD :: Link -- | ARINC 429 DLT_A429 :: Link -- | ARINC 653 Interpartition Communication messages DLT_A653_ICM :: Link -- | USB packet DLT_USB :: Link -- | Bluetooth HCI UART transport layer (part H:4) DLT_BLUETOOTH_HCI_H4 :: Link -- | Multi Link Frame Relay (FRF.16) DLT_MFR :: Link -- | IEEE 802.16 MAC Common Part Sublayer DLT_IEEE802_16_MAC_CPS :: Link -- | USB packets, beginning with a Linux USB header DLT_USB_LINUX :: Link -- | Controller Area Network (CAN) v2.0B DLT_CAN20B :: Link -- | IEEE 802.15.4, with address fields padded DLT_IEEE802_15_4_LINUX :: Link -- | Per Packet Information encapsulated packets DLT_PPI :: Link -- |
    --
  1. 16 MAC Common Part Sublayer with radiotap radio header
  2. --
DLT_IEEE802_16_MAC_CPS_RADIO :: Link -- | IEEE 802.15.4, exactly as in the spec DLT_IEEE802_15_4 :: Link -- | The interface structure. data Interface Interface :: String -> String -> [PcapAddr] -> Word32 -> Interface -- | the interface name ifName :: Interface -> String -- | interface description string (if any) ifDescription :: Interface -> String -- | address families supported by this interface ifAddresses :: Interface -> [PcapAddr] ifFlags :: Interface -> Word32 -- | The address structure. data PcapAddr PcapAddr :: SockAddr -> Maybe SockAddr -> Maybe SockAddr -> Maybe SockAddr -> PcapAddr -- | interface address addrSA :: PcapAddr -> SockAddr -- | network mask addrMask :: PcapAddr -> Maybe SockAddr -- | broadcast address addrBcast :: PcapAddr -> Maybe SockAddr -- | address of peer, of a point-to-point link addrPeer :: PcapAddr -> Maybe SockAddr -- | The socket address record. Note that this is not the same as SockAddr -- from Network.Socket. (That is a Haskell version of C's -- struct sockaddr_in. This is the real struct sockaddr -- from the BSD network stack.) data SockAddr SockAddr :: !!Family -> !!ByteString -> SockAddr -- | an address family exported by Network.Socket saFamily :: SockAddr -> !!Family saAddr :: SockAddr -> !!ByteString -- | The network address record. Both the address and mask are in network -- byte order. data Network Network :: !!Word32 -> !!Word32 -> Network -- | IPv4 network address netAddr :: Network -> !!Word32 -- | IPv4 netmask netMask :: Network -> !!Word32 data PktHdr PktHdr :: !!Word32 -> !!Word32 -> !!Word32 -> !!Word32 -> PktHdr -- | timestamp (seconds) hdrSeconds :: PktHdr -> !!Word32 -- | timestamp (microseconds) hdrUseconds :: PktHdr -> !!Word32 -- | number of bytes present in capture hdrCaptureLength :: PktHdr -> !!Word32 -- | number of bytes on the wire hdrWireLength :: PktHdr -> !!Word32 data Statistics Statistics :: !!Word32 -> !!Word32 -> !!Word32 -> Statistics -- | packets received statReceived :: Statistics -> !!Word32 -- | packets dropped by libpcap statDropped :: Statistics -> !!Word32 -- | packets dropped by the network interface statIfaceDropped :: Statistics -> !!Word32 -- | openOffline opens a dump file for reading. The file format is -- the same as used by tcpdump and Wireshark. The string -- "-" is a synonym for stdin. openOffline :: FilePath -> IO (ForeignPtr PcapTag) -- | openLive is used to get a packet descriptor that can be used to -- look at packets on the network. The arguments are the device name, the -- snapshot legnth (in bytes), the promiscuity of the interface -- (True == promiscuous) and a timeout in milliseconds. -- -- Using "any" as the device name will capture packets from all -- interfaces. On some systems, reading from the "any" device is -- incompatible with setting the interfaces into promiscuous mode. In -- that case, only packets whose link layer addresses match those of the -- interfaces are captured. openLive :: String -> Int -> Bool -> Int -> IO (ForeignPtr PcapTag) -- | openDead is used to get a packet capture descriptor without -- opening a file or device. It is typically used to test packet filter -- compilation by setFilter. The arguments are the link type and -- the snapshot length. openDead :: Link -> Int -> IO (ForeignPtr PcapTag) -- | openDump opens a dump file for writing. This dump file is -- written to by the dump function. The arguments are a raw packet -- capture descriptor and the file name, with "-" as a synonym for -- stdout. openDump :: Ptr PcapTag -> FilePath -> IO Pdump -- | Set a filter on the specified packet capture descriptor. Valid filter -- strings are those accepted by tcpdump. setFilter :: Ptr PcapTag -> String -> Bool -> Word32 -> IO () -- | Compile a filter for use by another program using the Berkeley Packet -- Filter library. compileFilter :: Int -> Link -> String -> Bool -> Word32 -> IO BpfProgram -- | lookupDev returns the name of a device suitable for use with -- openLive and lookupNet. If you only have one interface, -- it is the function of choice. If not, see findAllDevs. lookupDev :: IO String -- | findAllDevs returns a list of all the network devices that can -- be opened by openLive. It returns only those devices that the -- calling process has sufficient privileges to open, so it may not find -- every device on the system. findAllDevs :: IO [Interface] -- | Return the network address and mask for the specified interface name. -- Only valid for IPv4. For other protocols, use findAllDevs and -- search the Interface list for the associated network mask. lookupNet :: String -> IO Network -- | Set a packet capture descriptor into non-blocking mode if the second -- argument is True, otherwise put it in blocking mode. Note that -- the packet capture descriptor must have been obtaine from -- openLive. setNonBlock :: Ptr PcapTag -> Bool -> IO () -- | Return the blocking status of the packet capture descriptor. -- True indicates that the descriptor is non-blocking. Descriptors -- referring to dump files opened by openDump always return -- False. getNonBlock :: Ptr PcapTag -> IO Bool -- | Specify the direction in which packets are to be captured. Complete -- functionality is not necessarily available on all platforms. setDirection :: Ptr PcapTag -> Direction -> IO () -- | Returns the datalink type associated with the given pcap descriptor. datalink :: Ptr PcapTag -> IO Link -- | Sets the datalink type for a given pcap descriptor. setDatalink :: Ptr PcapTag -> Link -> IO () -- | List all the datalink types supported by a pcap descriptor. Entries -- from the resulting list are valid arguments to setDatalink. listDatalinks :: Ptr PcapTag -> IO [Link] -- | Collect and process packets. The arguments are the packet capture -- descriptor, the count and a callback function. -- -- The count is the maximum number of packets to process before -- returning. A count of -1 means process all of the packets received in -- one buffer (if a live capture) or all of the packets in a dump file -- (if offline). -- -- The callback function is passed two arguments, a packet header record -- and a pointer to the packet data (Ptr Word8). THe header -- record contains the number of bytes captured, whcih can be used to -- marshal the data into a list or array. dispatch :: Ptr PcapTag -> Int -> Callback -> IO Int -- | Similar to dispatch, but loop until the number of packets -- specified by the second argument are read. A negative value loops -- forever. -- -- This function does not return when a live read tiemout occurs. Use -- dispatch instead if you wnat to specify a timeout. loop :: Ptr PcapTag -> Int -> Callback -> IO Int -- | Read the next packet (equivalent to calling dispatch with a -- count of 1). next :: Ptr PcapTag -> IO (PktHdr, Ptr Word8) -- | Write the packet data given by the second and third arguments to a -- dump file opened by openDead. dump is designed so it can -- be easily used as a default callback function by dispatch or -- loop. dump :: Ptr PcapDumpTag -> Ptr PktHdr -> Ptr Word8 -> IO () -- | Send a raw packet through the network interface. sendPacket :: Ptr PcapTag -> Ptr Word8 -> Int -> IO () toPktHdr :: Ptr PktHdr -> IO PktHdr -- | Returns the number of packets received, the number of packets dropped -- by the packet filter and the number of packets dropped by the -- interface (before processing by the packet filter). statistics :: Ptr PcapTag -> IO Statistics -- | Version of the library. The returned pair consists of the major and -- minor version numbers. version :: Ptr PcapTag -> IO (Int, Int) -- | isSwapped returns True if the current dump file uses a -- different byte order than the one native to the system. isSwapped :: Ptr PcapTag -> IO Bool -- | The snapshot length that was used in the call to openLive. snapshotLen :: Ptr PcapTag -> IO Int instance Eq Link instance Ord Link instance Read Link instance Show Link instance Eq Direction instance Show Direction instance Read Direction instance Eq Network instance Read Network instance Show Network instance Eq SockAddr instance Read SockAddr instance Show SockAddr instance Eq PcapAddr instance Read PcapAddr instance Show PcapAddr instance Eq Interface instance Read Interface instance Show Interface instance Eq Statistics instance Show Statistics instance Eq PktHdr instance Show PktHdr -- | The Network.Pcap module is a high(ish) level binding to all -- of the functions in libpcap. See -- http://www.tcpdump.org for more information. -- -- This module is built on the lower-level Network.Pcap.Base -- module, which is slightly more efficient. Don't use -- Network.Pcap.Base unless profiling data indicates that you -- need to. -- -- Only a minimum of marshaling is done on received packets. To convert -- captured packet data to a ByteString (space efficient, and with -- O(1) access to every byte in a captured packet), use -- toBS. -- -- Note that the SockAddr exported here is not the -- SockAddr from Network.Socket. The SockAddr -- from Network.Socket corresponds to struct -- sockaddr_in in BSD terminology. The SockAddr record here -- is BSD's struct sockaddr. See W.R.Stevens, TCP Illustrated, -- volume 2, for further elucidation. -- -- This binding should be portable across systems that can use the -- libpcap from tcpdump.org. It does not yet work with -- Winpcap, a similar library for Windows, although adapting it should -- not prove difficult. module Network.Pcap -- | packet capture handle data PcapHandle -- | dump file handle data DumpHandle -- | Compiled Berkeley Packet Filter program type BpfProgram = ForeignPtr BpfProgramTag -- | the type of the callback function passed to dispatch or -- loop. type Callback = PktHdr -> Ptr Word8 -> IO () -- | callback using ByteString for packet body type CallbackBS = PktHdr -> ByteString -> IO () -- | The direction in which packets are to be captured. See -- setDirection. data Direction -- | incoming and outgoing packets (the default InOut :: Direction -- | incoming packets In :: Direction -- | outgoing packets Out :: Direction -- | Datalink types. -- -- This covers all of the datalink types defined in bpf.h. Types defined -- on your system may vary. data Link -- | no link layer encapsulation DLT_NULL :: Link -- | unknown encapsulation DLT_UNKNOWN :: Int -> Link -- | 10 Mbit per second (or faster) ethernet DLT_EN10MB :: Link -- | original 3 Mbit per second ethernet DLT_EN3MB :: Link -- | amateur radio AX.25 DLT_AX25 :: Link -- | Proteon ProNET Token Ring DLT_PRONET :: Link -- | Chaos DLT_CHAOS :: Link -- | IEEE 802 networks DLT_IEEE802 :: Link -- | ARCNET DLT_ARCNET :: Link -- | Serial line IP DLT_SLIP :: Link -- | Point-to-point protocol DLT_PPP :: Link -- | FDDI DLT_FDDI :: Link -- | LLC SNAP encapsulated ATM DLT_ATM_RFC1483 :: Link -- | raw IP DLT_RAW :: Link -- | BSD OS serial line IP DLT_SLIP_BSDOS :: Link -- | BSD OS point-to-point protocol DLT_PPP_BSDOS :: Link -- | Linux classical IP over ATM DLT_ATM_CLIP :: Link -- | Redback SmartEdge 400/800 DLT_REDBACK_SMARTEDGE :: Link -- | PPP over serial with HDLC encapsulation DLT_PPP_SERIAL :: Link -- | PPP over ethernet DLT_PPP_ETHER :: Link -- | Symantec Enterprise Firewall DLT_SYMANTEC_FIREWALL :: Link -- | Cisco HDLC DLT_C_HDLC :: Link -- | IEEE 802.11 wireless DLT_IEEE802_11 :: Link -- | Frame Relay DLT_FRELAY :: Link -- | OpenBSD loopback device DLT_LOOP :: Link -- | Encapsulated packets for IPsec DLT_ENC :: Link -- | Linux cooked sockets DLT_LINUX_SLL :: Link -- | Apple LocalTalk DLT_LTALK :: Link -- | Acorn Econet DLT_ECONET :: Link -- | OpenBSD's old ipfilter DLT_IPFILTER :: Link -- | OpenBSD's pflog DLT_PFLOG :: Link -- | Cisco IOS DLT_CISCO_IOS :: Link -- | Intersil Prism II wireless chips DLT_PRISM_HEADER :: Link -- | Aironet (Cisco) 802.11 wireless DLT_AIRONET_HEADER :: Link -- | Siemens HiPath HDLC DLT_HHDLC :: Link -- | RFC 2625 IP-over-Fibre Channel DLT_IP_OVER_FC :: Link -- | Full Frontal ATM on Solaris with SunATM DLT_SUNATM :: Link -- |
    --
  1. 11 plus a number of bits of link-layer information
  2. --
DLT_IEEE802_11_RADIO :: Link -- | Linux ARCNET header DLT_ARCNET_LINUX :: Link -- | Apple IP-over-IEEE 1394 DLT_APPLE_IP_OVER_IEEE1394 :: Link -- | SS7, C7 MTP2 with pseudo-header DLT_MTP2_WITH_PHDR :: Link -- | SS7, C7 Message Transfer Part 2 (MPT2) DLT_MTP2 :: Link -- | SS7, C7 Message Transfer Part 3 (MPT3) DLT_MTP3 :: Link -- | SS7, C7 SCCP DLT_SCCP :: Link -- | DOCSIS MAC frame DLT_DOCSIS :: Link -- | Linux IrDA packet DLT_LINUX_IRDA :: Link -- | Reserved for private use DLT_USER0 :: Link -- | Reserved for private use DLT_USER1 :: Link -- | Reserved for private use DLT_USER2 :: Link -- | Reserved for private use DLT_USER3 :: Link -- | Reserved for private use DLT_USER4 :: Link -- | Reserved for private use DLT_USER5 :: Link -- | Reserved for private use DLT_USER6 :: Link -- | Reserved for private use DLT_USER7 :: Link -- | Reserved for private use DLT_USER8 :: Link -- | Reserved for private use DLT_USER9 :: Link -- | Reserved for private use DLT_USER10 :: Link -- | Reserved for private use DLT_USER11 :: Link -- | Reserved for private use DLT_USER12 :: Link -- | Reserved for private use DLT_USER13 :: Link -- | Reserved for private use DLT_USER14 :: Link -- | Reserved for private use DLT_USER15 :: Link -- | Outgoing packets for ppp daemon DLT_PPP_PPPD :: Link -- | GPRS LLC DLT_GPRS_LLC :: Link -- | GPF-T (ITU-T G.7041/Y.1303) DLT_GPF_T :: Link -- | GPF-F (ITU-T G.7041/Y.1303) DLT_GPF_F :: Link -- | Raw LAPD for vISDN (not generic LAPD) DLT_LINUX_LAPD :: Link -- | ARINC 429 DLT_A429 :: Link -- | ARINC 653 Interpartition Communication messages DLT_A653_ICM :: Link -- | USB packet DLT_USB :: Link -- | Bluetooth HCI UART transport layer (part H:4) DLT_BLUETOOTH_HCI_H4 :: Link -- | Multi Link Frame Relay (FRF.16) DLT_MFR :: Link -- | IEEE 802.16 MAC Common Part Sublayer DLT_IEEE802_16_MAC_CPS :: Link -- | USB packets, beginning with a Linux USB header DLT_USB_LINUX :: Link -- | Controller Area Network (CAN) v2.0B DLT_CAN20B :: Link -- | IEEE 802.15.4, with address fields padded DLT_IEEE802_15_4_LINUX :: Link -- | Per Packet Information encapsulated packets DLT_PPI :: Link -- |
    --
  1. 16 MAC Common Part Sublayer with radiotap radio header
  2. --
DLT_IEEE802_16_MAC_CPS_RADIO :: Link -- | IEEE 802.15.4, exactly as in the spec DLT_IEEE802_15_4 :: Link -- | The interface structure. data Interface Interface :: String -> String -> [PcapAddr] -> Word32 -> Interface -- | the interface name ifName :: Interface -> String -- | interface description string (if any) ifDescription :: Interface -> String -- | address families supported by this interface ifAddresses :: Interface -> [PcapAddr] ifFlags :: Interface -> Word32 -- | The address structure. data PcapAddr PcapAddr :: SockAddr -> Maybe SockAddr -> Maybe SockAddr -> Maybe SockAddr -> PcapAddr -- | interface address addrSA :: PcapAddr -> SockAddr -- | network mask addrMask :: PcapAddr -> Maybe SockAddr -- | broadcast address addrBcast :: PcapAddr -> Maybe SockAddr -- | address of peer, of a point-to-point link addrPeer :: PcapAddr -> Maybe SockAddr -- | The socket address record. Note that this is not the same as SockAddr -- from Network.Socket. (That is a Haskell version of C's -- struct sockaddr_in. This is the real struct sockaddr -- from the BSD network stack.) data SockAddr SockAddr :: !!Family -> !!ByteString -> SockAddr -- | an address family exported by Network.Socket saFamily :: SockAddr -> !!Family saAddr :: SockAddr -> !!ByteString -- | The network address record. Both the address and mask are in network -- byte order. data Network Network :: !!Word32 -> !!Word32 -> Network -- | IPv4 network address netAddr :: Network -> !!Word32 -- | IPv4 netmask netMask :: Network -> !!Word32 data PktHdr PktHdr :: !!Word32 -> !!Word32 -> !!Word32 -> !!Word32 -> PktHdr -- | timestamp (seconds) hdrSeconds :: PktHdr -> !!Word32 -- | timestamp (microseconds) hdrUseconds :: PktHdr -> !!Word32 -- | number of bytes present in capture hdrCaptureLength :: PktHdr -> !!Word32 -- | number of bytes on the wire hdrWireLength :: PktHdr -> !!Word32 data Statistics Statistics :: !!Word32 -> !!Word32 -> !!Word32 -> Statistics -- | packets received statReceived :: Statistics -> !!Word32 -- | packets dropped by libpcap statDropped :: Statistics -> !!Word32 -- | packets dropped by the network interface statIfaceDropped :: Statistics -> !!Word32 -- | openOffline opens a dump file for reading. The file format is -- the same as used by tcpdump and Wireshark. The string -- "-" is a synonym for stdin. openOffline :: FilePath -> IO PcapHandle -- | openLive is used to get a PcapHandle that can be used to -- look at packets on the network. The arguments are the device name, the -- snapshot length (in bytes), the promiscuity of the interface -- (True == promiscuous) and a timeout in microseconds. -- -- The timeout allows the packet filter to delay while accumulating -- multiple packets, which is more efficient than reading packets one by -- one. A timeout of zero will wait indefinitely for "enough" packets to -- arrive. -- -- Using "any" as the device name will capture packets from all -- interfaces. On some systems, reading from the "any" device is -- incompatible with setting the interfaces into promiscuous mode. In -- that case, only packets whose link layer addresses match those of the -- interfaces are captured. openLive :: String -> Int -> Bool -> Int64 -> IO PcapHandle -- | openDead is used to get a PcapHandle without opening a -- file or device. It is typically used to test packet filter compilation -- by setFilter. The arguments are the link type and the snapshot -- length. openDead :: Link -> Int -> IO PcapHandle -- | openDump opens a dump file for writing. This dump file is -- written to by the dump function. openDump :: PcapHandle -> FilePath -> IO DumpHandle -- | Set a filter on the specified packet capture handle. Valid filter -- strings are those accepted by tcpdump. setFilter :: PcapHandle -> String -> Bool -> Word32 -> IO () -- | Compile a filter for use by another program using the Berkeley Packet -- Filter library. compileFilter :: Int -> Link -> String -> Bool -> Word32 -> IO BpfProgram -- | lookupDev returns the name of a device suitable for use with -- openLive and lookupNet. If you only have one interface, -- it is the function of choice. If not, see findAllDevs. lookupDev :: IO String -- | findAllDevs returns a list of all the network devices that can -- be opened by openLive. It returns only those devices that the -- calling process has sufficient privileges to open, so it may not find -- every device on the system. findAllDevs :: IO [Interface] -- | Return the network address and mask for the specified interface name. -- Only valid for IPv4. For other protocols, use findAllDevs and -- search the Interface list for the associated network mask. lookupNet :: String -> IO Network -- | Set the given PcapHandle into non-blocking mode if the second -- argument is True, otherwise put it in blocking mode. Note that -- the PcapHandle must have been obtained from openLive. setNonBlock :: PcapHandle -> Bool -> IO () -- | Return the blocking status of the PcapHandle. True -- indicates that the handle is non-blocking. Handles referring to dump -- files opened by openDump always return False. getNonBlock :: PcapHandle -> IO Bool -- | Specify the direction in which packets are to be captured. Complete -- functionality is not necessarily available on all platforms. setDirection :: PcapHandle -> Direction -> IO () -- | Returns the datalink type associated with the given handle. datalink :: PcapHandle -> IO Link -- | Sets the datalink type for the given handle. setDatalink :: PcapHandle -> Link -> IO () -- | List all the datalink types supported by the given handle. Entries -- from the resulting list are valid arguments to setDatalink. listDatalinks :: PcapHandle -> IO [Link] -- | Collect and process packets. -- -- The count is the maximum number of packets to process before -- returning. A count of -1 means process all of the packets received in -- one buffer (if a live capture) or all of the packets in a dump file -- (if offline). -- -- The callback function is passed two arguments, a packet header record -- and a pointer to the packet data (Ptr Word8). THe header -- record contains the number of bytes captured, whcih can be used to -- marshal the data into a list, array, or ByteString (using -- toBS). dispatch :: PcapHandle -> Int -> Callback -> IO Int -- | Similar to dispatch, but loop until the number of packets -- specified by the second argument are read. A negative value loops -- forever. -- -- This function does not return when a live read tiemout occurs. Use -- dispatch instead if you wnat to specify a timeout. loop :: PcapHandle -> Int -> Callback -> IO Int -- | Read the next packet (equivalent to calling dispatch with a -- count of 1). next :: PcapHandle -> IO (PktHdr, Ptr Word8) -- | Write the packet data given by the second and third arguments to a -- dump file opened by openDead. dump is designed so it can -- be easily used as a default callback function by dispatch or -- loop. dump :: DumpHandle -> Ptr PktHdr -> Ptr Word8 -> IO () -- | Variant of dispatch for use with ByteString. dispatchBS :: PcapHandle -> Int -> CallbackBS -> IO Int -- | Variant of loop for use with ByteString. loopBS :: PcapHandle -> Int -> CallbackBS -> IO Int nextBS :: PcapHandle -> IO (PktHdr, ByteString) dumpBS :: DumpHandle -> Ptr PktHdr -> ByteString -> IO () -- | Send a raw packet through the network interface. sendPacket :: PcapHandle -> Ptr Word8 -> Int -> IO () -- | Variant of sendPacket for use with ByteString. sendPacketBS :: PcapHandle -> ByteString -> IO () -- | Represent a captured packet as a ByteString. Suitable for use -- as is with the result of next, or use curry -- toBS inside a Callback with dispatch. toBS :: (PktHdr, Ptr Word8) -> IO (PktHdr, ByteString) -- | Get the timestamp of a packet as a single quantity, in microseconds. hdrTime :: PktHdr -> Int64 -- | Get the timestamp of a packet as a DiffTime. hdrDiffTime :: PktHdr -> DiffTime -- | Returns the number of packets received, the number of packets dropped -- by the packet filter and the number of packets dropped by the -- interface (before processing by the packet filter). statistics :: PcapHandle -> IO Statistics -- | Version of the library. The returned pair consists of the major and -- minor version numbers. version :: PcapHandle -> IO (Int, Int) -- | isSwapped returns True if the current dump file uses a -- different byte order than the one native to the system. isSwapped :: PcapHandle -> IO Bool -- | The snapshot length that was used in the call to openLive. snapshotLen :: PcapHandle -> IO Int