-- Hoogle documentation, generated by Haddock -- See Hoogle, http://www.haskell.org/hoogle/ -- | pcap interface -- -- FFI Wrapper around libpcap @package pcap @version 0.2 -- | The Pcap modules is a binding to all of the functions in -- libpcap (See http://www.tcpdump.org for more information.) -- -- Only a minimum of mashalling is done; for light duty applications, the -- user can 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 Pcap
--   import Foreign
--   
--   main = do
--   	let
--   		printIt :: PktHdr -> Ptr Word8 -> IO ()
--   		printIt ph bytep = do
--           		a <- peekArray (fromIntegral (caplen ph)) bytep 
--          			print a
--   
--           p <- openLive "em0" 100 True 10000
--           s <- withForeignPtr p $ \ptr -> do
--                   dispatch ptr (-1) printIt
--           return ()
--   
-- -- Users requiring higher perfomance (such as O(1) access to any byte in -- a packet) should roll their own marshalling functions. -- -- 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 BDS's struct sockaddr. See W.R.Stevens, TCP -- Illustrated, volume 2, for further eluciadation. -- -- This binding should be portable for systems that can use the libpcap -- from tcpdump.org. It will not work with Winpcap, a similar library for -- Windows, although adapting it should not prove difficult. module Network.Pcap -- | packet capture descriptor type Pcap = ForeignPtr PcapTag -- | savefile descriptor type Pdump = ForeignPtr PcapDumpTag -- | 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 () -- | 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 -- | 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 -- | PPP over serial with HDLC encapsulation DLT_PPP_SERIAL :: Link -- | PPP over ethernet DLT_PPP_ETHER :: Link -- | Cisco HDLC DLT_C_HDLC :: Link -- | IEEE 802.11 wireless DLT_IEEE802_11 :: Link -- | OpenBSD loopback device DLT_LOOP :: 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 -- | 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 ifAddr :: PcapAddr -> SockAddr -- | network mask ifMask :: PcapAddr -> Maybe SockAddr -- | broadcast address ifBcast :: PcapAddr -> Maybe SockAddr -- | address of peer, of a point-to-point link ifPeer :: PcapAddr -> Maybe SockAddr -- | The socket address record. Note that this is not the same as SockAddr -- from Network.Sockets. (That is a Haskell version of struct -- sockaddr_in. This is the real struct sockaddr from the BSD network -- stack.) data SockAddr SockAddr :: Family -> [Word8] -> SockAddr -- | an address family exported by Network.Socket sockAddrFamily :: SockAddr -> Family sockAddrAddr :: SockAddr -> [Word8] -- | 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) sec :: PktHdr -> Word32 -- | timestamp (microseconds) usec :: PktHdr -> Word32 -- | number of bytes present in capture caplen :: PktHdr -> Word32 -- | number of bytes on the wire len :: PktHdr -> Word32 data Statistics Statistics :: Word32 -> Word32 -> Word32 -> Statistics -- | packets received recv :: Statistics -> Word32 -- | packets dropped by libpcap drop :: Statistics -> Word32 -- | packets dropped by the interface ifdrop :: Statistics -> Word32 -- | openOffline opens a "savefile" for reading. The file foramt is the as -- used for tcpdump. The string "-" is a synonym for stdin. openOffline :: String -> IO Pcap -- | openLive is used to get a packet descriptor that can be used to look -- at packates 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 Pcap -- | 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 linktype and the snapshot length. openDead :: Link -> Int -> IO Pcap -- | openDump opens a "savefile" for writing. This savefile is written to -- by the dump function. The arguments are a raw packet capture -- descriptor and the filename, with "-" as a synonym for stdout. openDump :: Ptr PcapTag -> String -> 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 Address 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 descripto must have been obtaine from openLive. setNonBlock :: Ptr PcapTag -> Bool -> IO () -- | Return the blocking status of the packet capture descriptor. Ture -- indicates that the descriptor is non-blocking. Descriptors referring -- savefiles opened by openDump always reutre False. getNonBlock :: Ptr PcapTag -> IO Bool -- | 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 savefile (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. -- -- It 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 (by 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 -- savefile 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 () -- | 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 -- | Major version number of the library. majorVersion :: Ptr PcapTag -> IO Int -- | Minor version number of the library. minorVersion :: Ptr PcapTag -> IO Int -- | isSwapped is True if the current savefile 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 Read Network instance Show Network instance Read SockAddr instance Show SockAddr instance Read PcapAddr instance Show PcapAddr instance Read Interface instance Show Interface instance Show Statistics instance Show PktHdr