pcap-0.2: pcap interfaceSource codeContentsIndex
Network.Pcap
Portabilitynon-portable
Stabilityexperimental
Maintainernickburlett@mac.com, dominic.steinitz@blueyonder.co.uk
Contents
Types
Device opening
Filter handling
Device utilities
Interface control
Blocking mode
Link layer utilities
Packet processing
Miscellaneous
Description

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.

Synopsis
type Pcap = ForeignPtr PcapTag
type Pdump = ForeignPtr PcapDumpTag
type BpfProgram = ForeignPtr BpfProgramTag
type Callback = PktHdr -> Ptr Word8 -> IO ()
data Link
= DLT_NULL
| DLT_EN10MB
| DLT_EN3MB
| DLT_AX25
| DLT_PRONET
| DLT_CHAOS
| DLT_IEEE802
| DLT_ARCNET
| DLT_SLIP
| DLT_PPP
| DLT_FDDI
| DLT_ATM_RFC1483
| DLT_RAW
| DLT_SLIP_BSDOS
| DLT_PPP_BSDOS
| DLT_ATM_CLIP
| DLT_PPP_SERIAL
| DLT_PPP_ETHER
| DLT_C_HDLC
| DLT_IEEE802_11
| DLT_LOOP
| DLT_LINUX_SLL
| DLT_LTALK
| DLT_ECONET
| DLT_IPFILTER
| DLT_PFLOG
| DLT_CISCO_IOS
| DLT_PRISM_HEADER
| DLT_AIRONET_HEADER
data Interface = Interface {
ifName :: String
ifDescription :: String
ifAddresses :: [PcapAddr]
ifFlags :: Word32
}
data PcapAddr = PcapAddr {
ifAddr :: SockAddr
ifMask :: Maybe SockAddr
ifBcast :: Maybe SockAddr
ifPeer :: Maybe SockAddr
}
data SockAddr = SockAddr {
sockAddrFamily :: Family
sockAddrAddr :: [Word8]
}
data Network = Network {
netAddr :: Word32
netMask :: Word32
}
data PktHdr = PktHdr {
sec :: Word32
usec :: Word32
caplen :: Word32
len :: Word32
}
data Statistics = Statistics {
recv :: Word32
drop :: Word32
ifdrop :: Word32
}
openOffline :: String -> IO Pcap
openLive :: String -> Int -> Bool -> Int -> IO Pcap
openDead :: Link -> Int -> IO Pcap
openDump :: Ptr PcapTag -> String -> IO Pdump
setFilter :: Ptr PcapTag -> String -> Bool -> Word32 -> IO ()
compileFilter :: Int -> Link -> String -> Bool -> Word32 -> IO BpfProgram
lookupDev :: IO String
findAllDevs :: IO [Interface]
lookupNet :: String -> IO Network
setNonBlock :: Ptr PcapTag -> Bool -> IO ()
getNonBlock :: Ptr PcapTag -> IO Bool
datalink :: Ptr PcapTag -> IO Link
setDatalink :: Ptr PcapTag -> Link -> IO ()
listDatalinks :: Ptr PcapTag -> IO [Link]
dispatch :: Ptr PcapTag -> Int -> Callback -> IO Int
loop :: Ptr PcapTag -> Int -> Callback -> IO Int
next :: Ptr PcapTag -> IO (PktHdr, Ptr Word8)
dump :: Ptr PcapDumpTag -> Ptr PktHdr -> Ptr Word8 -> IO ()
statistics :: Ptr PcapTag -> IO Statistics
majorVersion :: Ptr PcapTag -> IO Int
minorVersion :: Ptr PcapTag -> IO Int
isSwapped :: Ptr PcapTag -> IO Bool
snapshotLen :: Ptr PcapTag -> IO Int
Types
type Pcap = ForeignPtr PcapTagSource
packet capture descriptor
type Pdump = ForeignPtr PcapDumpTagSource
savefile descriptor
type BpfProgram = ForeignPtr BpfProgramTagSource
Compiled Berkeley Packet Filter program
type Callback = PktHdr -> Ptr Word8 -> IO ()Source
the type of the callback function passed to dispatch or loop.
data Link Source

Datalink types.

This covers all of the datalink types defined in bpf.h. Types defined on your system may vary.

