Safe Haskell | None |
---|---|
Language | Haskell2010 |
- type SlowTicks = Int
- data TcpTimers = TcpTimers {
- ttDelayedAck :: !Bool
- tt2MSL :: !SlowTicks
- ttRetransmitValid :: !Bool
- ttRetransmit :: !SlowTicks
- ttRetries :: !Int
- ttRTO :: !SlowTicks
- ttSRTT :: !NominalDiffTime
- ttRTTVar :: !NominalDiffTime
- ttMaxIdle :: !SlowTicks
- ttIdle :: !SlowTicks
- emptyTcpTimers :: TcpTimers
- resetRetransmit :: TcpTimers -> (TcpTimers, ())
- retryRetransmit :: TcpTimers -> (TcpTimers, ())
- stopRetransmit :: TcpTimers -> (TcpTimers, ())
- reset2MSL :: Config -> TcpTimers -> (TcpTimers, ())
- updateTimers :: TcpTimers -> (TcpTimers, TcpTimers)
- calibrateRTO :: NominalDiffTime -> TcpTimers -> (TcpTimers, ())
- data State
- class GetState tcb where
- whenState :: (BaseM m IO, GetState tcb) => tcb -> State -> m () -> m ()
- setState :: Tcb -> State -> IO ()
- class CanSend sock where
- getSndNxt :: (BaseM io IO, CanSend sock) => sock -> io TcpSeqNum
- getSndWnd :: (BaseM io IO, CanSend sock) => sock -> io TcpSeqNum
- class CanReceive sock where
- getRcvNxt :: (BaseM io IO, CanReceive sock) => sock -> io TcpSeqNum
- getRcvWnd :: (BaseM io IO, CanReceive sock) => sock -> io Word16
- getRcvRight :: (BaseM io IO, CanReceive sock) => sock -> io TcpSeqNum
- data ListenTcb = ListenTcb {}
- newListenTcb :: Addr -> TcpPort -> Int -> IO ListenTcb
- createChild :: HasConfig cfg => cfg -> TcpSeqNum -> ListenTcb -> RouteInfo Addr -> Addr -> TcpHeader -> (Tcb -> State -> IO ()) -> (Tcb -> State -> IO ()) -> IO Tcb
- reserveSlot :: ListenTcb -> IO Bool
- releaseSlot :: ListenTcb -> IO ()
- acceptTcb :: ListenTcb -> IO Tcb
- data Tcb = Tcb {
- tcbParent :: Maybe ListenTcb
- tcbConfig :: !(IORef TcbConfig)
- tcbState :: !(IORef State)
- tcbEstablished :: Tcb -> State -> IO ()
- tcbClosed :: Tcb -> State -> IO ()
- tcbSndUp :: !SeqNumVar
- tcbSndWl1 :: !SeqNumVar
- tcbSndWl2 :: !SeqNumVar
- tcbIss :: !SeqNumVar
- tcbSendWindow :: !(IORef Window)
- tcbRcvUp :: !SeqNumVar
- tcbIrs :: !SeqNumVar
- tcbNeedsDelayedAck :: !(IORef Bool)
- tcbRecvWindow :: !(IORef Window)
- tcbRecvBuffer :: !Buffer
- tcbLocalPort :: !TcpPort
- tcbRemotePort :: !TcpPort
- tcbRouteInfo :: !(RouteInfo Addr)
- tcbRemote :: !Addr
- tcbMss :: !(IORef Int64)
- tcbTimers :: !(IORef TcpTimers)
- tcbTSRecent :: !(IORef Word32)
- tcbLastAckSent :: !(IORef TcpSeqNum)
- newTcb :: HasConfig state => state -> Maybe ListenTcb -> TcpSeqNum -> RouteInfo Addr -> TcpPort -> Addr -> TcpPort -> State -> TSClock -> (Tcb -> State -> IO ()) -> (Tcb -> State -> IO ()) -> IO Tcb
- signalDelayedAck :: Tcb -> IO ()
- setRcvNxt :: TcpSeqNum -> Tcb -> IO Bool
- finalizeTcb :: Tcb -> IO ()
- getSndUna :: BaseM io IO => Tcb -> io TcpSeqNum
- resetIdleTimer :: TcpTimers -> (TcpTimers, ())
- data TcbConfig = TcbConfig {
- tcUseTimestamp :: !Bool
- usingTimestamps :: Tcb -> IO Bool
- disableTimestamp :: Tcb -> IO ()
- queueBytes :: ByteString -> Tcb -> IO ()
- haveBytesAvail :: Tcb -> IO Bool
- receiveBytes :: Int -> Tcb -> IO ByteString
- tryReceiveBytes :: Int -> Tcb -> IO (Maybe ByteString)
- data TimeWaitTcb = TimeWaitTcb {
- twSndNxt :: !TcpSeqNum
- twRcvNxt :: !SeqNumVar
- twRcvWnd :: !Word16
- twLocalPort :: !TcpPort
- twRemotePort :: !TcpPort
- twRouteInfo :: !(RouteInfo Addr)
- twRemote :: !Addr
- mkTimeWaitTcb :: Tcb -> IO TimeWaitTcb
Timers
TcpTimers | |
|
resetRetransmit :: TcpTimers -> (TcpTimers, ()) Source #
Reset retransmit info.
retryRetransmit :: TcpTimers -> (TcpTimers, ()) Source #
Increment the retry count, and double the last retransmit timer.
stopRetransmit :: TcpTimers -> (TcpTimers, ()) Source #
Invalidate the retransmit timer.
updateTimers :: TcpTimers -> (TcpTimers, TcpTimers) Source #
Update all slow-tick timers. Return the old timers, for use with 'atomicModifyIORef\''.
calibrateRTO :: NominalDiffTime -> TcpTimers -> (TcpTimers, ()) Source #
Calibrate the RTO timer, given a round-trip measurement, as specified by RFC-6298.
TCB States
setState :: Tcb -> State -> IO () Source #
The Tcb type is the only one that supports changing state.
Sending
Receiving
class CanReceive sock where Source #
getRcvRight :: (BaseM io IO, CanReceive sock) => sock -> io TcpSeqNum Source #
Listening TCBs
:: HasConfig cfg | |
=> cfg | |
-> TcpSeqNum | |
-> ListenTcb | |
-> RouteInfo Addr | |
-> Addr | |
-> TcpHeader | |
-> (Tcb -> State -> IO ()) | On Established |
-> (Tcb -> State -> IO ()) | On Closed |
-> IO Tcb |
Create a child from a Syn request.
reserveSlot :: ListenTcb -> IO Bool Source #
Reserve a slot in the accept queue, returns True when the space has been reserved.
releaseSlot :: ListenTcb -> IO () Source #
Release a slot back to the accept queue.
Active TCBs
Tcb | |
|
signalDelayedAck :: Tcb -> IO () Source #
Record that a delayed ack should be sent.
finalizeTcb :: Tcb -> IO () Source #
Cleanup the Tcb.
resetIdleTimer :: TcpTimers -> (TcpTimers, ()) Source #
Reset idle timer in the presence of packets, for use with 'atomicModifyIORef\''.
Active Config
disableTimestamp :: Tcb -> IO () Source #
Disable the use of the timestamp option.
Windowing
queueBytes :: ByteString -> Tcb -> IO () Source #
Queue bytes in the receive buffer.
haveBytesAvail :: Tcb -> IO Bool Source #
Determine if there are bytes in the receive buffer that can be read.
receiveBytes :: Int -> Tcb -> IO ByteString Source #
Remove data from the receive buffer, and move the right-side of the receive window. Reading 0 bytes indicates that the remote side has closed the connection.
tryReceiveBytes :: Int -> Tcb -> IO (Maybe ByteString) Source #
Non-blocking version of receiveBytes
. Reading 0 bytes indicates that the
remote side has closed the connection.
TimeWait TCBs
data TimeWaitTcb Source #
TimeWaitTcb | |
|
mkTimeWaitTcb :: Tcb -> IO TimeWaitTcb Source #