Safe Haskell | None |
---|---|
Language | Haskell98 |
- tcpProtocol :: IP4Protocol
- newtype TcpPort = TcpPort {}
- putTcpPort :: Putter TcpPort
- getTcpPort :: Get TcpPort
- newtype TcpSeqNum = TcpSeqNum {}
- putTcpSeqNum :: Putter TcpSeqNum
- getTcpSeqNum :: Get TcpSeqNum
- type TcpAckNum = TcpSeqNum
- putTcpAckNum :: Putter TcpAckNum
- getTcpAckNum :: Get TcpAckNum
- data TcpHeader = TcpHeader {
- tcpSourcePort :: !TcpPort
- tcpDestPort :: !TcpPort
- tcpSeqNum :: !TcpSeqNum
- tcpAckNum :: !TcpAckNum
- tcpCwr :: !Bool
- tcpEce :: !Bool
- tcpUrg :: !Bool
- tcpAck :: !Bool
- tcpPsh :: !Bool
- tcpRst :: !Bool
- tcpSyn :: !Bool
- tcpFin :: !Bool
- tcpWindow :: !Word16
- tcpChecksum :: !Word16
- tcpUrgentPointer :: !Word16
- tcpOptions :: [TcpOption]
- emptyTcpHeader :: TcpHeader
- tcpFixedHeaderLength :: Int
- putTcpHeader :: Putter TcpHeader
- getTcpHeader :: Get (TcpHeader, Int)
- putTcpControl :: Putter TcpHeader
- setTcpControl :: Word8 -> TcpHeader -> TcpHeader
- class HasTcpOptions a where
- findTcpOption :: TcpOptionTag -> a -> Maybe TcpOption
- setTcpOption :: TcpOption -> a -> a
- setTcpOptions :: HasTcpOptions a => [TcpOption] -> a -> a
- data TcpOptionTag
- getTcpOptionTag :: Get TcpOptionTag
- putTcpOptionTag :: Putter TcpOptionTag
- data TcpOption
- data SackBlock = SackBlock {}
- tcpOptionTag :: TcpOption -> TcpOptionTag
- tcpOptionsLength :: [TcpOption] -> (Int, Int)
- tcpOptionLength :: TcpOption -> Int
- putTcpOption :: Putter TcpOption
- getTcpOptions :: Get [TcpOption]
- getTcpOption :: Get TcpOption
- getMaxSegmentSize :: Get TcpOption
- putMaxSegmentSize :: Putter Word16
- getSackPermitted :: Get TcpOption
- putSackPermitted :: Put
- getSack :: Get TcpOption
- putSack :: Putter [SackBlock]
- getSackBlock :: Get SackBlock
- putSackBlock :: Putter SackBlock
- sackLength :: [SackBlock] -> Int
- getWindowScaling :: Get TcpOption
- putWindowScaling :: Putter Word8
- getTimestamp :: Get TcpOption
- putTimestamp :: Word32 -> Word32 -> Put
- getUnknown :: Word8 -> Get TcpOption
- putUnknown :: Word8 -> ByteString -> Put
- parseTcpPacket :: ByteString -> Either String (TcpHeader, ByteString)
- getTcpPacket :: Get (TcpHeader, ByteString)
- putTcpPacket :: TcpHeader -> ByteString -> Put
- renderWithTcpChecksumIP4 :: IP4 -> IP4 -> TcpHeader -> ByteString -> ByteString
- computeTcpChecksumIP4 :: IP4 -> IP4 -> TcpHeader -> ByteString -> (ByteString, Word16)
- validateTcpChecksumIP4 :: IP4 -> IP4 -> ByteString -> Bool
Documentation
TcpHeader | |
|
tcpFixedHeaderLength :: Int Source
The length of the fixed part of the TcpHeader, in 4-byte octets.
putTcpHeader :: Putter TcpHeader Source
Render a TcpHeader. The checksum value is never rendered, as it is expected to be calculated and poked in afterwords.
getTcpHeader :: Get (TcpHeader, Int) Source
Parse out a TcpHeader, and its length. The resulting length is in bytes, and is derived from the data offset.
putTcpControl :: Putter TcpHeader Source
Render out the Word8
that contains the Control field of the TcpHeader.
setTcpControl :: Word8 -> TcpHeader -> TcpHeader Source
Parse out the control flags from the octet that contains them.
class HasTcpOptions a where Source
findTcpOption :: TcpOptionTag -> a -> Maybe TcpOption Source
setTcpOption :: TcpOption -> a -> a Source
setTcpOptions :: HasTcpOptions a => [TcpOption] -> a -> a Source
data TcpOptionTag Source
tcpOptionsLength :: [TcpOption] -> (Int, Int) Source
Get the rendered length of a list of TcpOptions, in 4-byte words, and the number of padding bytes required. This rounds up to the nearest 4-byte word.
tcpOptionLength :: TcpOption -> Int Source
getTcpOptions :: Get [TcpOption] Source
Parse in known tcp options.
sackLength :: [SackBlock] -> Int Source
putTimestamp :: Word32 -> Word32 -> Put Source
getUnknown :: Word8 -> Get TcpOption Source
putUnknown :: Word8 -> ByteString -> Put Source
getTcpPacket :: Get (TcpHeader, ByteString) Source
Parse a TcpPacket.
putTcpPacket :: TcpHeader -> ByteString -> Put Source
Render out a TcpPacket, without calculating its checksum.
renderWithTcpChecksumIP4 :: IP4 -> IP4 -> TcpHeader -> ByteString -> ByteString Source
Calculate the checksum of a TcpHeader, and its body.
computeTcpChecksumIP4 :: IP4 -> IP4 -> TcpHeader -> ByteString -> (ByteString, Word16) Source
Calculate the checksum of a tcp packet, and return its rendered header.
validateTcpChecksumIP4 :: IP4 -> IP4 -> ByteString -> Bool Source
Re-create the checksum, minimizing duplication of the original, rendered TCP packet.