Constructors
DLT_NULLno link layer encapsulation
DLT_EN10MB10 Mbit per second (or faster) ethernet
DLT_EN3MBoriginal 3 Mbit per second ethernet
DLT_AX25amateur radio AX.25
DLT_PRONETProteon ProNET Token Ring
DLT_CHAOSChaos
DLT_IEEE802IEEE 802 networks
DLT_ARCNETARCNET
DLT_SLIPSerial line IP
DLT_PPPPoint-to-point protocol
DLT_FDDIFDDI
DLT_ATM_RFC1483LLC SNAP encapsulated ATM
DLT_RAWraw IP
DLT_SLIP_BSDOSBSD OS serial line IP
DLT_PPP_BSDOSBSD OS point-to-point protocol
DLT_ATM_CLIPLinux classical IP over ATM
DLT_PPP_SERIALPPP over serial with HDLC encapsulation
DLT_PPP_ETHERPPP over ethernet
DLT_C_HDLCCisco HDLC
DLT_IEEE802_11IEEE 802.11 wireless
DLT_LOOPOpenBSD loopback device
DLT_LINUX_SLLLinux cooked sockets
DLT_LTALKApple LocalTalk
DLT_ECONETAcorn Econet
DLT_IPFILTEROpenBSD's old ipfilter
DLT_PFLOGOpenBSD's pflog
DLT_CISCO_IOSCisco IOS
DLT_PRISM_HEADERIntersil Prism II wireless chips
DLT_AIRONET_HEADERAironet (Cisco) 802.11 wireless
show/hide Instances
data Interface Source
The interface structure
Constructors
Interface
ifName :: Stringthe interface name
ifDescription :: Stringinterface description string (if any)
ifAddresses :: [PcapAddr]address families supported by this interface
ifFlags :: Word32
show/hide Instances
data PcapAddr Source
The address structure
Constructors
PcapAddr
ifAddr :: SockAddrinterface address
ifMask :: Maybe SockAddrnetwork mask
ifBcast :: Maybe SockAddrbroadcast address
ifPeer :: Maybe SockAddraddress of peer, of a point-to-point link
show/hide Instances
data SockAddr Source
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.)
Constructors
SockAddr
sockAddrFamily :: Familyan address family exported by Network.Socket
sockAddrAddr :: [Word8]
show/hide Instances
data Network Source
The network address record. Both the address and mask are in network byte order.
Constructors
Network
netAddr :: Word32IPv4 network address
netMask :: Word32IPv4 netmask
show/hide Instances
data PktHdr Source
Constructors
PktHdr
sec :: Word32timestamp (seconds)
usec :: Word32timestamp (microseconds)
caplen :: Word32number of bytes present in capture
len :: Word32number of bytes on the wire
show/hide Instances
data Statistics Source
Constructors
Statistics
recv :: Word32packets received
drop :: Word32packets dropped by libpcap
ifdrop :: Word32packets dropped by the interface
show/hide Instances
Device opening
openOfflineSource
:: Stringfilename
-> IO Pcap
openOffline opens a "savefile" for reading. The file foramt is the as used for tcpdump. The string "-" is a synonym for stdin.
openLiveSource
:: Stringdevice name
-> Intsnapshot length
-> Boolset to promiscuous mode?
-> Inttimeout in milliseconds
-> 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.

openDeadSource
:: Linkdatalink type
-> Intsnapshot length
-> IO Pcappacket capture descriptor
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.
openDumpSource
:: Ptr PcapTagpacket capture descriptor
-> Stringsavefile name
-> IO Pdumpdavefile descriptor
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.
Filter handling
setFilterSource
:: Ptr PcapTagpacket capture descriptor
-> Stringfilter string
-> Booloptimize?
-> Word32IPv4 network mask
-> IO ()
Set a filter on the specified packet capture descriptor. Valid filter strings are those accepted by tcpdump.
compileFilterSource
:: Intsnapshot length
-> Linkdatalink type
-> Stringfilter string
-> Booloptimize?
-> Word32IPv4 network mask
-> IO BpfProgram
Compile a filter for use by another program using the Berkeley Packet Filter library.
Device utilities
lookupDev :: IO StringSource
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.
findAllDevs :: IO [Interface]Source
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.
lookupNetSource
:: Stringdevice name
-> IO Network
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.
Interface control
Blocking mode
setNonBlock :: Ptr PcapTag -> Bool -> IO ()Source
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.
getNonBlock :: Ptr PcapTag -> IO BoolSource
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.
Link layer utilities
datalink :: Ptr PcapTag -> IO LinkSource
Returns the datalink type associated with the given pcap descriptor.
setDatalink :: Ptr PcapTag -> Link -> IO ()Source
Sets the datalink type for a given pcap descriptor.
listDatalinks :: Ptr PcapTag -> IO [Link]Source
List all the datalink types supported by a pcap descriptor. Entries from the resulting list are valid arguments to setDatalink.
Packet processing
dispatchSource
:: Ptr PcapTagpacket capture descriptor
-> Intnumber of packets to process
-> Callbackpacket processing function
-> IO Intnumber of packets read

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.

loopSource
:: Ptr PcapTagpacket cpature descriptor
-> Intnumber of packet to read
-> Callbackpacket processing function
-> IO Intnumber of packets read

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.

nextSource
:: Ptr PcapTagpacket capture descriptor
-> IO (PktHdr, Ptr Word8)packet header and data of the next packet
Read the next packet (by calling dispatch with a count of 1).
dumpSource
:: Ptr PcapDumpTagsavefile descriptor
-> Ptr PktHdrpacket header record
-> Ptr Word8packet data
-> IO ()
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.
Miscellaneous
statistics :: Ptr PcapTag -> IO StatisticsSource
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).
majorVersion :: Ptr PcapTag -> IO IntSource
Major version number of the library.
minorVersion :: Ptr PcapTag -> IO IntSource
Minor version number of the library.
isSwapped :: Ptr PcapTag -> IO BoolSource
isSwapped is True if the current savefile uses a different byte order than the one native to the system.
snapshotLen :: Ptr PcapTag -> IO IntSource
The snapshot length that was used in the call to openLive.
Produced by Haddock version 2.4.2