Safe Haskell | None |
---|---|
Language | Haskell98 |
- data Host = Host {}
- emptyHost :: POSIXTime -> Host
- takePort :: Host -> Maybe (TcpPort, Host)
- releasePort :: TcpPort -> Host -> Host
- type Connections = Map SocketId TcpSocket
- removeClosed :: Connections -> Connections
- data SocketId = SocketId {
- sidLocalPort :: !TcpPort
- sidRemotePort :: !TcpPort
- sidRemoteHost :: !IP4
- emptySocketId :: SocketId
- listenSocketId :: TcpPort -> SocketId
- incomingSocketId :: IP4 -> TcpHeader -> SocketId
- data SocketResult a
- socketError :: Exception e => e -> SocketResult a
- type TimeWaitConnections = Map SocketId TimeWaitSock
- data TimeWaitSock = TimeWaitSock {
- tw2MSL :: !SlowTicks
- twInit2MSL :: !SlowTicks
- twSeqNum :: !TcpSeqNum
- twTimestamp :: Maybe Timestamp
- twReset2MSL :: TimeWaitSock -> TimeWaitSock
- mkTimeWait :: TcpSocket -> TimeWaitSock
- addTimeWait :: TcpSocket -> TimeWaitConnections -> TimeWaitConnections
- stepTimeWaitConnections :: TimeWaitConnections -> TimeWaitConnections
- type SlowTicks = Int
- mslTimeout :: SlowTicks
- data TcpTimers = TcpTimers {}
- emptyTcpTimers :: TcpTimers
- data Timestamp = Timestamp {}
- emptyTimestamp :: POSIXTime -> Timestamp
- stepTimestamp :: POSIXTime -> Timestamp -> Timestamp
- mkTimestamp :: Timestamp -> TcpOption
- type Acceptor = SocketId -> IO ()
- type Notify = Bool -> IO ()
- type Close = IO ()
- data TcpSocket = TcpSocket {
- tcpParent :: Maybe SocketId
- tcpSocketId :: !SocketId
- tcpState :: !ConnState
- tcpAcceptors :: Seq Acceptor
- tcpNotify :: Maybe Notify
- tcpIss :: !TcpSeqNum
- tcpSndNxt :: !TcpSeqNum
- tcpSndUna :: !TcpSeqNum
- tcpUserClosed :: Bool
- tcpOut :: RemoteWindow
- tcpOutBuffer :: Buffer Outgoing
- tcpOutMSS :: !Int64
- tcpIn :: LocalWindow
- tcpInBuffer :: Buffer Incoming
- tcpInMSS :: !Int64
- tcpTimers :: !TcpTimers
- tcpTimestamp :: Maybe Timestamp
- tcpSack :: Bool
- tcpWindowScale :: Bool
- emptyTcpSocket :: Word16 -> Int -> TcpSocket
- defaultMSS :: Int64
- nothingOutstanding :: TcpSocket -> Bool
- tcpRcvNxt :: TcpSocket -> TcpSeqNum
- inRcvWnd :: TcpSeqNum -> TcpSocket -> Bool
- nextSegSize :: TcpSocket -> Int64
- isAccepting :: TcpSocket -> Bool
- needsDelayedAck :: TcpSocket -> Bool
- mkMSS :: TcpSocket -> TcpOption
- data ConnState
Documentation
releasePort :: TcpPort -> Host -> Host Source
type Connections = Map SocketId TcpSocket Source
SocketId | |
|
listenSocketId :: TcpPort -> SocketId Source
incomingSocketId :: IP4 -> TcpHeader -> SocketId Source
socketError :: Exception e => e -> SocketResult a Source
type TimeWaitConnections = Map SocketId TimeWaitSock Source
The socket that's in TimeWait, plus its current 2MSL value.
data TimeWaitSock Source
TimeWaitSock | |
|
addTimeWait :: TcpSocket -> TimeWaitConnections -> TimeWaitConnections Source
Add a socket to the TimeWait map.
stepTimeWaitConnections :: TimeWaitConnections -> TimeWaitConnections Source
Take one step, collecting any connections whose 2MSL timer goes to 0.
mslTimeout :: SlowTicks Source
MSL is 60 seconds, which is slightly more aggressive than the 2 minutes from the original RFC.
Manage the timestamp values that are in flight between two hosts.
Timestamp | |
|
stepTimestamp :: POSIXTime -> Timestamp -> Timestamp Source
Update the timestamp value, advancing based on the timestamp granularity. If the number of ticks to advance is 0, don't advance the timestamp.
mkTimestamp :: Timestamp -> TcpOption Source
Generate timestamp option for an outgoing packet.
TcpSocket | |
|
emptyTcpSocket :: Word16 -> Int -> TcpSocket Source
nextSegSize :: TcpSocket -> Int64 Source
isAccepting :: TcpSocket -> Bool Source
needsDelayedAck :: TcpSocket -> Bool Source