pcap-0.3: A system-independent interface for user-level packet captureContentsIndex
Network.Pcap.Base
Portabilitynon-portable
Stabilityexperimental
Maintainerbos@serpentine.com
Contents
Types
Device opening
Filter handling
Device utilities
Interface control
Link layer utilities
Packet processing
Sending packets
Conversion
Miscellaneous
Description

The 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 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 Socket. The SockAddr from 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.

Synopsis
data PcapTag
data PcapDumpTag
type Pdump = ForeignPtr PcapDumpTag
type BpfProgram = ForeignPtr BpfProgramTag
data BpfProgramTag
type Callback = PktHdr -> Ptr Word8 -> IO ()
data Direction
= InOut
| In
| Out
data Link
= DLT_NULL
| DLT_UNKNOWN Int
| 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_REDBACK_SMARTEDGE
| DLT_PPP_SERIAL
| DLT_PPP_ETHER
| DLT_SYMANTEC_FIREWALL
| DLT_C_HDLC
| DLT_IEEE802_11
| DLT_FRELAY
| DLT_LOOP
| DLT_ENC
| DLT_LINUX_SLL
| DLT_LTALK
| DLT_ECONET
| DLT_IPFILTER
| DLT_PFLOG
| DLT_CISCO_IOS
| DLT_PRISM_HEADER
| DLT_AIRONET_HEADER
| DLT_HHDLC
| DLT_IP_OVER_FC
| DLT_SUNATM
| DLT_IEEE802_11_RADIO
| DLT_ARCNET_LINUX
| DLT_APPLE_IP_OVER_IEEE1394
| DLT_MTP2_WITH_PHDR
| DLT_MTP2
| DLT_MTP3
| DLT_SCCP
| DLT_DOCSIS
| DLT_LINUX_IRDA
| DLT_USER0
| DLT_USER1
| DLT_USER2
| DLT_USER3
| DLT_USER4
| DLT_USER5
| DLT_USER6
| DLT_USER7
| DLT_USER8
| DLT_USER9
| DLT_USER10
| DLT_USER11
| DLT_USER12
| DLT_USER13
| DLT_USER14
| DLT_USER15
| DLT_PPP_PPPD
| DLT_GPRS_LLC
| DLT_GPF_T
| DLT_GPF_F
| DLT_LINUX_LAPD
| DLT_A429
| DLT_A653_ICM
| DLT_USB
| DLT_BLUETOOTH_HCI_H4
| DLT_MFR
| DLT_IEEE802_16_MAC_CPS
| DLT_USB_LINUX
| DLT_CAN20B
| DLT_IEEE802_15_4_LINUX
| DLT_PPI
| DLT_IEEE802_16_MAC_CPS_RADIO
| DLT_IEEE802_15_4
data Interface = Interface {
ifName :: String
ifDescription :: String
ifAddresses :: [PcapAddr]
ifFlags :: Word32
}
data PcapAddr = PcapAddr {
addrSA :: SockAddr
addrMask :: (Maybe SockAddr)
addrBcast :: (Maybe SockAddr)
addrPeer :: (Maybe SockAddr)
}
data SockAddr = SockAddr {
saFamily :: !Family
saAddr :: !ByteString
}
data Network = Network {
netAddr :: !Word32
netMask :: !Word32
}
data PktHdr = PktHdr {
hdrSeconds :: !Word32
hdrUseconds :: !Word32
hdrCaptureLength :: !Word32
hdrWireLength :: !Word32
}
data Statistics = Statistics {
statReceived :: !Word32
statDropped :: !Word32
statIfaceDropped :: !Word32
}
openOffline :: FilePath -> IO (ForeignPtr PcapTag)
openLive :: String -> Int -> Bool -> Int -> IO (ForeignPtr PcapTag)
openDead :: Link -> Int -> IO (ForeignPtr PcapTag)
openDump :: Ptr PcapTag -> FilePath -> 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
setDirection :: Ptr PcapTag -> Direction -> IO ()
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 ()
sendPacket :: Ptr PcapTag -> Ptr Word8 -> Int -> IO ()
toPktHdr :: Ptr PktHdr -> IO PktHdr
statistics :: Ptr PcapTag -> IO Statistics
version :: Ptr PcapTag -> IO (Int, Int)
isSwapped :: Ptr PcapTag -> IO Bool
snapshotLen :: Ptr PcapTag -> IO Int
Types
data PcapTag
data PcapDumpTag
packet capture descriptor
type Pdump = ForeignPtr PcapDumpTag
dump file descriptor
type BpfProgram = ForeignPtr BpfProgramTag
Compiled Berkeley Packet Filter program
data BpfProgramTag
type Callback = PktHdr -> Ptr Word8 -> IO ()
the type of the callback function passed to dispatch or loop.
data Direction
The direction in which packets are to be captured. See setDirection.
Constructors
InOutincoming and outgoing packets (the default
Inincoming packets
Outoutgoing packets
show/hide Instances
data Link

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_UNKNOWN Intunknown 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_REDBACK_SMARTEDGERedback SmartEdge 400/800
DLT_PPP_SERIALPPP over serial with HDLC encapsulation
DLT_PPP_ETHERPPP over ethernet
DLT_SYMANTEC_FIREWALLSymantec Enterprise Firewall
DLT_C_HDLCCisco HDLC
DLT_IEEE802_11IEEE 802.11 wireless
DLT_FRELAYFrame Relay
DLT_LOOPOpenBSD loopback device
DLT_ENCEncapsulated packets for IPsec
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
DLT_HHDLCSiemens HiPath HDLC
DLT_IP_OVER_FCRFC 2625 IP-over-Fibre Channel
DLT_SUNATMFull Frontal ATM on Solaris with SunATM
DLT_IEEE802_11_RADIO802.11 plus a number of bits of link-layer information
DLT_ARCNET_LINUXLinux ARCNET header
DLT_APPLE_IP_OVER_IEEE1394Apple IP-over-IEEE 1394
DLT_MTP2_WITH_PHDRSS7, C7 MTP2 with pseudo-header
DLT_MTP2SS7, C7 Message Transfer Part 2 (MPT2)
DLT_MTP3SS7, C7 Message Transfer Part 3 (MPT3)
DLT_SCCPSS7, C7 SCCP
DLT_DOCSISDOCSIS MAC frame
DLT_LINUX_IRDALinux IrDA packet
DLT_USER0Reserved for private use
DLT_USER1Reserved for private use
DLT_USER2Reserved for private use
DLT_USER3Reserved for private use
DLT_USER4Reserved for private use
DLT_USER5Reserved for private use
DLT_USER6Reserved for private use
DLT_USER7Reserved for private use
DLT_USER8Reserved for private use
DLT_USER9Reserved for private use
DLT_USER10Reserved for private use
DLT_USER11Reserved for private use
DLT_USER12Reserved for private use
DLT_USER13Reserved for private use
DLT_USER14Reserved for private use
DLT_USER15Reserved for private use
DLT_PPP_PPPDOutgoing packets for ppp daemon
DLT_GPRS_LLCGPRS LLC
DLT_GPF_TGPF-T (ITU-T G.7041/Y.1303)
DLT_GPF_FGPF-F (ITU-T G.7041/Y.1303)
DLT_LINUX_LAPDRaw LAPD for vISDN (not generic LAPD)
DLT_A429ARINC 429
DLT_A653_ICMARINC 653 Interpartition Communication messages
DLT_USBUSB packet
DLT_BLUETOOTH_HCI_H4Bluetooth HCI UART transport layer (part H:4)
DLT_MFRMulti Link Frame Relay (FRF.16)
DLT_IEEE802_16_MAC_CPSIEEE 802.16 MAC Common Part Sublayer
DLT_USB_LINUXUSB packets, beginning with a Linux USB header
DLT_CAN20BController Area Network (CAN) v2.0B
DLT_IEEE802_15_4_LINUXIEEE 802.15.4, with address fields padded
DLT_PPIPer Packet Information encapsulated packets
DLT_IEEE802_16_MAC_CPS_RADIO802.16 MAC Common Part Sublayer with radiotap radio header
DLT_IEEE802_15_4IEEE 802.15.4, exactly as in the spec
show/hide Instances
data Interface
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
The address structure.
Constructors
PcapAddr
addrSA :: SockAddrinterface address
addrMask :: (Maybe SockAddr)network mask
addrBcast :: (Maybe SockAddr)broadcast address
addrPeer :: (Maybe SockAddr)address of peer, of a point-to-point link
show/hide Instances
data SockAddr
The socket address record. Note that this is not the same as SockAddr from Socket. (That is a Haskell version of C's struct sockaddr_in. This is the real struct sockaddr from the BSD network stack.)
Constructors
SockAddr
saFamily :: !Familyan address family exported by Network.Socket
saAddr :: !ByteString
show/hide Instances
data Network
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
Constructors
PktHdr
hdrSeconds :: !Word32timestamp (seconds)
hdrUseconds :: !Word32timestamp (microseconds)
hdrCaptureLength :: !Word32number of bytes present in capture
hdrWireLength :: !Word32number of bytes on the wire
show/hide Instances
data Statistics
Constructors
Statistics
statReceived :: !Word32packets received
statDropped :: !Word32packets dropped by libpcap
statIfaceDropped :: !Word32packets dropped by the network interface
show/hide Instances
Device opening
openOffline
:: FilePathfilename
-> IO (ForeignPtr PcapTag)
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.
openLive
:: Stringdevice name
-> Intsnapshot length
-> Boolset to promiscuous mode?
-> Inttimeout in milliseconds
-> 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.

openDead
:: Linkdatalink type
-> Intsnapshot length
-> IO (ForeignPtr PcapTag)packet 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 link type and the snapshot length.
openDump
:: Ptr PcapTagpacket capture descriptor
-> FilePathdump file name
-> IO Pdumpdavefile descriptor
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.
Filter handling
setFilter
:: 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.
compileFilter
:: 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 String
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]
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.
lookupNet
:: 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 Interface list for the associated network mask.
Interface control
setNonBlock :: Ptr PcapTag -> Bool -> IO ()
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.
getNonBlock :: Ptr PcapTag -> IO Bool
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.
setDirection :: Ptr PcapTag -> Direction -> IO ()
Specify the direction in which packets are to be captured. Complete functionality is not necessarily available on all platforms.
Link layer utilities
datalink :: Ptr PcapTag -> IO Link
Returns the datalink type associated with the given pcap descriptor.
setDatalink :: Ptr PcapTag -> Link -> IO ()
Sets the datalink type for a given pcap descriptor.
listDatalinks :: Ptr PcapTag -> IO [Link]
List all the datalink types supported by a pcap descriptor. Entries from the resulting list are valid arguments to setDatalink.
Packet processing
dispatch
:: 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 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.

loop
:: Ptr PcapTagpacket capture 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.

This function does not return when a live read tiemout occurs. Use dispatch instead if you wnat to specify a timeout.

next
:: Ptr PcapTagpacket capture descriptor
-> IO (PktHdr, Ptr Word8)packet header and data of the next packet
Read the next packet (equivalent to calling dispatch with a count of 1).
dump
:: Ptr PcapDumpTagdump file descriptor
-> Ptr PktHdrpacket header record
-> Ptr Word8packet data
-> IO ()
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.
Sending packets
sendPacket
:: Ptr PcapTag
-> Ptr Word8packet data (including link-level header)
-> Intpacket size
-> IO ()
Send a raw packet through the network interface.
Conversion
toPktHdr :: Ptr PktHdr -> IO PktHdr
Miscellaneous
statistics :: Ptr PcapTag -> IO Statistics
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).
version :: Ptr PcapTag -> IO (Int, Int)
Version of the library. The returned pair consists of the major and minor version numbers.
isSwapped :: Ptr PcapTag -> IO Bool
isSwapped returns True if the current dump file uses a different byte order than the one native to the system.
snapshotLen :: Ptr PcapTag -> IO Int
The snapshot length that was used in the call to openLive.
Produced by Haddock version 0.8