{-# LANGUAGE RecordWildCards #-}
module Network.QUIC.Connection.Migration (
getMyCID,
getMyCIDs,
getPeerCID,
isMyCID,
myCIDsInclude,
shouldUpdateMyCID,
shouldUpdatePeerCID,
resetPeerCID,
getNewMyCID,
getMyCIDSeqNum,
setMyCID,
setPeerCIDAndRetireCIDs,
retirePeerCID,
retireMyCID,
addPeerCID,
waitPeerCID,
choosePeerCIDForPrivacy,
setPeerStatelessResetToken,
isStatelessRestTokenValid,
setMigrationStarted,
isPathValidating,
checkResponse,
validatePath,
getMyRetirePriorTo,
setMyRetirePriorTo,
getPeerRetirePriorTo,
setPeerRetirePriorTo,
checkPeerCIDCapacity,
) where
import Control.Concurrent.STM
import qualified Data.IntMap.Strict as IntMap
import qualified Data.Map.Strict as Map
import Network.QUIC.Connection.Misc
import Network.QUIC.Connection.Queue
import Network.QUIC.Connection.Types
import Network.QUIC.Connector
import Network.QUIC.Imports
import Network.QUIC.Parameters
import Network.QUIC.Qlog
import Network.QUIC.Types
getMyCID :: Connection -> IO CID
getMyCID :: Connection -> IO CID
getMyCID Connection{Recv
Buffer
Array EncryptionLevel (TVar [ReceivedPacket])
IOArray Bool Coder1RTT
IOArray EncryptionLevel Cipher
IOArray EncryptionLevel Protector
IOArray EncryptionLevel Coder
ThreadId
TVar TxFlow
TVar Concurrency
TVar MigrationState
TVar CIDDB
IORef Bool
IORef Int
IORef (IO ())
IORef (Bool, Int)
IORef (Map Word64 (Weak ThreadId))
IORef Socket
IORef RxFlow
IORef Microseconds
IORef VersionInfo
IORef AuthCIDs
IORef Parameters
IORef StreamTable
IORef PeerInfo
IORef Concurrency
IORef Negotiated
IORef CIDDB
IORef RoleInfo
Rate
OutputQ
CryptoQ
InputQ
VersionInfo
RecvQ
SizedBuffer
ConnState
Parameters
LDCC
Hooks
Shared
Send
DebugLogger
CID -> StatelessResetToken
QLogger
connState :: ConnState
connDebugLog :: DebugLogger
connQLog :: QLogger
connHooks :: Hooks
connSend :: Send
connRecv :: Recv
connRecvQ :: RecvQ
connSocket :: IORef Socket
genStatelessResetToken :: CID -> StatelessResetToken
readers :: IORef (Map Word64 (Weak ThreadId))
mainThreadId :: ThreadId
controlRate :: Rate
roleInfo :: IORef RoleInfo
quicVersionInfo :: IORef VersionInfo
origVersionInfo :: VersionInfo
myParameters :: Parameters
myCIDDB :: IORef CIDDB
peerParameters :: IORef Parameters
peerCIDDB :: TVar CIDDB
peerInfo :: IORef PeerInfo
inputQ :: InputQ
cryptoQ :: CryptoQ
outputQ :: OutputQ
outputRate :: Rate
shared :: Shared
delayedAckCount :: IORef Int
delayedAckCancel :: IORef (IO ())
peerPacketNumber :: IORef Int
streamTable :: IORef StreamTable
myStreamId :: TVar Concurrency
myUniStreamId :: TVar Concurrency
peerStreamId :: IORef Concurrency
peerUniStreamId :: IORef Concurrency
flowTx :: TVar TxFlow
flowRx :: IORef RxFlow
migrationState :: TVar MigrationState
sentRetirePriorTo :: IORef Bool
minIdleTimeout :: IORef Microseconds
bytesTx :: IORef Int
bytesRx :: IORef Int
pendingQ :: Array EncryptionLevel (TVar [ReceivedPacket])
ciphers :: IOArray EncryptionLevel Cipher
coders :: IOArray EncryptionLevel Coder
coders1RTT :: IOArray Bool Coder1RTT
protectors :: IOArray EncryptionLevel Protector
currentKeyPhase :: IORef (Bool, Int)
negotiated :: IORef Negotiated
connMyAuthCIDs :: IORef AuthCIDs
connPeerAuthCIDs :: IORef AuthCIDs
encodeBuf :: Buffer
encryptRes :: SizedBuffer
decryptBuf :: Buffer
connResources :: IORef (IO ())
connLDCC :: LDCC
connLDCC :: Connection -> LDCC
connResources :: Connection -> IORef (IO ())
decryptBuf :: Connection -> Buffer
encryptRes :: Connection -> SizedBuffer
encodeBuf :: Connection -> Buffer
connPeerAuthCIDs :: Connection -> IORef AuthCIDs
connMyAuthCIDs :: Connection -> IORef AuthCIDs
negotiated :: Connection -> IORef Negotiated
currentKeyPhase :: Connection -> IORef (Bool, Int)
protectors :: Connection -> IOArray EncryptionLevel Protector
coders1RTT :: Connection -> IOArray Bool Coder1RTT
coders :: Connection -> IOArray EncryptionLevel Coder
ciphers :: Connection -> IOArray EncryptionLevel Cipher
pendingQ :: Connection -> Array EncryptionLevel (TVar [ReceivedPacket])
bytesRx :: Connection -> IORef Int
bytesTx :: Connection -> IORef Int
minIdleTimeout :: Connection -> IORef Microseconds
sentRetirePriorTo :: Connection -> IORef Bool
migrationState :: Connection -> TVar MigrationState
flowRx :: Connection -> IORef RxFlow
flowTx :: Connection -> TVar TxFlow
peerUniStreamId :: Connection -> IORef Concurrency
peerStreamId :: Connection -> IORef Concurrency
myUniStreamId :: Connection -> TVar Concurrency
myStreamId :: Connection -> TVar Concurrency
streamTable :: Connection -> IORef StreamTable
peerPacketNumber :: Connection -> IORef Int
delayedAckCancel :: Connection -> IORef (IO ())
delayedAckCount :: Connection -> IORef Int
shared :: Connection -> Shared
outputRate :: Connection -> Rate
outputQ :: Connection -> OutputQ
cryptoQ :: Connection -> CryptoQ
inputQ :: Connection -> InputQ
peerInfo :: Connection -> IORef PeerInfo
peerCIDDB :: Connection -> TVar CIDDB
peerParameters :: Connection -> IORef Parameters
myCIDDB :: Connection -> IORef CIDDB
myParameters :: Connection -> Parameters
origVersionInfo :: Connection -> VersionInfo
quicVersionInfo :: Connection -> IORef VersionInfo
roleInfo :: Connection -> IORef RoleInfo
controlRate :: Connection -> Rate
mainThreadId :: Connection -> ThreadId
readers :: Connection -> IORef (Map Word64 (Weak ThreadId))
genStatelessResetToken :: Connection -> CID -> StatelessResetToken
connSocket :: Connection -> IORef Socket
connRecvQ :: Connection -> RecvQ
connRecv :: Connection -> Recv
connSend :: Connection -> Send
connHooks :: Connection -> Hooks
connQLog :: Connection -> QLogger
connDebugLog :: Connection -> DebugLogger
connState :: Connection -> ConnState
..} = CIDInfo -> CID
cidInfoCID (CIDInfo -> CID) -> (CIDDB -> CIDInfo) -> CIDDB -> CID
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CIDDB -> CIDInfo
usedCIDInfo (CIDDB -> CID) -> IO CIDDB -> IO CID
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> IORef CIDDB -> IO CIDDB
forall a. IORef a -> IO a
readIORef IORef CIDDB
myCIDDB
getMyCIDs :: Connection -> IO [CID]
getMyCIDs :: Connection -> IO [CID]
getMyCIDs Connection{Recv
Buffer
Array EncryptionLevel (TVar [ReceivedPacket])
IOArray Bool Coder1RTT
IOArray EncryptionLevel Cipher
IOArray EncryptionLevel Protector
IOArray EncryptionLevel Coder
ThreadId
TVar TxFlow
TVar Concurrency
TVar MigrationState
TVar CIDDB
IORef Bool
IORef Int
IORef (IO ())
IORef (Bool, Int)
IORef (Map Word64 (Weak ThreadId))
IORef Socket
IORef RxFlow
IORef Microseconds
IORef VersionInfo
IORef AuthCIDs
IORef Parameters
IORef StreamTable
IORef PeerInfo
IORef Concurrency
IORef Negotiated
IORef CIDDB
IORef RoleInfo
Rate
OutputQ
CryptoQ
InputQ
VersionInfo
RecvQ
SizedBuffer
ConnState
Parameters
LDCC
Hooks
Shared
Send
DebugLogger
CID -> StatelessResetToken
QLogger
connLDCC :: Connection -> LDCC
connResources :: Connection -> IORef (IO ())
decryptBuf :: Connection -> Buffer
encryptRes :: Connection -> SizedBuffer
encodeBuf :: Connection -> Buffer
connPeerAuthCIDs :: Connection -> IORef AuthCIDs
connMyAuthCIDs :: Connection -> IORef AuthCIDs
negotiated :: Connection -> IORef Negotiated
currentKeyPhase :: Connection -> IORef (Bool, Int)
protectors :: Connection -> IOArray EncryptionLevel Protector
coders1RTT :: Connection -> IOArray Bool Coder1RTT
coders :: Connection -> IOArray EncryptionLevel Coder
ciphers :: Connection -> IOArray EncryptionLevel Cipher
pendingQ :: Connection -> Array EncryptionLevel (TVar [ReceivedPacket])
bytesRx :: Connection -> IORef Int
bytesTx :: Connection -> IORef Int
minIdleTimeout :: Connection -> IORef Microseconds
sentRetirePriorTo :: Connection -> IORef Bool
migrationState :: Connection -> TVar MigrationState
flowRx :: Connection -> IORef RxFlow
flowTx :: Connection -> TVar TxFlow
peerUniStreamId :: Connection -> IORef Concurrency
peerStreamId :: Connection -> IORef Concurrency
myUniStreamId :: Connection -> TVar Concurrency
myStreamId :: Connection -> TVar Concurrency
streamTable :: Connection -> IORef StreamTable
peerPacketNumber :: Connection -> IORef Int
delayedAckCancel :: Connection -> IORef (IO ())
delayedAckCount :: Connection -> IORef Int
shared :: Connection -> Shared
outputRate :: Connection -> Rate
outputQ :: Connection -> OutputQ
cryptoQ :: Connection -> CryptoQ
inputQ :: Connection -> InputQ
peerInfo :: Connection -> IORef PeerInfo
peerCIDDB :: Connection -> TVar CIDDB
peerParameters :: Connection -> IORef Parameters
myCIDDB :: Connection -> IORef CIDDB
myParameters :: Connection -> Parameters
origVersionInfo :: Connection -> VersionInfo
quicVersionInfo :: Connection -> IORef VersionInfo
roleInfo :: Connection -> IORef RoleInfo
controlRate :: Connection -> Rate
mainThreadId :: Connection -> ThreadId
readers :: Connection -> IORef (Map Word64 (Weak ThreadId))
genStatelessResetToken :: Connection -> CID -> StatelessResetToken
connSocket :: Connection -> IORef Socket
connRecvQ :: Connection -> RecvQ
connRecv :: Connection -> Recv
connSend :: Connection -> Send
connHooks :: Connection -> Hooks
connQLog :: Connection -> QLogger
connDebugLog :: Connection -> DebugLogger
connState :: Connection -> ConnState
connState :: ConnState
connDebugLog :: DebugLogger
connQLog :: QLogger
connHooks :: Hooks
connSend :: Send
connRecv :: Recv
connRecvQ :: RecvQ
connSocket :: IORef Socket
genStatelessResetToken :: CID -> StatelessResetToken
readers :: IORef (Map Word64 (Weak ThreadId))
mainThreadId :: ThreadId
controlRate :: Rate
roleInfo :: IORef RoleInfo
quicVersionInfo :: IORef VersionInfo
origVersionInfo :: VersionInfo
myParameters :: Parameters
myCIDDB :: IORef CIDDB
peerParameters :: IORef Parameters
peerCIDDB :: TVar CIDDB
peerInfo :: IORef PeerInfo
inputQ :: InputQ
cryptoQ :: CryptoQ
outputQ :: OutputQ
outputRate :: Rate
shared :: Shared
delayedAckCount :: IORef Int
delayedAckCancel :: IORef (IO ())
peerPacketNumber :: IORef Int
streamTable :: IORef StreamTable
myStreamId :: TVar Concurrency
myUniStreamId :: TVar Concurrency
peerStreamId :: IORef Concurrency
peerUniStreamId :: IORef Concurrency
flowTx :: TVar TxFlow
flowRx :: IORef RxFlow
migrationState :: TVar MigrationState
sentRetirePriorTo :: IORef Bool
minIdleTimeout :: IORef Microseconds
bytesTx :: IORef Int
bytesRx :: IORef Int
pendingQ :: Array EncryptionLevel (TVar [ReceivedPacket])
ciphers :: IOArray EncryptionLevel Cipher
coders :: IOArray EncryptionLevel Coder
coders1RTT :: IOArray Bool Coder1RTT
protectors :: IOArray EncryptionLevel Protector
currentKeyPhase :: IORef (Bool, Int)
negotiated :: IORef Negotiated
connMyAuthCIDs :: IORef AuthCIDs
connPeerAuthCIDs :: IORef AuthCIDs
encodeBuf :: Buffer
encryptRes :: SizedBuffer
decryptBuf :: Buffer
connResources :: IORef (IO ())
connLDCC :: LDCC
..} = Map CID Int -> [CID]
forall k a. Map k a -> [k]
Map.keys (Map CID Int -> [CID]) -> (CIDDB -> Map CID Int) -> CIDDB -> [CID]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CIDDB -> Map CID Int
revInfos (CIDDB -> [CID]) -> IO CIDDB -> IO [CID]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> IORef CIDDB -> IO CIDDB
forall a. IORef a -> IO a
readIORef IORef CIDDB
myCIDDB
getMyCIDSeqNum :: Connection -> IO Int
getMyCIDSeqNum :: Connection -> IO Int
getMyCIDSeqNum Connection{Recv
Buffer
Array EncryptionLevel (TVar [ReceivedPacket])
IOArray Bool Coder1RTT
IOArray EncryptionLevel Cipher
IOArray EncryptionLevel Protector
IOArray EncryptionLevel Coder
ThreadId
TVar TxFlow
TVar Concurrency
TVar MigrationState
TVar CIDDB
IORef Bool
IORef Int
IORef (IO ())
IORef (Bool, Int)
IORef (Map Word64 (Weak ThreadId))
IORef Socket
IORef RxFlow
IORef Microseconds
IORef VersionInfo
IORef AuthCIDs
IORef Parameters
IORef StreamTable
IORef PeerInfo
IORef Concurrency
IORef Negotiated
IORef CIDDB
IORef RoleInfo
Rate
OutputQ
CryptoQ
InputQ
VersionInfo
RecvQ
SizedBuffer
ConnState
Parameters
LDCC
Hooks
Shared
Send
DebugLogger
CID -> StatelessResetToken
QLogger
connLDCC :: Connection -> LDCC
connResources :: Connection -> IORef (IO ())
decryptBuf :: Connection -> Buffer
encryptRes :: Connection -> SizedBuffer
encodeBuf :: Connection -> Buffer
connPeerAuthCIDs :: Connection -> IORef AuthCIDs
connMyAuthCIDs :: Connection -> IORef AuthCIDs
negotiated :: Connection -> IORef Negotiated
currentKeyPhase :: Connection -> IORef (Bool, Int)
protectors :: Connection -> IOArray EncryptionLevel Protector
coders1RTT :: Connection -> IOArray Bool Coder1RTT
coders :: Connection -> IOArray EncryptionLevel Coder
ciphers :: Connection -> IOArray EncryptionLevel Cipher
pendingQ :: Connection -> Array EncryptionLevel (TVar [ReceivedPacket])
bytesRx :: Connection -> IORef Int
bytesTx :: Connection -> IORef Int
minIdleTimeout :: Connection -> IORef Microseconds
sentRetirePriorTo :: Connection -> IORef Bool
migrationState :: Connection -> TVar MigrationState
flowRx :: Connection -> IORef RxFlow
flowTx :: Connection -> TVar TxFlow
peerUniStreamId :: Connection -> IORef Concurrency
peerStreamId :: Connection -> IORef Concurrency
myUniStreamId :: Connection -> TVar Concurrency
myStreamId :: Connection -> TVar Concurrency
streamTable :: Connection -> IORef StreamTable
peerPacketNumber :: Connection -> IORef Int
delayedAckCancel :: Connection -> IORef (IO ())
delayedAckCount :: Connection -> IORef Int
shared :: Connection -> Shared
outputRate :: Connection -> Rate
outputQ :: Connection -> OutputQ
cryptoQ :: Connection -> CryptoQ
inputQ :: Connection -> InputQ
peerInfo :: Connection -> IORef PeerInfo
peerCIDDB :: Connection -> TVar CIDDB
peerParameters :: Connection -> IORef Parameters
myCIDDB :: Connection -> IORef CIDDB
myParameters :: Connection -> Parameters
origVersionInfo :: Connection -> VersionInfo
quicVersionInfo :: Connection -> IORef VersionInfo
roleInfo :: Connection -> IORef RoleInfo
controlRate :: Connection -> Rate
mainThreadId :: Connection -> ThreadId
readers :: Connection -> IORef (Map Word64 (Weak ThreadId))
genStatelessResetToken :: Connection -> CID -> StatelessResetToken
connSocket :: Connection -> IORef Socket
connRecvQ :: Connection -> RecvQ
connRecv :: Connection -> Recv
connSend :: Connection -> Send
connHooks :: Connection -> Hooks
connQLog :: Connection -> QLogger
connDebugLog :: Connection -> DebugLogger
connState :: Connection -> ConnState
connState :: ConnState
connDebugLog :: DebugLogger
connQLog :: QLogger
connHooks :: Hooks
connSend :: Send
connRecv :: Recv
connRecvQ :: RecvQ
connSocket :: IORef Socket
genStatelessResetToken :: CID -> StatelessResetToken
readers :: IORef (Map Word64 (Weak ThreadId))
mainThreadId :: ThreadId
controlRate :: Rate
roleInfo :: IORef RoleInfo
quicVersionInfo :: IORef VersionInfo
origVersionInfo :: VersionInfo
myParameters :: Parameters
myCIDDB :: IORef CIDDB
peerParameters :: IORef Parameters
peerCIDDB :: TVar CIDDB
peerInfo :: IORef PeerInfo
inputQ :: InputQ
cryptoQ :: CryptoQ
outputQ :: OutputQ
outputRate :: Rate
shared :: Shared
delayedAckCount :: IORef Int
delayedAckCancel :: IORef (IO ())
peerPacketNumber :: IORef Int
streamTable :: IORef StreamTable
myStreamId :: TVar Concurrency
myUniStreamId :: TVar Concurrency
peerStreamId :: IORef Concurrency
peerUniStreamId :: IORef Concurrency
flowTx :: TVar TxFlow
flowRx :: IORef RxFlow
migrationState :: TVar MigrationState
sentRetirePriorTo :: IORef Bool
minIdleTimeout :: IORef Microseconds
bytesTx :: IORef Int
bytesRx :: IORef Int
pendingQ :: Array EncryptionLevel (TVar [ReceivedPacket])
ciphers :: IOArray EncryptionLevel Cipher
coders :: IOArray EncryptionLevel Coder
coders1RTT :: IOArray Bool Coder1RTT
protectors :: IOArray EncryptionLevel Protector
currentKeyPhase :: IORef (Bool, Int)
negotiated :: IORef Negotiated
connMyAuthCIDs :: IORef AuthCIDs
connPeerAuthCIDs :: IORef AuthCIDs
encodeBuf :: Buffer
encryptRes :: SizedBuffer
decryptBuf :: Buffer
connResources :: IORef (IO ())
connLDCC :: LDCC
..} = CIDInfo -> Int
cidInfoSeq (CIDInfo -> Int) -> (CIDDB -> CIDInfo) -> CIDDB -> Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CIDDB -> CIDInfo
usedCIDInfo (CIDDB -> Int) -> IO CIDDB -> IO Int
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> IORef CIDDB -> IO CIDDB
forall a. IORef a -> IO a
readIORef IORef CIDDB
myCIDDB
getPeerCID :: Connection -> IO CID
getPeerCID :: Connection -> IO CID
getPeerCID Connection{Recv
Buffer
Array EncryptionLevel (TVar [ReceivedPacket])
IOArray Bool Coder1RTT
IOArray EncryptionLevel Cipher
IOArray EncryptionLevel Protector
IOArray EncryptionLevel Coder
ThreadId
TVar TxFlow
TVar Concurrency
TVar MigrationState
TVar CIDDB
IORef Bool
IORef Int
IORef (IO ())
IORef (Bool, Int)
IORef (Map Word64 (Weak ThreadId))
IORef Socket
IORef RxFlow
IORef Microseconds
IORef VersionInfo
IORef AuthCIDs
IORef Parameters
IORef StreamTable
IORef PeerInfo
IORef Concurrency
IORef Negotiated
IORef CIDDB
IORef RoleInfo
Rate
OutputQ
CryptoQ
InputQ
VersionInfo
RecvQ
SizedBuffer
ConnState
Parameters
LDCC
Hooks
Shared
Send
DebugLogger
CID -> StatelessResetToken
QLogger
connLDCC :: Connection -> LDCC
connResources :: Connection -> IORef (IO ())
decryptBuf :: Connection -> Buffer
encryptRes :: Connection -> SizedBuffer
encodeBuf :: Connection -> Buffer
connPeerAuthCIDs :: Connection -> IORef AuthCIDs
connMyAuthCIDs :: Connection -> IORef AuthCIDs
negotiated :: Connection -> IORef Negotiated
currentKeyPhase :: Connection -> IORef (Bool, Int)
protectors :: Connection -> IOArray EncryptionLevel Protector
coders1RTT :: Connection -> IOArray Bool Coder1RTT
coders :: Connection -> IOArray EncryptionLevel Coder
ciphers :: Connection -> IOArray EncryptionLevel Cipher
pendingQ :: Connection -> Array EncryptionLevel (TVar [ReceivedPacket])
bytesRx :: Connection -> IORef Int
bytesTx :: Connection -> IORef Int
minIdleTimeout :: Connection -> IORef Microseconds
sentRetirePriorTo :: Connection -> IORef Bool
migrationState :: Connection -> TVar MigrationState
flowRx :: Connection -> IORef RxFlow
flowTx :: Connection -> TVar TxFlow
peerUniStreamId :: Connection -> IORef Concurrency
peerStreamId :: Connection -> IORef Concurrency
myUniStreamId :: Connection -> TVar Concurrency
myStreamId :: Connection -> TVar Concurrency
streamTable :: Connection -> IORef StreamTable
peerPacketNumber :: Connection -> IORef Int
delayedAckCancel :: Connection -> IORef (IO ())
delayedAckCount :: Connection -> IORef Int
shared :: Connection -> Shared
outputRate :: Connection -> Rate
outputQ :: Connection -> OutputQ
cryptoQ :: Connection -> CryptoQ
inputQ :: Connection -> InputQ
peerInfo :: Connection -> IORef PeerInfo
peerCIDDB :: Connection -> TVar CIDDB
peerParameters :: Connection -> IORef Parameters
myCIDDB :: Connection -> IORef CIDDB
myParameters :: Connection -> Parameters
origVersionInfo :: Connection -> VersionInfo
quicVersionInfo :: Connection -> IORef VersionInfo
roleInfo :: Connection -> IORef RoleInfo
controlRate :: Connection -> Rate
mainThreadId :: Connection -> ThreadId
readers :: Connection -> IORef (Map Word64 (Weak ThreadId))
genStatelessResetToken :: Connection -> CID -> StatelessResetToken
connSocket :: Connection -> IORef Socket
connRecvQ :: Connection -> RecvQ
connRecv :: Connection -> Recv
connSend :: Connection -> Send
connHooks :: Connection -> Hooks
connQLog :: Connection -> QLogger
connDebugLog :: Connection -> DebugLogger
connState :: Connection -> ConnState
connState :: ConnState
connDebugLog :: DebugLogger
connQLog :: QLogger
connHooks :: Hooks
connSend :: Send
connRecv :: Recv
connRecvQ :: RecvQ
connSocket :: IORef Socket
genStatelessResetToken :: CID -> StatelessResetToken
readers :: IORef (Map Word64 (Weak ThreadId))
mainThreadId :: ThreadId
controlRate :: Rate
roleInfo :: IORef RoleInfo
quicVersionInfo :: IORef VersionInfo
origVersionInfo :: VersionInfo
myParameters :: Parameters
myCIDDB :: IORef CIDDB
peerParameters :: IORef Parameters
peerCIDDB :: TVar CIDDB
peerInfo :: IORef PeerInfo
inputQ :: InputQ
cryptoQ :: CryptoQ
outputQ :: OutputQ
outputRate :: Rate
shared :: Shared
delayedAckCount :: IORef Int
delayedAckCancel :: IORef (IO ())
peerPacketNumber :: IORef Int
streamTable :: IORef StreamTable
myStreamId :: TVar Concurrency
myUniStreamId :: TVar Concurrency
peerStreamId :: IORef Concurrency
peerUniStreamId :: IORef Concurrency
flowTx :: TVar TxFlow
flowRx :: IORef RxFlow
migrationState :: TVar MigrationState
sentRetirePriorTo :: IORef Bool
minIdleTimeout :: IORef Microseconds
bytesTx :: IORef Int
bytesRx :: IORef Int
pendingQ :: Array EncryptionLevel (TVar [ReceivedPacket])
ciphers :: IOArray EncryptionLevel Cipher
coders :: IOArray EncryptionLevel Coder
coders1RTT :: IOArray Bool Coder1RTT
protectors :: IOArray EncryptionLevel Protector
currentKeyPhase :: IORef (Bool, Int)
negotiated :: IORef Negotiated
connMyAuthCIDs :: IORef AuthCIDs
connPeerAuthCIDs :: IORef AuthCIDs
encodeBuf :: Buffer
encryptRes :: SizedBuffer
decryptBuf :: Buffer
connResources :: IORef (IO ())
connLDCC :: LDCC
..} = CIDInfo -> CID
cidInfoCID (CIDInfo -> CID) -> (CIDDB -> CIDInfo) -> CIDDB -> CID
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CIDDB -> CIDInfo
usedCIDInfo (CIDDB -> CID) -> IO CIDDB -> IO CID
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> TVar CIDDB -> IO CIDDB
forall a. TVar a -> IO a
readTVarIO TVar CIDDB
peerCIDDB
isMyCID :: Connection -> CID -> IO Bool
isMyCID :: Connection -> CID -> IO Bool
isMyCID Connection{Recv
Buffer
Array EncryptionLevel (TVar [ReceivedPacket])
IOArray Bool Coder1RTT
IOArray EncryptionLevel Cipher
IOArray EncryptionLevel Protector
IOArray EncryptionLevel Coder
ThreadId
TVar TxFlow
TVar Concurrency
TVar MigrationState
TVar CIDDB
IORef Bool
IORef Int
IORef (IO ())
IORef (Bool, Int)
IORef (Map Word64 (Weak ThreadId))
IORef Socket
IORef RxFlow
IORef Microseconds
IORef VersionInfo
IORef AuthCIDs
IORef Parameters
IORef StreamTable
IORef PeerInfo
IORef Concurrency
IORef Negotiated
IORef CIDDB
IORef RoleInfo
Rate
OutputQ
CryptoQ
InputQ
VersionInfo
RecvQ
SizedBuffer
ConnState
Parameters
LDCC
Hooks
Shared
Send
DebugLogger
CID -> StatelessResetToken
QLogger
connLDCC :: Connection -> LDCC
connResources :: Connection -> IORef (IO ())
decryptBuf :: Connection -> Buffer
encryptRes :: Connection -> SizedBuffer
encodeBuf :: Connection -> Buffer
connPeerAuthCIDs :: Connection -> IORef AuthCIDs
connMyAuthCIDs :: Connection -> IORef AuthCIDs
negotiated :: Connection -> IORef Negotiated
currentKeyPhase :: Connection -> IORef (Bool, Int)
protectors :: Connection -> IOArray EncryptionLevel Protector
coders1RTT :: Connection -> IOArray Bool Coder1RTT
coders :: Connection -> IOArray EncryptionLevel Coder
ciphers :: Connection -> IOArray EncryptionLevel Cipher
pendingQ :: Connection -> Array EncryptionLevel (TVar [ReceivedPacket])
bytesRx :: Connection -> IORef Int
bytesTx :: Connection -> IORef Int
minIdleTimeout :: Connection -> IORef Microseconds
sentRetirePriorTo :: Connection -> IORef Bool
migrationState :: Connection -> TVar MigrationState
flowRx :: Connection -> IORef RxFlow
flowTx :: Connection -> TVar TxFlow
peerUniStreamId :: Connection -> IORef Concurrency
peerStreamId :: Connection -> IORef Concurrency
myUniStreamId :: Connection -> TVar Concurrency
myStreamId :: Connection -> TVar Concurrency
streamTable :: Connection -> IORef StreamTable
peerPacketNumber :: Connection -> IORef Int
delayedAckCancel :: Connection -> IORef (IO ())
delayedAckCount :: Connection -> IORef Int
shared :: Connection -> Shared
outputRate :: Connection -> Rate
outputQ :: Connection -> OutputQ
cryptoQ :: Connection -> CryptoQ
inputQ :: Connection -> InputQ
peerInfo :: Connection -> IORef PeerInfo
peerCIDDB :: Connection -> TVar CIDDB
peerParameters :: Connection -> IORef Parameters
myCIDDB :: Connection -> IORef CIDDB
myParameters :: Connection -> Parameters
origVersionInfo :: Connection -> VersionInfo
quicVersionInfo :: Connection -> IORef VersionInfo
roleInfo :: Connection -> IORef RoleInfo
controlRate :: Connection -> Rate
mainThreadId :: Connection -> ThreadId
readers :: Connection -> IORef (Map Word64 (Weak ThreadId))
genStatelessResetToken :: Connection -> CID -> StatelessResetToken
connSocket :: Connection -> IORef Socket
connRecvQ :: Connection -> RecvQ
connRecv :: Connection -> Recv
connSend :: Connection -> Send
connHooks :: Connection -> Hooks
connQLog :: Connection -> QLogger
connDebugLog :: Connection -> DebugLogger
connState :: Connection -> ConnState
connState :: ConnState
connDebugLog :: DebugLogger
connQLog :: QLogger
connHooks :: Hooks
connSend :: Send
connRecv :: Recv
connRecvQ :: RecvQ
connSocket :: IORef Socket
genStatelessResetToken :: CID -> StatelessResetToken
readers :: IORef (Map Word64 (Weak ThreadId))
mainThreadId :: ThreadId
controlRate :: Rate
roleInfo :: IORef RoleInfo
quicVersionInfo :: IORef VersionInfo
origVersionInfo :: VersionInfo
myParameters :: Parameters
myCIDDB :: IORef CIDDB
peerParameters :: IORef Parameters
peerCIDDB :: TVar CIDDB
peerInfo :: IORef PeerInfo
inputQ :: InputQ
cryptoQ :: CryptoQ
outputQ :: OutputQ
outputRate :: Rate
shared :: Shared
delayedAckCount :: IORef Int
delayedAckCancel :: IORef (IO ())
peerPacketNumber :: IORef Int
streamTable :: IORef StreamTable
myStreamId :: TVar Concurrency
myUniStreamId :: TVar Concurrency
peerStreamId :: IORef Concurrency
peerUniStreamId :: IORef Concurrency
flowTx :: TVar TxFlow
flowRx :: IORef RxFlow
migrationState :: TVar MigrationState
sentRetirePriorTo :: IORef Bool
minIdleTimeout :: IORef Microseconds
bytesTx :: IORef Int
bytesRx :: IORef Int
pendingQ :: Array EncryptionLevel (TVar [ReceivedPacket])
ciphers :: IOArray EncryptionLevel Cipher
coders :: IOArray EncryptionLevel Coder
coders1RTT :: IOArray Bool Coder1RTT
protectors :: IOArray EncryptionLevel Protector
currentKeyPhase :: IORef (Bool, Int)
negotiated :: IORef Negotiated
connMyAuthCIDs :: IORef AuthCIDs
connPeerAuthCIDs :: IORef AuthCIDs
encodeBuf :: Buffer
encryptRes :: SizedBuffer
decryptBuf :: Buffer
connResources :: IORef (IO ())
connLDCC :: LDCC
..} CID
cid =
(CID -> CID -> Bool
forall a. Eq a => a -> a -> Bool
== CID
cid) (CID -> Bool) -> (CIDDB -> CID) -> CIDDB -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CIDInfo -> CID
cidInfoCID (CIDInfo -> CID) -> (CIDDB -> CIDInfo) -> CIDDB -> CID
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CIDDB -> CIDInfo
usedCIDInfo (CIDDB -> Bool) -> IO CIDDB -> IO Bool
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> IORef CIDDB -> IO CIDDB
forall a. IORef a -> IO a
readIORef IORef CIDDB
myCIDDB
shouldUpdateMyCID :: Connection -> Int -> IO Bool
shouldUpdateMyCID :: Connection -> Int -> IO Bool
shouldUpdateMyCID Connection{Recv
Buffer
Array EncryptionLevel (TVar [ReceivedPacket])
IOArray Bool Coder1RTT
IOArray EncryptionLevel Cipher
IOArray EncryptionLevel Protector
IOArray EncryptionLevel Coder
ThreadId
TVar TxFlow
TVar Concurrency
TVar MigrationState
TVar CIDDB
IORef Bool
IORef Int
IORef (IO ())
IORef (Bool, Int)
IORef (Map Word64 (Weak ThreadId))
IORef Socket
IORef RxFlow
IORef Microseconds
IORef VersionInfo
IORef AuthCIDs
IORef Parameters
IORef StreamTable
IORef PeerInfo
IORef Concurrency
IORef Negotiated
IORef CIDDB
IORef RoleInfo
Rate
OutputQ
CryptoQ
InputQ
VersionInfo
RecvQ
SizedBuffer
ConnState
Parameters
LDCC
Hooks
Shared
Send
DebugLogger
CID -> StatelessResetToken
QLogger
connLDCC :: Connection -> LDCC
connResources :: Connection -> IORef (IO ())
decryptBuf :: Connection -> Buffer
encryptRes :: Connection -> SizedBuffer
encodeBuf :: Connection -> Buffer
connPeerAuthCIDs :: Connection -> IORef AuthCIDs
connMyAuthCIDs :: Connection -> IORef AuthCIDs
negotiated :: Connection -> IORef Negotiated
currentKeyPhase :: Connection -> IORef (Bool, Int)
protectors :: Connection -> IOArray EncryptionLevel Protector
coders1RTT :: Connection -> IOArray Bool Coder1RTT
coders :: Connection -> IOArray EncryptionLevel Coder
ciphers :: Connection -> IOArray EncryptionLevel Cipher
pendingQ :: Connection -> Array EncryptionLevel (TVar [ReceivedPacket])
bytesRx :: Connection -> IORef Int
bytesTx :: Connection -> IORef Int
minIdleTimeout :: Connection -> IORef Microseconds
sentRetirePriorTo :: Connection -> IORef Bool
migrationState :: Connection -> TVar MigrationState
flowRx :: Connection -> IORef RxFlow
flowTx :: Connection -> TVar TxFlow
peerUniStreamId :: Connection -> IORef Concurrency
peerStreamId :: Connection -> IORef Concurrency
myUniStreamId :: Connection -> TVar Concurrency
myStreamId :: Connection -> TVar Concurrency
streamTable :: Connection -> IORef StreamTable
peerPacketNumber :: Connection -> IORef Int
delayedAckCancel :: Connection -> IORef (IO ())
delayedAckCount :: Connection -> IORef Int
shared :: Connection -> Shared
outputRate :: Connection -> Rate
outputQ :: Connection -> OutputQ
cryptoQ :: Connection -> CryptoQ
inputQ :: Connection -> InputQ
peerInfo :: Connection -> IORef PeerInfo
peerCIDDB :: Connection -> TVar CIDDB
peerParameters :: Connection -> IORef Parameters
myCIDDB :: Connection -> IORef CIDDB
myParameters :: Connection -> Parameters
origVersionInfo :: Connection -> VersionInfo
quicVersionInfo :: Connection -> IORef VersionInfo
roleInfo :: Connection -> IORef RoleInfo
controlRate :: Connection -> Rate
mainThreadId :: Connection -> ThreadId
readers :: Connection -> IORef (Map Word64 (Weak ThreadId))
genStatelessResetToken :: Connection -> CID -> StatelessResetToken
connSocket :: Connection -> IORef Socket
connRecvQ :: Connection -> RecvQ
connRecv :: Connection -> Recv
connSend :: Connection -> Send
connHooks :: Connection -> Hooks
connQLog :: Connection -> QLogger
connDebugLog :: Connection -> DebugLogger
connState :: Connection -> ConnState
connState :: ConnState
connDebugLog :: DebugLogger
connQLog :: QLogger
connHooks :: Hooks
connSend :: Send
connRecv :: Recv
connRecvQ :: RecvQ
connSocket :: IORef Socket
genStatelessResetToken :: CID -> StatelessResetToken
readers :: IORef (Map Word64 (Weak ThreadId))
mainThreadId :: ThreadId
controlRate :: Rate
roleInfo :: IORef RoleInfo
quicVersionInfo :: IORef VersionInfo
origVersionInfo :: VersionInfo
myParameters :: Parameters
myCIDDB :: IORef CIDDB
peerParameters :: IORef Parameters
peerCIDDB :: TVar CIDDB
peerInfo :: IORef PeerInfo
inputQ :: InputQ
cryptoQ :: CryptoQ
outputQ :: OutputQ
outputRate :: Rate
shared :: Shared
delayedAckCount :: IORef Int
delayedAckCancel :: IORef (IO ())
peerPacketNumber :: IORef Int
streamTable :: IORef StreamTable
myStreamId :: TVar Concurrency
myUniStreamId :: TVar Concurrency
peerStreamId :: IORef Concurrency
peerUniStreamId :: IORef Concurrency
flowTx :: TVar TxFlow
flowRx :: IORef RxFlow
migrationState :: TVar MigrationState
sentRetirePriorTo :: IORef Bool
minIdleTimeout :: IORef Microseconds
bytesTx :: IORef Int
bytesRx :: IORef Int
pendingQ :: Array EncryptionLevel (TVar [ReceivedPacket])
ciphers :: IOArray EncryptionLevel Cipher
coders :: IOArray EncryptionLevel Coder
coders1RTT :: IOArray Bool Coder1RTT
protectors :: IOArray EncryptionLevel Protector
currentKeyPhase :: IORef (Bool, Int)
negotiated :: IORef Negotiated
connMyAuthCIDs :: IORef AuthCIDs
connPeerAuthCIDs :: IORef AuthCIDs
encodeBuf :: Buffer
encryptRes :: SizedBuffer
decryptBuf :: Buffer
connResources :: IORef (IO ())
connLDCC :: LDCC
..} Int
nseq = do
Int
useq <- CIDInfo -> Int
cidInfoSeq (CIDInfo -> Int) -> (CIDDB -> CIDInfo) -> CIDDB -> Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CIDDB -> CIDInfo
usedCIDInfo (CIDDB -> Int) -> IO CIDDB -> IO Int
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> IORef CIDDB -> IO CIDDB
forall a. IORef a -> IO a
readIORef IORef CIDDB
myCIDDB
Bool -> IO Bool
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (Int
nseq Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
useq)
myCIDsInclude :: Connection -> CID -> IO (Maybe Int)
myCIDsInclude :: Connection -> CID -> IO (Maybe Int)
myCIDsInclude Connection{Recv
Buffer
Array EncryptionLevel (TVar [ReceivedPacket])
IOArray Bool Coder1RTT
IOArray EncryptionLevel Cipher
IOArray EncryptionLevel Protector
IOArray EncryptionLevel Coder
ThreadId
TVar TxFlow
TVar Concurrency
TVar MigrationState
TVar CIDDB
IORef Bool
IORef Int
IORef (IO ())
IORef (Bool, Int)
IORef (Map Word64 (Weak ThreadId))
IORef Socket
IORef RxFlow
IORef Microseconds
IORef VersionInfo
IORef AuthCIDs
IORef Parameters
IORef StreamTable
IORef PeerInfo
IORef Concurrency
IORef Negotiated
IORef CIDDB
IORef RoleInfo
Rate
OutputQ
CryptoQ
InputQ
VersionInfo
RecvQ
SizedBuffer
ConnState
Parameters
LDCC
Hooks
Shared
Send
DebugLogger
CID -> StatelessResetToken
QLogger
connLDCC :: Connection -> LDCC
connResources :: Connection -> IORef (IO ())
decryptBuf :: Connection -> Buffer
encryptRes :: Connection -> SizedBuffer
encodeBuf :: Connection -> Buffer
connPeerAuthCIDs :: Connection -> IORef AuthCIDs
connMyAuthCIDs :: Connection -> IORef AuthCIDs
negotiated :: Connection -> IORef Negotiated
currentKeyPhase :: Connection -> IORef (Bool, Int)
protectors :: Connection -> IOArray EncryptionLevel Protector
coders1RTT :: Connection -> IOArray Bool Coder1RTT
coders :: Connection -> IOArray EncryptionLevel Coder
ciphers :: Connection -> IOArray EncryptionLevel Cipher
pendingQ :: Connection -> Array EncryptionLevel (TVar [ReceivedPacket])
bytesRx :: Connection -> IORef Int
bytesTx :: Connection -> IORef Int
minIdleTimeout :: Connection -> IORef Microseconds
sentRetirePriorTo :: Connection -> IORef Bool
migrationState :: Connection -> TVar MigrationState
flowRx :: Connection -> IORef RxFlow
flowTx :: Connection -> TVar TxFlow
peerUniStreamId :: Connection -> IORef Concurrency
peerStreamId :: Connection -> IORef Concurrency
myUniStreamId :: Connection -> TVar Concurrency
myStreamId :: Connection -> TVar Concurrency
streamTable :: Connection -> IORef StreamTable
peerPacketNumber :: Connection -> IORef Int
delayedAckCancel :: Connection -> IORef (IO ())
delayedAckCount :: Connection -> IORef Int
shared :: Connection -> Shared
outputRate :: Connection -> Rate
outputQ :: Connection -> OutputQ
cryptoQ :: Connection -> CryptoQ
inputQ :: Connection -> InputQ
peerInfo :: Connection -> IORef PeerInfo
peerCIDDB :: Connection -> TVar CIDDB
peerParameters :: Connection -> IORef Parameters
myCIDDB :: Connection -> IORef CIDDB
myParameters :: Connection -> Parameters
origVersionInfo :: Connection -> VersionInfo
quicVersionInfo :: Connection -> IORef VersionInfo
roleInfo :: Connection -> IORef RoleInfo
controlRate :: Connection -> Rate
mainThreadId :: Connection -> ThreadId
readers :: Connection -> IORef (Map Word64 (Weak ThreadId))
genStatelessResetToken :: Connection -> CID -> StatelessResetToken
connSocket :: Connection -> IORef Socket
connRecvQ :: Connection -> RecvQ
connRecv :: Connection -> Recv
connSend :: Connection -> Send
connHooks :: Connection -> Hooks
connQLog :: Connection -> QLogger
connDebugLog :: Connection -> DebugLogger
connState :: Connection -> ConnState
connState :: ConnState
connDebugLog :: DebugLogger
connQLog :: QLogger
connHooks :: Hooks
connSend :: Send
connRecv :: Recv
connRecvQ :: RecvQ
connSocket :: IORef Socket
genStatelessResetToken :: CID -> StatelessResetToken
readers :: IORef (Map Word64 (Weak ThreadId))
mainThreadId :: ThreadId
controlRate :: Rate
roleInfo :: IORef RoleInfo
quicVersionInfo :: IORef VersionInfo
origVersionInfo :: VersionInfo
myParameters :: Parameters
myCIDDB :: IORef CIDDB
peerParameters :: IORef Parameters
peerCIDDB :: TVar CIDDB
peerInfo :: IORef PeerInfo
inputQ :: InputQ
cryptoQ :: CryptoQ
outputQ :: OutputQ
outputRate :: Rate
shared :: Shared
delayedAckCount :: IORef Int
delayedAckCancel :: IORef (IO ())
peerPacketNumber :: IORef Int
streamTable :: IORef StreamTable
myStreamId :: TVar Concurrency
myUniStreamId :: TVar Concurrency
peerStreamId :: IORef Concurrency
peerUniStreamId :: IORef Concurrency
flowTx :: TVar TxFlow
flowRx :: IORef RxFlow
migrationState :: TVar MigrationState
sentRetirePriorTo :: IORef Bool
minIdleTimeout :: IORef Microseconds
bytesTx :: IORef Int
bytesRx :: IORef Int
pendingQ :: Array EncryptionLevel (TVar [ReceivedPacket])
ciphers :: IOArray EncryptionLevel Cipher
coders :: IOArray EncryptionLevel Coder
coders1RTT :: IOArray Bool Coder1RTT
protectors :: IOArray EncryptionLevel Protector
currentKeyPhase :: IORef (Bool, Int)
negotiated :: IORef Negotiated
connMyAuthCIDs :: IORef AuthCIDs
connPeerAuthCIDs :: IORef AuthCIDs
encodeBuf :: Buffer
encryptRes :: SizedBuffer
decryptBuf :: Buffer
connResources :: IORef (IO ())
connLDCC :: LDCC
..} CID
cid =
CID -> Map CID Int -> Maybe Int
forall k a. Ord k => k -> Map k a -> Maybe a
Map.lookup CID
cid (Map CID Int -> Maybe Int)
-> (CIDDB -> Map CID Int) -> CIDDB -> Maybe Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CIDDB -> Map CID Int
revInfos (CIDDB -> Maybe Int) -> IO CIDDB -> IO (Maybe Int)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> IORef CIDDB -> IO CIDDB
forall a. IORef a -> IO a
readIORef IORef CIDDB
myCIDDB
resetPeerCID :: Connection -> CID -> IO ()
resetPeerCID :: Connection -> CID -> IO ()
resetPeerCID Connection{Recv
Buffer
Array EncryptionLevel (TVar [ReceivedPacket])
IOArray Bool Coder1RTT
IOArray EncryptionLevel Cipher
IOArray EncryptionLevel Protector
IOArray EncryptionLevel Coder
ThreadId
TVar TxFlow
TVar Concurrency
TVar MigrationState
TVar CIDDB
IORef Bool
IORef Int
IORef (IO ())
IORef (Bool, Int)
IORef (Map Word64 (Weak ThreadId))
IORef Socket
IORef RxFlow
IORef Microseconds
IORef VersionInfo
IORef AuthCIDs
IORef Parameters
IORef StreamTable
IORef PeerInfo
IORef Concurrency
IORef Negotiated
IORef CIDDB
IORef RoleInfo
Rate
OutputQ
CryptoQ
InputQ
VersionInfo
RecvQ
SizedBuffer
ConnState
Parameters
LDCC
Hooks
Shared
Send
DebugLogger
CID -> StatelessResetToken
QLogger
connLDCC :: Connection -> LDCC
connResources :: Connection -> IORef (IO ())
decryptBuf :: Connection -> Buffer
encryptRes :: Connection -> SizedBuffer
encodeBuf :: Connection -> Buffer
connPeerAuthCIDs :: Connection -> IORef AuthCIDs
connMyAuthCIDs :: Connection -> IORef AuthCIDs
negotiated :: Connection -> IORef Negotiated
currentKeyPhase :: Connection -> IORef (Bool, Int)
protectors :: Connection -> IOArray EncryptionLevel Protector
coders1RTT :: Connection -> IOArray Bool Coder1RTT
coders :: Connection -> IOArray EncryptionLevel Coder
ciphers :: Connection -> IOArray EncryptionLevel Cipher
pendingQ :: Connection -> Array EncryptionLevel (TVar [ReceivedPacket])
bytesRx :: Connection -> IORef Int
bytesTx :: Connection -> IORef Int
minIdleTimeout :: Connection -> IORef Microseconds
sentRetirePriorTo :: Connection -> IORef Bool
migrationState :: Connection -> TVar MigrationState
flowRx :: Connection -> IORef RxFlow
flowTx :: Connection -> TVar TxFlow
peerUniStreamId :: Connection -> IORef Concurrency
peerStreamId :: Connection -> IORef Concurrency
myUniStreamId :: Connection -> TVar Concurrency
myStreamId :: Connection -> TVar Concurrency
streamTable :: Connection -> IORef StreamTable
peerPacketNumber :: Connection -> IORef Int
delayedAckCancel :: Connection -> IORef (IO ())
delayedAckCount :: Connection -> IORef Int
shared :: Connection -> Shared
outputRate :: Connection -> Rate
outputQ :: Connection -> OutputQ
cryptoQ :: Connection -> CryptoQ
inputQ :: Connection -> InputQ
peerInfo :: Connection -> IORef PeerInfo
peerCIDDB :: Connection -> TVar CIDDB
peerParameters :: Connection -> IORef Parameters
myCIDDB :: Connection -> IORef CIDDB
myParameters :: Connection -> Parameters
origVersionInfo :: Connection -> VersionInfo
quicVersionInfo :: Connection -> IORef VersionInfo
roleInfo :: Connection -> IORef RoleInfo
controlRate :: Connection -> Rate
mainThreadId :: Connection -> ThreadId
readers :: Connection -> IORef (Map Word64 (Weak ThreadId))
genStatelessResetToken :: Connection -> CID -> StatelessResetToken
connSocket :: Connection -> IORef Socket
connRecvQ :: Connection -> RecvQ
connRecv :: Connection -> Recv
connSend :: Connection -> Send
connHooks :: Connection -> Hooks
connQLog :: Connection -> QLogger
connDebugLog :: Connection -> DebugLogger
connState :: Connection -> ConnState
connState :: ConnState
connDebugLog :: DebugLogger
connQLog :: QLogger
connHooks :: Hooks
connSend :: Send
connRecv :: Recv
connRecvQ :: RecvQ
connSocket :: IORef Socket
genStatelessResetToken :: CID -> StatelessResetToken
readers :: IORef (Map Word64 (Weak ThreadId))
mainThreadId :: ThreadId
controlRate :: Rate
roleInfo :: IORef RoleInfo
quicVersionInfo :: IORef VersionInfo
origVersionInfo :: VersionInfo
myParameters :: Parameters
myCIDDB :: IORef CIDDB
peerParameters :: IORef Parameters
peerCIDDB :: TVar CIDDB
peerInfo :: IORef PeerInfo
inputQ :: InputQ
cryptoQ :: CryptoQ
outputQ :: OutputQ
outputRate :: Rate
shared :: Shared
delayedAckCount :: IORef Int
delayedAckCancel :: IORef (IO ())
peerPacketNumber :: IORef Int
streamTable :: IORef StreamTable
myStreamId :: TVar Concurrency
myUniStreamId :: TVar Concurrency
peerStreamId :: IORef Concurrency
peerUniStreamId :: IORef Concurrency
flowTx :: TVar TxFlow
flowRx :: IORef RxFlow
migrationState :: TVar MigrationState
sentRetirePriorTo :: IORef Bool
minIdleTimeout :: IORef Microseconds
bytesTx :: IORef Int
bytesRx :: IORef Int
pendingQ :: Array EncryptionLevel (TVar [ReceivedPacket])
ciphers :: IOArray EncryptionLevel Cipher
coders :: IOArray EncryptionLevel Coder
coders1RTT :: IOArray Bool Coder1RTT
protectors :: IOArray EncryptionLevel Protector
currentKeyPhase :: IORef (Bool, Int)
negotiated :: IORef Negotiated
connMyAuthCIDs :: IORef AuthCIDs
connPeerAuthCIDs :: IORef AuthCIDs
encodeBuf :: Buffer
encryptRes :: SizedBuffer
decryptBuf :: Buffer
connResources :: IORef (IO ())
connLDCC :: LDCC
..} CID
cid = STM () -> IO ()
forall a. STM a -> IO a
atomically (STM () -> IO ()) -> STM () -> IO ()
forall a b. (a -> b) -> a -> b
$ TVar CIDDB -> CIDDB -> STM ()
forall a. TVar a -> a -> STM ()
writeTVar TVar CIDDB
peerCIDDB (CIDDB -> STM ()) -> CIDDB -> STM ()
forall a b. (a -> b) -> a -> b
$ CID -> CIDDB
newCIDDB CID
cid
getNewMyCID :: Connection -> IO CIDInfo
getNewMyCID :: Connection -> IO CIDInfo
getNewMyCID Connection{Recv
Buffer
Array EncryptionLevel (TVar [ReceivedPacket])
IOArray Bool Coder1RTT
IOArray EncryptionLevel Cipher
IOArray EncryptionLevel Protector
IOArray EncryptionLevel Coder
ThreadId
TVar TxFlow
TVar Concurrency
TVar MigrationState
TVar CIDDB
IORef Bool
IORef Int
IORef (IO ())
IORef (Bool, Int)
IORef (Map Word64 (Weak ThreadId))
IORef Socket
IORef RxFlow
IORef Microseconds
IORef VersionInfo
IORef AuthCIDs
IORef Parameters
IORef StreamTable
IORef PeerInfo
IORef Concurrency
IORef Negotiated
IORef CIDDB
IORef RoleInfo
Rate
OutputQ
CryptoQ
InputQ
VersionInfo
RecvQ
SizedBuffer
ConnState
Parameters
LDCC
Hooks
Shared
Send
DebugLogger
CID -> StatelessResetToken
QLogger
connLDCC :: Connection -> LDCC
connResources :: Connection -> IORef (IO ())
decryptBuf :: Connection -> Buffer
encryptRes :: Connection -> SizedBuffer
encodeBuf :: Connection -> Buffer
connPeerAuthCIDs :: Connection -> IORef AuthCIDs
connMyAuthCIDs :: Connection -> IORef AuthCIDs
negotiated :: Connection -> IORef Negotiated
currentKeyPhase :: Connection -> IORef (Bool, Int)
protectors :: Connection -> IOArray EncryptionLevel Protector
coders1RTT :: Connection -> IOArray Bool Coder1RTT
coders :: Connection -> IOArray EncryptionLevel Coder
ciphers :: Connection -> IOArray EncryptionLevel Cipher
pendingQ :: Connection -> Array EncryptionLevel (TVar [ReceivedPacket])
bytesRx :: Connection -> IORef Int
bytesTx :: Connection -> IORef Int
minIdleTimeout :: Connection -> IORef Microseconds
sentRetirePriorTo :: Connection -> IORef Bool
migrationState :: Connection -> TVar MigrationState
flowRx :: Connection -> IORef RxFlow
flowTx :: Connection -> TVar TxFlow
peerUniStreamId :: Connection -> IORef Concurrency
peerStreamId :: Connection -> IORef Concurrency
myUniStreamId :: Connection -> TVar Concurrency
myStreamId :: Connection -> TVar Concurrency
streamTable :: Connection -> IORef StreamTable
peerPacketNumber :: Connection -> IORef Int
delayedAckCancel :: Connection -> IORef (IO ())
delayedAckCount :: Connection -> IORef Int
shared :: Connection -> Shared
outputRate :: Connection -> Rate
outputQ :: Connection -> OutputQ
cryptoQ :: Connection -> CryptoQ
inputQ :: Connection -> InputQ
peerInfo :: Connection -> IORef PeerInfo
peerCIDDB :: Connection -> TVar CIDDB
peerParameters :: Connection -> IORef Parameters
myCIDDB :: Connection -> IORef CIDDB
myParameters :: Connection -> Parameters
origVersionInfo :: Connection -> VersionInfo
quicVersionInfo :: Connection -> IORef VersionInfo
roleInfo :: Connection -> IORef RoleInfo
controlRate :: Connection -> Rate
mainThreadId :: Connection -> ThreadId
readers :: Connection -> IORef (Map Word64 (Weak ThreadId))
genStatelessResetToken :: Connection -> CID -> StatelessResetToken
connSocket :: Connection -> IORef Socket
connRecvQ :: Connection -> RecvQ
connRecv :: Connection -> Recv
connSend :: Connection -> Send
connHooks :: Connection -> Hooks
connQLog :: Connection -> QLogger
connDebugLog :: Connection -> DebugLogger
connState :: Connection -> ConnState
connState :: ConnState
connDebugLog :: DebugLogger
connQLog :: QLogger
connHooks :: Hooks
connSend :: Send
connRecv :: Recv
connRecvQ :: RecvQ
connSocket :: IORef Socket
genStatelessResetToken :: CID -> StatelessResetToken
readers :: IORef (Map Word64 (Weak ThreadId))
mainThreadId :: ThreadId
controlRate :: Rate
roleInfo :: IORef RoleInfo
quicVersionInfo :: IORef VersionInfo
origVersionInfo :: VersionInfo
myParameters :: Parameters
myCIDDB :: IORef CIDDB
peerParameters :: IORef Parameters
peerCIDDB :: TVar CIDDB
peerInfo :: IORef PeerInfo
inputQ :: InputQ
cryptoQ :: CryptoQ
outputQ :: OutputQ
outputRate :: Rate
shared :: Shared
delayedAckCount :: IORef Int
delayedAckCancel :: IORef (IO ())
peerPacketNumber :: IORef Int
streamTable :: IORef StreamTable
myStreamId :: TVar Concurrency
myUniStreamId :: TVar Concurrency
peerStreamId :: IORef Concurrency
peerUniStreamId :: IORef Concurrency
flowTx :: TVar TxFlow
flowRx :: IORef RxFlow
migrationState :: TVar MigrationState
sentRetirePriorTo :: IORef Bool
minIdleTimeout :: IORef Microseconds
bytesTx :: IORef Int
bytesRx :: IORef Int
pendingQ :: Array EncryptionLevel (TVar [ReceivedPacket])
ciphers :: IOArray EncryptionLevel Cipher
coders :: IOArray EncryptionLevel Coder
coders1RTT :: IOArray Bool Coder1RTT
protectors :: IOArray EncryptionLevel Protector
currentKeyPhase :: IORef (Bool, Int)
negotiated :: IORef Negotiated
connMyAuthCIDs :: IORef AuthCIDs
connPeerAuthCIDs :: IORef AuthCIDs
encodeBuf :: Buffer
encryptRes :: SizedBuffer
decryptBuf :: Buffer
connResources :: IORef (IO ())
connLDCC :: LDCC
..} = do
CID
cid <- IO CID
newCID
let srt :: StatelessResetToken
srt = CID -> StatelessResetToken
genStatelessResetToken CID
cid
IORef CIDDB -> (CIDDB -> (CIDDB, CIDInfo)) -> IO CIDInfo
forall a b. IORef a -> (a -> (a, b)) -> IO b
atomicModifyIORef' IORef CIDDB
myCIDDB ((CIDDB -> (CIDDB, CIDInfo)) -> IO CIDInfo)
-> (CIDDB -> (CIDDB, CIDInfo)) -> IO CIDInfo
forall a b. (a -> b) -> a -> b
$ CID -> StatelessResetToken -> CIDDB -> (CIDDB, CIDInfo)
new CID
cid StatelessResetToken
srt
addPeerCID :: Connection -> CIDInfo -> IO Bool
addPeerCID :: Connection -> CIDInfo -> IO Bool
addPeerCID conn :: Connection
conn@Connection{Recv
Buffer
Array EncryptionLevel (TVar [ReceivedPacket])
IOArray Bool Coder1RTT
IOArray EncryptionLevel Cipher
IOArray EncryptionLevel Protector
IOArray EncryptionLevel Coder
ThreadId
TVar TxFlow
TVar Concurrency
TVar MigrationState
TVar CIDDB
IORef Bool
IORef Int
IORef (IO ())
IORef (Bool, Int)
IORef (Map Word64 (Weak ThreadId))
IORef Socket
IORef RxFlow
IORef Microseconds
IORef VersionInfo
IORef AuthCIDs
IORef Parameters
IORef StreamTable
IORef PeerInfo
IORef Concurrency
IORef Negotiated
IORef CIDDB
IORef RoleInfo
Rate
OutputQ
CryptoQ
InputQ
VersionInfo
RecvQ
SizedBuffer
ConnState
Parameters
LDCC
Hooks
Shared
Send
DebugLogger
CID -> StatelessResetToken
QLogger
connLDCC :: Connection -> LDCC
connResources :: Connection -> IORef (IO ())
decryptBuf :: Connection -> Buffer
encryptRes :: Connection -> SizedBuffer
encodeBuf :: Connection -> Buffer
connPeerAuthCIDs :: Connection -> IORef AuthCIDs
connMyAuthCIDs :: Connection -> IORef AuthCIDs
negotiated :: Connection -> IORef Negotiated
currentKeyPhase :: Connection -> IORef (Bool, Int)
protectors :: Connection -> IOArray EncryptionLevel Protector
coders1RTT :: Connection -> IOArray Bool Coder1RTT
coders :: Connection -> IOArray EncryptionLevel Coder
ciphers :: Connection -> IOArray EncryptionLevel Cipher
pendingQ :: Connection -> Array EncryptionLevel (TVar [ReceivedPacket])
bytesRx :: Connection -> IORef Int
bytesTx :: Connection -> IORef Int
minIdleTimeout :: Connection -> IORef Microseconds
sentRetirePriorTo :: Connection -> IORef Bool
migrationState :: Connection -> TVar MigrationState
flowRx :: Connection -> IORef RxFlow
flowTx :: Connection -> TVar TxFlow
peerUniStreamId :: Connection -> IORef Concurrency
peerStreamId :: Connection -> IORef Concurrency
myUniStreamId :: Connection -> TVar Concurrency
myStreamId :: Connection -> TVar Concurrency
streamTable :: Connection -> IORef StreamTable
peerPacketNumber :: Connection -> IORef Int
delayedAckCancel :: Connection -> IORef (IO ())
delayedAckCount :: Connection -> IORef Int
shared :: Connection -> Shared
outputRate :: Connection -> Rate
outputQ :: Connection -> OutputQ
cryptoQ :: Connection -> CryptoQ
inputQ :: Connection -> InputQ
peerInfo :: Connection -> IORef PeerInfo
peerCIDDB :: Connection -> TVar CIDDB
peerParameters :: Connection -> IORef Parameters
myCIDDB :: Connection -> IORef CIDDB
myParameters :: Connection -> Parameters
origVersionInfo :: Connection -> VersionInfo
quicVersionInfo :: Connection -> IORef VersionInfo
roleInfo :: Connection -> IORef RoleInfo
controlRate :: Connection -> Rate
mainThreadId :: Connection -> ThreadId
readers :: Connection -> IORef (Map Word64 (Weak ThreadId))
genStatelessResetToken :: Connection -> CID -> StatelessResetToken
connSocket :: Connection -> IORef Socket
connRecvQ :: Connection -> RecvQ
connRecv :: Connection -> Recv
connSend :: Connection -> Send
connHooks :: Connection -> Hooks
connQLog :: Connection -> QLogger
connDebugLog :: Connection -> DebugLogger
connState :: Connection -> ConnState
connState :: ConnState
connDebugLog :: DebugLogger
connQLog :: QLogger
connHooks :: Hooks
connSend :: Send
connRecv :: Recv
connRecvQ :: RecvQ
connSocket :: IORef Socket
genStatelessResetToken :: CID -> StatelessResetToken
readers :: IORef (Map Word64 (Weak ThreadId))
mainThreadId :: ThreadId
controlRate :: Rate
roleInfo :: IORef RoleInfo
quicVersionInfo :: IORef VersionInfo
origVersionInfo :: VersionInfo
myParameters :: Parameters
myCIDDB :: IORef CIDDB
peerParameters :: IORef Parameters
peerCIDDB :: TVar CIDDB
peerInfo :: IORef PeerInfo
inputQ :: InputQ
cryptoQ :: CryptoQ
outputQ :: OutputQ
outputRate :: Rate
shared :: Shared
delayedAckCount :: IORef Int
delayedAckCancel :: IORef (IO ())
peerPacketNumber :: IORef Int
streamTable :: IORef StreamTable
myStreamId :: TVar Concurrency
myUniStreamId :: TVar Concurrency
peerStreamId :: IORef Concurrency
peerUniStreamId :: IORef Concurrency
flowTx :: TVar TxFlow
flowRx :: IORef RxFlow
migrationState :: TVar MigrationState
sentRetirePriorTo :: IORef Bool
minIdleTimeout :: IORef Microseconds
bytesTx :: IORef Int
bytesRx :: IORef Int
pendingQ :: Array EncryptionLevel (TVar [ReceivedPacket])
ciphers :: IOArray EncryptionLevel Cipher
coders :: IOArray EncryptionLevel Coder
coders1RTT :: IOArray Bool Coder1RTT
protectors :: IOArray EncryptionLevel Protector
currentKeyPhase :: IORef (Bool, Int)
negotiated :: IORef Negotiated
connMyAuthCIDs :: IORef AuthCIDs
connPeerAuthCIDs :: IORef AuthCIDs
encodeBuf :: Buffer
encryptRes :: SizedBuffer
decryptBuf :: Buffer
connResources :: IORef (IO ())
connLDCC :: LDCC
..} CIDInfo
cidInfo = do
let lim :: Int
lim = Parameters -> Int
activeConnectionIdLimit (Parameters -> Int) -> Parameters -> Int
forall a b. (a -> b) -> a -> b
$ Connection -> Parameters
getMyParameters Connection
conn
STM Bool -> IO Bool
forall a. STM a -> IO a
atomically (STM Bool -> IO Bool) -> STM Bool -> IO Bool
forall a b. (a -> b) -> a -> b
$ do
CIDDB
db <- TVar CIDDB -> STM CIDDB
forall a. TVar a -> STM a
readTVar TVar CIDDB
peerCIDDB
case CID -> Map CID Int -> Maybe Int
forall k a. Ord k => k -> Map k a -> Maybe a
Map.lookup (CIDInfo -> CID
cidInfoCID CIDInfo
cidInfo) (CIDDB -> Map CID Int
revInfos CIDDB
db) of
Maybe Int
Nothing -> do
let n :: Int
n = Map CID Int -> Int
forall k a. Map k a -> Int
Map.size (Map CID Int -> Int) -> Map CID Int -> Int
forall a b. (a -> b) -> a -> b
$ CIDDB -> Map CID Int
revInfos CIDDB
db
if Int
n Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= Int
lim
then Bool -> STM Bool
forall a. a -> STM a
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
False
else do
TVar CIDDB -> (CIDDB -> CIDDB) -> STM ()
forall a. TVar a -> (a -> a) -> STM ()
modifyTVar' TVar CIDDB
peerCIDDB ((CIDDB -> CIDDB) -> STM ()) -> (CIDDB -> CIDDB) -> STM ()
forall a b. (a -> b) -> a -> b
$ CIDInfo -> CIDDB -> CIDDB
add CIDInfo
cidInfo
Bool -> STM Bool
forall a. a -> STM a
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
True
Just Int
_ -> Bool -> STM Bool
forall a. a -> STM a
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
True
shouldUpdatePeerCID :: Connection -> IO Bool
shouldUpdatePeerCID :: Connection -> IO Bool
shouldUpdatePeerCID Connection{Recv
Buffer
Array EncryptionLevel (TVar [ReceivedPacket])
IOArray Bool Coder1RTT
IOArray EncryptionLevel Cipher
IOArray EncryptionLevel Protector
IOArray EncryptionLevel Coder
ThreadId
TVar TxFlow
TVar Concurrency
TVar MigrationState
TVar CIDDB
IORef Bool
IORef Int
IORef (IO ())
IORef (Bool, Int)
IORef (Map Word64 (Weak ThreadId))
IORef Socket
IORef RxFlow
IORef Microseconds
IORef VersionInfo
IORef AuthCIDs
IORef Parameters
IORef StreamTable
IORef PeerInfo
IORef Concurrency
IORef Negotiated
IORef CIDDB
IORef RoleInfo
Rate
OutputQ
CryptoQ
InputQ
VersionInfo
RecvQ
SizedBuffer
ConnState
Parameters
LDCC
Hooks
Shared
Send
DebugLogger
CID -> StatelessResetToken
QLogger
connLDCC :: Connection -> LDCC
connResources :: Connection -> IORef (IO ())
decryptBuf :: Connection -> Buffer
encryptRes :: Connection -> SizedBuffer
encodeBuf :: Connection -> Buffer
connPeerAuthCIDs :: Connection -> IORef AuthCIDs
connMyAuthCIDs :: Connection -> IORef AuthCIDs
negotiated :: Connection -> IORef Negotiated
currentKeyPhase :: Connection -> IORef (Bool, Int)
protectors :: Connection -> IOArray EncryptionLevel Protector
coders1RTT :: Connection -> IOArray Bool Coder1RTT
coders :: Connection -> IOArray EncryptionLevel Coder
ciphers :: Connection -> IOArray EncryptionLevel Cipher
pendingQ :: Connection -> Array EncryptionLevel (TVar [ReceivedPacket])
bytesRx :: Connection -> IORef Int
bytesTx :: Connection -> IORef Int
minIdleTimeout :: Connection -> IORef Microseconds
sentRetirePriorTo :: Connection -> IORef Bool
migrationState :: Connection -> TVar MigrationState
flowRx :: Connection -> IORef RxFlow
flowTx :: Connection -> TVar TxFlow
peerUniStreamId :: Connection -> IORef Concurrency
peerStreamId :: Connection -> IORef Concurrency
myUniStreamId :: Connection -> TVar Concurrency
myStreamId :: Connection -> TVar Concurrency
streamTable :: Connection -> IORef StreamTable
peerPacketNumber :: Connection -> IORef Int
delayedAckCancel :: Connection -> IORef (IO ())
delayedAckCount :: Connection -> IORef Int
shared :: Connection -> Shared
outputRate :: Connection -> Rate
outputQ :: Connection -> OutputQ
cryptoQ :: Connection -> CryptoQ
inputQ :: Connection -> InputQ
peerInfo :: Connection -> IORef PeerInfo
peerCIDDB :: Connection -> TVar CIDDB
peerParameters :: Connection -> IORef Parameters
myCIDDB :: Connection -> IORef CIDDB
myParameters :: Connection -> Parameters
origVersionInfo :: Connection -> VersionInfo
quicVersionInfo :: Connection -> IORef VersionInfo
roleInfo :: Connection -> IORef RoleInfo
controlRate :: Connection -> Rate
mainThreadId :: Connection -> ThreadId
readers :: Connection -> IORef (Map Word64 (Weak ThreadId))
genStatelessResetToken :: Connection -> CID -> StatelessResetToken
connSocket :: Connection -> IORef Socket
connRecvQ :: Connection -> RecvQ
connRecv :: Connection -> Recv
connSend :: Connection -> Send
connHooks :: Connection -> Hooks
connQLog :: Connection -> QLogger
connDebugLog :: Connection -> DebugLogger
connState :: Connection -> ConnState
connState :: ConnState
connDebugLog :: DebugLogger
connQLog :: QLogger
connHooks :: Hooks
connSend :: Send
connRecv :: Recv
connRecvQ :: RecvQ
connSocket :: IORef Socket
genStatelessResetToken :: CID -> StatelessResetToken
readers :: IORef (Map Word64 (Weak ThreadId))
mainThreadId :: ThreadId
controlRate :: Rate
roleInfo :: IORef RoleInfo
quicVersionInfo :: IORef VersionInfo
origVersionInfo :: VersionInfo
myParameters :: Parameters
myCIDDB :: IORef CIDDB
peerParameters :: IORef Parameters
peerCIDDB :: TVar CIDDB
peerInfo :: IORef PeerInfo
inputQ :: InputQ
cryptoQ :: CryptoQ
outputQ :: OutputQ
outputRate :: Rate
shared :: Shared
delayedAckCount :: IORef Int
delayedAckCancel :: IORef (IO ())
peerPacketNumber :: IORef Int
streamTable :: IORef StreamTable
myStreamId :: TVar Concurrency
myUniStreamId :: TVar Concurrency
peerStreamId :: IORef Concurrency
peerUniStreamId :: IORef Concurrency
flowTx :: TVar TxFlow
flowRx :: IORef RxFlow
migrationState :: TVar MigrationState
sentRetirePriorTo :: IORef Bool
minIdleTimeout :: IORef Microseconds
bytesTx :: IORef Int
bytesRx :: IORef Int
pendingQ :: Array EncryptionLevel (TVar [ReceivedPacket])
ciphers :: IOArray EncryptionLevel Cipher
coders :: IOArray EncryptionLevel Coder
coders1RTT :: IOArray Bool Coder1RTT
protectors :: IOArray EncryptionLevel Protector
currentKeyPhase :: IORef (Bool, Int)
negotiated :: IORef Negotiated
connMyAuthCIDs :: IORef AuthCIDs
connPeerAuthCIDs :: IORef AuthCIDs
encodeBuf :: Buffer
encryptRes :: SizedBuffer
decryptBuf :: Buffer
connResources :: IORef (IO ())
connLDCC :: LDCC
..} =
Bool -> Bool
not (Bool -> Bool) -> (CIDDB -> Bool) -> CIDDB -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CIDDB -> Bool
triggeredByMe (CIDDB -> Bool) -> IO CIDDB -> IO Bool
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> TVar CIDDB -> IO CIDDB
forall a. TVar a -> IO a
readTVarIO TVar CIDDB
peerCIDDB
choosePeerCIDForPrivacy :: Connection -> IO ()
choosePeerCIDForPrivacy :: Connection -> IO ()
choosePeerCIDForPrivacy Connection
conn = do
Maybe CIDInfo
mr <- STM (Maybe CIDInfo) -> IO (Maybe CIDInfo)
forall a. STM a -> IO a
atomically (STM (Maybe CIDInfo) -> IO (Maybe CIDInfo))
-> STM (Maybe CIDInfo) -> IO (Maybe CIDInfo)
forall a b. (a -> b) -> a -> b
$ do
Maybe CIDInfo
mncid <- Connection -> STM (Maybe CIDInfo)
pickPeerCID Connection
conn
case Maybe CIDInfo
mncid of
Maybe CIDInfo
Nothing -> () -> STM ()
forall a. a -> STM a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
Just CIDInfo
ncid -> do
Connection -> CIDInfo -> Bool -> STM ()
setPeerCID Connection
conn CIDInfo
ncid Bool
False
() -> STM ()
forall a. a -> STM a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
Maybe CIDInfo -> STM (Maybe CIDInfo)
forall a. a -> STM a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe CIDInfo
mncid
case Maybe CIDInfo
mr of
Maybe CIDInfo
Nothing -> () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
Just CIDInfo
ncid -> Connection -> LR -> IO ()
forall q. KeepQlog q => q -> LR -> IO ()
qlogCIDUpdate Connection
conn (LR -> IO ()) -> LR -> IO ()
forall a b. (a -> b) -> a -> b
$ CID -> LR
Remote (CID -> LR) -> CID -> LR
forall a b. (a -> b) -> a -> b
$ CIDInfo -> CID
cidInfoCID CIDInfo
ncid
waitPeerCID :: Connection -> IO CIDInfo
waitPeerCID :: Connection -> IO CIDInfo
waitPeerCID conn :: Connection
conn@Connection{Recv
Buffer
Array EncryptionLevel (TVar [ReceivedPacket])
IOArray Bool Coder1RTT
IOArray EncryptionLevel Cipher
IOArray EncryptionLevel Protector
IOArray EncryptionLevel Coder
ThreadId
TVar TxFlow
TVar Concurrency
TVar MigrationState
TVar CIDDB
IORef Bool
IORef Int
IORef (IO ())
IORef (Bool, Int)
IORef (Map Word64 (Weak ThreadId))
IORef Socket
IORef RxFlow
IORef Microseconds
IORef VersionInfo
IORef AuthCIDs
IORef Parameters
IORef StreamTable
IORef PeerInfo
IORef Concurrency
IORef Negotiated
IORef CIDDB
IORef RoleInfo
Rate
OutputQ
CryptoQ
InputQ
VersionInfo
RecvQ
SizedBuffer
ConnState
Parameters
LDCC
Hooks
Shared
Send
DebugLogger
CID -> StatelessResetToken
QLogger
connLDCC :: Connection -> LDCC
connResources :: Connection -> IORef (IO ())
decryptBuf :: Connection -> Buffer
encryptRes :: Connection -> SizedBuffer
encodeBuf :: Connection -> Buffer
connPeerAuthCIDs :: Connection -> IORef AuthCIDs
connMyAuthCIDs :: Connection -> IORef AuthCIDs
negotiated :: Connection -> IORef Negotiated
currentKeyPhase :: Connection -> IORef (Bool, Int)
protectors :: Connection -> IOArray EncryptionLevel Protector
coders1RTT :: Connection -> IOArray Bool Coder1RTT
coders :: Connection -> IOArray EncryptionLevel Coder
ciphers :: Connection -> IOArray EncryptionLevel Cipher
pendingQ :: Connection -> Array EncryptionLevel (TVar [ReceivedPacket])
bytesRx :: Connection -> IORef Int
bytesTx :: Connection -> IORef Int
minIdleTimeout :: Connection -> IORef Microseconds
sentRetirePriorTo :: Connection -> IORef Bool
migrationState :: Connection -> TVar MigrationState
flowRx :: Connection -> IORef RxFlow
flowTx :: Connection -> TVar TxFlow
peerUniStreamId :: Connection -> IORef Concurrency
peerStreamId :: Connection -> IORef Concurrency
myUniStreamId :: Connection -> TVar Concurrency
myStreamId :: Connection -> TVar Concurrency
streamTable :: Connection -> IORef StreamTable
peerPacketNumber :: Connection -> IORef Int
delayedAckCancel :: Connection -> IORef (IO ())
delayedAckCount :: Connection -> IORef Int
shared :: Connection -> Shared
outputRate :: Connection -> Rate
outputQ :: Connection -> OutputQ
cryptoQ :: Connection -> CryptoQ
inputQ :: Connection -> InputQ
peerInfo :: Connection -> IORef PeerInfo
peerCIDDB :: Connection -> TVar CIDDB
peerParameters :: Connection -> IORef Parameters
myCIDDB :: Connection -> IORef CIDDB
myParameters :: Connection -> Parameters
origVersionInfo :: Connection -> VersionInfo
quicVersionInfo :: Connection -> IORef VersionInfo
roleInfo :: Connection -> IORef RoleInfo
controlRate :: Connection -> Rate
mainThreadId :: Connection -> ThreadId
readers :: Connection -> IORef (Map Word64 (Weak ThreadId))
genStatelessResetToken :: Connection -> CID -> StatelessResetToken
connSocket :: Connection -> IORef Socket
connRecvQ :: Connection -> RecvQ
connRecv :: Connection -> Recv
connSend :: Connection -> Send
connHooks :: Connection -> Hooks
connQLog :: Connection -> QLogger
connDebugLog :: Connection -> DebugLogger
connState :: Connection -> ConnState
connState :: ConnState
connDebugLog :: DebugLogger
connQLog :: QLogger
connHooks :: Hooks
connSend :: Send
connRecv :: Recv
connRecvQ :: RecvQ
connSocket :: IORef Socket
genStatelessResetToken :: CID -> StatelessResetToken
readers :: IORef (Map Word64 (Weak ThreadId))
mainThreadId :: ThreadId
controlRate :: Rate
roleInfo :: IORef RoleInfo
quicVersionInfo :: IORef VersionInfo
origVersionInfo :: VersionInfo
myParameters :: Parameters
myCIDDB :: IORef CIDDB
peerParameters :: IORef Parameters
peerCIDDB :: TVar CIDDB
peerInfo :: IORef PeerInfo
inputQ :: InputQ
cryptoQ :: CryptoQ
outputQ :: OutputQ
outputRate :: Rate
shared :: Shared
delayedAckCount :: IORef Int
delayedAckCancel :: IORef (IO ())
peerPacketNumber :: IORef Int
streamTable :: IORef StreamTable
myStreamId :: TVar Concurrency
myUniStreamId :: TVar Concurrency
peerStreamId :: IORef Concurrency
peerUniStreamId :: IORef Concurrency
flowTx :: TVar TxFlow
flowRx :: IORef RxFlow
migrationState :: TVar MigrationState
sentRetirePriorTo :: IORef Bool
minIdleTimeout :: IORef Microseconds
bytesTx :: IORef Int
bytesRx :: IORef Int
pendingQ :: Array EncryptionLevel (TVar [ReceivedPacket])
ciphers :: IOArray EncryptionLevel Cipher
coders :: IOArray EncryptionLevel Coder
coders1RTT :: IOArray Bool Coder1RTT
protectors :: IOArray EncryptionLevel Protector
currentKeyPhase :: IORef (Bool, Int)
negotiated :: IORef Negotiated
connMyAuthCIDs :: IORef AuthCIDs
connPeerAuthCIDs :: IORef AuthCIDs
encodeBuf :: Buffer
encryptRes :: SizedBuffer
decryptBuf :: Buffer
connResources :: IORef (IO ())
connLDCC :: LDCC
..} = do
CIDInfo
r <- STM CIDInfo -> IO CIDInfo
forall a. STM a -> IO a
atomically (STM CIDInfo -> IO CIDInfo) -> STM CIDInfo -> IO CIDInfo
forall a b. (a -> b) -> a -> b
$ do
let ref :: TVar CIDDB
ref = TVar CIDDB
peerCIDDB
CIDDB
db <- TVar CIDDB -> STM CIDDB
forall a. TVar a -> STM a
readTVar TVar CIDDB
ref
Maybe CIDInfo
mncid <- Connection -> STM (Maybe CIDInfo)
pickPeerCID Connection
conn
Bool -> STM ()
check (Bool -> STM ()) -> Bool -> STM ()
forall a b. (a -> b) -> a -> b
$ Maybe CIDInfo -> Bool
forall a. Maybe a -> Bool
isJust Maybe CIDInfo
mncid
let u :: CIDInfo
u = CIDDB -> CIDInfo
usedCIDInfo CIDDB
db
Connection -> CIDInfo -> Bool -> STM ()
setPeerCID Connection
conn (Maybe CIDInfo -> CIDInfo
forall a. HasCallStack => Maybe a -> a
fromJust Maybe CIDInfo
mncid) Bool
True
CIDInfo -> STM CIDInfo
forall a. a -> STM a
forall (m :: * -> *) a. Monad m => a -> m a
return CIDInfo
u
Connection -> LR -> IO ()
forall q. KeepQlog q => q -> LR -> IO ()
qlogCIDUpdate Connection
conn (LR -> IO ()) -> LR -> IO ()
forall a b. (a -> b) -> a -> b
$ CID -> LR
Remote (CID -> LR) -> CID -> LR
forall a b. (a -> b) -> a -> b
$ CIDInfo -> CID
cidInfoCID CIDInfo
r
CIDInfo -> IO CIDInfo
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return CIDInfo
r
pickPeerCID :: Connection -> STM (Maybe CIDInfo)
pickPeerCID :: Connection -> STM (Maybe CIDInfo)
pickPeerCID Connection{Recv
Buffer
Array EncryptionLevel (TVar [ReceivedPacket])
IOArray Bool Coder1RTT
IOArray EncryptionLevel Cipher
IOArray EncryptionLevel Protector
IOArray EncryptionLevel Coder
ThreadId
TVar TxFlow
TVar Concurrency
TVar MigrationState
TVar CIDDB
IORef Bool
IORef Int
IORef (IO ())
IORef (Bool, Int)
IORef (Map Word64 (Weak ThreadId))
IORef Socket
IORef RxFlow
IORef Microseconds
IORef VersionInfo
IORef AuthCIDs
IORef Parameters
IORef StreamTable
IORef PeerInfo
IORef Concurrency
IORef Negotiated
IORef CIDDB
IORef RoleInfo
Rate
OutputQ
CryptoQ
InputQ
VersionInfo
RecvQ
SizedBuffer
ConnState
Parameters
LDCC
Hooks
Shared
Send
DebugLogger
CID -> StatelessResetToken
QLogger
connLDCC :: Connection -> LDCC
connResources :: Connection -> IORef (IO ())
decryptBuf :: Connection -> Buffer
encryptRes :: Connection -> SizedBuffer
encodeBuf :: Connection -> Buffer
connPeerAuthCIDs :: Connection -> IORef AuthCIDs
connMyAuthCIDs :: Connection -> IORef AuthCIDs
negotiated :: Connection -> IORef Negotiated
currentKeyPhase :: Connection -> IORef (Bool, Int)
protectors :: Connection -> IOArray EncryptionLevel Protector
coders1RTT :: Connection -> IOArray Bool Coder1RTT
coders :: Connection -> IOArray EncryptionLevel Coder
ciphers :: Connection -> IOArray EncryptionLevel Cipher
pendingQ :: Connection -> Array EncryptionLevel (TVar [ReceivedPacket])
bytesRx :: Connection -> IORef Int
bytesTx :: Connection -> IORef Int
minIdleTimeout :: Connection -> IORef Microseconds
sentRetirePriorTo :: Connection -> IORef Bool
migrationState :: Connection -> TVar MigrationState
flowRx :: Connection -> IORef RxFlow
flowTx :: Connection -> TVar TxFlow
peerUniStreamId :: Connection -> IORef Concurrency
peerStreamId :: Connection -> IORef Concurrency
myUniStreamId :: Connection -> TVar Concurrency
myStreamId :: Connection -> TVar Concurrency
streamTable :: Connection -> IORef StreamTable
peerPacketNumber :: Connection -> IORef Int
delayedAckCancel :: Connection -> IORef (IO ())
delayedAckCount :: Connection -> IORef Int
shared :: Connection -> Shared
outputRate :: Connection -> Rate
outputQ :: Connection -> OutputQ
cryptoQ :: Connection -> CryptoQ
inputQ :: Connection -> InputQ
peerInfo :: Connection -> IORef PeerInfo
peerCIDDB :: Connection -> TVar CIDDB
peerParameters :: Connection -> IORef Parameters
myCIDDB :: Connection -> IORef CIDDB
myParameters :: Connection -> Parameters
origVersionInfo :: Connection -> VersionInfo
quicVersionInfo :: Connection -> IORef VersionInfo
roleInfo :: Connection -> IORef RoleInfo
controlRate :: Connection -> Rate
mainThreadId :: Connection -> ThreadId
readers :: Connection -> IORef (Map Word64 (Weak ThreadId))
genStatelessResetToken :: Connection -> CID -> StatelessResetToken
connSocket :: Connection -> IORef Socket
connRecvQ :: Connection -> RecvQ
connRecv :: Connection -> Recv
connSend :: Connection -> Send
connHooks :: Connection -> Hooks
connQLog :: Connection -> QLogger
connDebugLog :: Connection -> DebugLogger
connState :: Connection -> ConnState
connState :: ConnState
connDebugLog :: DebugLogger
connQLog :: QLogger
connHooks :: Hooks
connSend :: Send
connRecv :: Recv
connRecvQ :: RecvQ
connSocket :: IORef Socket
genStatelessResetToken :: CID -> StatelessResetToken
readers :: IORef (Map Word64 (Weak ThreadId))
mainThreadId :: ThreadId
controlRate :: Rate
roleInfo :: IORef RoleInfo
quicVersionInfo :: IORef VersionInfo
origVersionInfo :: VersionInfo
myParameters :: Parameters
myCIDDB :: IORef CIDDB
peerParameters :: IORef Parameters
peerCIDDB :: TVar CIDDB
peerInfo :: IORef PeerInfo
inputQ :: InputQ
cryptoQ :: CryptoQ
outputQ :: OutputQ
outputRate :: Rate
shared :: Shared
delayedAckCount :: IORef Int
delayedAckCancel :: IORef (IO ())
peerPacketNumber :: IORef Int
streamTable :: IORef StreamTable
myStreamId :: TVar Concurrency
myUniStreamId :: TVar Concurrency
peerStreamId :: IORef Concurrency
peerUniStreamId :: IORef Concurrency
flowTx :: TVar TxFlow
flowRx :: IORef RxFlow
migrationState :: TVar MigrationState
sentRetirePriorTo :: IORef Bool
minIdleTimeout :: IORef Microseconds
bytesTx :: IORef Int
bytesRx :: IORef Int
pendingQ :: Array EncryptionLevel (TVar [ReceivedPacket])
ciphers :: IOArray EncryptionLevel Cipher
coders :: IOArray EncryptionLevel Coder
coders1RTT :: IOArray Bool Coder1RTT
protectors :: IOArray EncryptionLevel Protector
currentKeyPhase :: IORef (Bool, Int)
negotiated :: IORef Negotiated
connMyAuthCIDs :: IORef AuthCIDs
connPeerAuthCIDs :: IORef AuthCIDs
encodeBuf :: Buffer
encryptRes :: SizedBuffer
decryptBuf :: Buffer
connResources :: IORef (IO ())
connLDCC :: LDCC
..} = do
CIDDB
db <- TVar CIDDB -> STM CIDDB
forall a. TVar a -> STM a
readTVar TVar CIDDB
peerCIDDB
let n :: Int
n = CIDInfo -> Int
cidInfoSeq (CIDInfo -> Int) -> CIDInfo -> Int
forall a b. (a -> b) -> a -> b
$ CIDDB -> CIDInfo
usedCIDInfo CIDDB
db
mcidinfo :: Maybe CIDInfo
mcidinfo = Int -> IntMap CIDInfo -> Maybe CIDInfo
forall a. Int -> IntMap a -> Maybe a
IntMap.lookup (Int
n Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1) (IntMap CIDInfo -> Maybe CIDInfo)
-> IntMap CIDInfo -> Maybe CIDInfo
forall a b. (a -> b) -> a -> b
$ CIDDB -> IntMap CIDInfo
cidInfos CIDDB
db
Maybe CIDInfo -> STM (Maybe CIDInfo)
forall a. a -> STM a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe CIDInfo
mcidinfo
setPeerCID :: Connection -> CIDInfo -> Bool -> STM ()
setPeerCID :: Connection -> CIDInfo -> Bool -> STM ()
setPeerCID Connection{Recv
Buffer
Array EncryptionLevel (TVar [ReceivedPacket])
IOArray Bool Coder1RTT
IOArray EncryptionLevel Cipher
IOArray EncryptionLevel Protector
IOArray EncryptionLevel Coder
ThreadId
TVar TxFlow
TVar Concurrency
TVar MigrationState
TVar CIDDB
IORef Bool
IORef Int
IORef (IO ())
IORef (Bool, Int)
IORef (Map Word64 (Weak ThreadId))
IORef Socket
IORef RxFlow
IORef Microseconds
IORef VersionInfo
IORef AuthCIDs
IORef Parameters
IORef StreamTable
IORef PeerInfo
IORef Concurrency
IORef Negotiated
IORef CIDDB
IORef RoleInfo
Rate
OutputQ
CryptoQ
InputQ
VersionInfo
RecvQ
SizedBuffer
ConnState
Parameters
LDCC
Hooks
Shared
Send
DebugLogger
CID -> StatelessResetToken
QLogger
connLDCC :: Connection -> LDCC
connResources :: Connection -> IORef (IO ())
decryptBuf :: Connection -> Buffer
encryptRes :: Connection -> SizedBuffer
encodeBuf :: Connection -> Buffer
connPeerAuthCIDs :: Connection -> IORef AuthCIDs
connMyAuthCIDs :: Connection -> IORef AuthCIDs
negotiated :: Connection -> IORef Negotiated
currentKeyPhase :: Connection -> IORef (Bool, Int)
protectors :: Connection -> IOArray EncryptionLevel Protector
coders1RTT :: Connection -> IOArray Bool Coder1RTT
coders :: Connection -> IOArray EncryptionLevel Coder
ciphers :: Connection -> IOArray EncryptionLevel Cipher
pendingQ :: Connection -> Array EncryptionLevel (TVar [ReceivedPacket])
bytesRx :: Connection -> IORef Int
bytesTx :: Connection -> IORef Int
minIdleTimeout :: Connection -> IORef Microseconds
sentRetirePriorTo :: Connection -> IORef Bool
migrationState :: Connection -> TVar MigrationState
flowRx :: Connection -> IORef RxFlow
flowTx :: Connection -> TVar TxFlow
peerUniStreamId :: Connection -> IORef Concurrency
peerStreamId :: Connection -> IORef Concurrency
myUniStreamId :: Connection -> TVar Concurrency
myStreamId :: Connection -> TVar Concurrency
streamTable :: Connection -> IORef StreamTable
peerPacketNumber :: Connection -> IORef Int
delayedAckCancel :: Connection -> IORef (IO ())
delayedAckCount :: Connection -> IORef Int
shared :: Connection -> Shared
outputRate :: Connection -> Rate
outputQ :: Connection -> OutputQ
cryptoQ :: Connection -> CryptoQ
inputQ :: Connection -> InputQ
peerInfo :: Connection -> IORef PeerInfo
peerCIDDB :: Connection -> TVar CIDDB
peerParameters :: Connection -> IORef Parameters
myCIDDB :: Connection -> IORef CIDDB
myParameters :: Connection -> Parameters
origVersionInfo :: Connection -> VersionInfo
quicVersionInfo :: Connection -> IORef VersionInfo
roleInfo :: Connection -> IORef RoleInfo
controlRate :: Connection -> Rate
mainThreadId :: Connection -> ThreadId
readers :: Connection -> IORef (Map Word64 (Weak ThreadId))
genStatelessResetToken :: Connection -> CID -> StatelessResetToken
connSocket :: Connection -> IORef Socket
connRecvQ :: Connection -> RecvQ
connRecv :: Connection -> Recv
connSend :: Connection -> Send
connHooks :: Connection -> Hooks
connQLog :: Connection -> QLogger
connDebugLog :: Connection -> DebugLogger
connState :: Connection -> ConnState
connState :: ConnState
connDebugLog :: DebugLogger
connQLog :: QLogger
connHooks :: Hooks
connSend :: Send
connRecv :: Recv
connRecvQ :: RecvQ
connSocket :: IORef Socket
genStatelessResetToken :: CID -> StatelessResetToken
readers :: IORef (Map Word64 (Weak ThreadId))
mainThreadId :: ThreadId
controlRate :: Rate
roleInfo :: IORef RoleInfo
quicVersionInfo :: IORef VersionInfo
origVersionInfo :: VersionInfo
myParameters :: Parameters
myCIDDB :: IORef CIDDB
peerParameters :: IORef Parameters
peerCIDDB :: TVar CIDDB
peerInfo :: IORef PeerInfo
inputQ :: InputQ
cryptoQ :: CryptoQ
outputQ :: OutputQ
outputRate :: Rate
shared :: Shared
delayedAckCount :: IORef Int
delayedAckCancel :: IORef (IO ())
peerPacketNumber :: IORef Int
streamTable :: IORef StreamTable
myStreamId :: TVar Concurrency
myUniStreamId :: TVar Concurrency
peerStreamId :: IORef Concurrency
peerUniStreamId :: IORef Concurrency
flowTx :: TVar TxFlow
flowRx :: IORef RxFlow
migrationState :: TVar MigrationState
sentRetirePriorTo :: IORef Bool
minIdleTimeout :: IORef Microseconds
bytesTx :: IORef Int
bytesRx :: IORef Int
pendingQ :: Array EncryptionLevel (TVar [ReceivedPacket])
ciphers :: IOArray EncryptionLevel Cipher
coders :: IOArray EncryptionLevel Coder
coders1RTT :: IOArray Bool Coder1RTT
protectors :: IOArray EncryptionLevel Protector
currentKeyPhase :: IORef (Bool, Int)
negotiated :: IORef Negotiated
connMyAuthCIDs :: IORef AuthCIDs
connPeerAuthCIDs :: IORef AuthCIDs
encodeBuf :: Buffer
encryptRes :: SizedBuffer
decryptBuf :: Buffer
connResources :: IORef (IO ())
connLDCC :: LDCC
..} CIDInfo
cidInfo Bool
pri =
TVar CIDDB -> (CIDDB -> CIDDB) -> STM ()
forall a. TVar a -> (a -> a) -> STM ()
modifyTVar' TVar CIDDB
peerCIDDB ((CIDDB -> CIDDB) -> STM ()) -> (CIDDB -> CIDDB) -> STM ()
forall a b. (a -> b) -> a -> b
$ CIDInfo -> Bool -> CIDDB -> CIDDB
set CIDInfo
cidInfo Bool
pri
retirePeerCID :: Connection -> Int -> IO ()
retirePeerCID :: Connection -> Int -> IO ()
retirePeerCID Connection{Recv
Buffer
Array EncryptionLevel (TVar [ReceivedPacket])
IOArray Bool Coder1RTT
IOArray EncryptionLevel Cipher
IOArray EncryptionLevel Protector
IOArray EncryptionLevel Coder
ThreadId
TVar TxFlow
TVar Concurrency
TVar MigrationState
TVar CIDDB
IORef Bool
IORef Int
IORef (IO ())
IORef (Bool, Int)
IORef (Map Word64 (Weak ThreadId))
IORef Socket
IORef RxFlow
IORef Microseconds
IORef VersionInfo
IORef AuthCIDs
IORef Parameters
IORef StreamTable
IORef PeerInfo
IORef Concurrency
IORef Negotiated
IORef CIDDB
IORef RoleInfo
Rate
OutputQ
CryptoQ
InputQ
VersionInfo
RecvQ
SizedBuffer
ConnState
Parameters
LDCC
Hooks
Shared
Send
DebugLogger
CID -> StatelessResetToken
QLogger
connLDCC :: Connection -> LDCC
connResources :: Connection -> IORef (IO ())
decryptBuf :: Connection -> Buffer
encryptRes :: Connection -> SizedBuffer
encodeBuf :: Connection -> Buffer
connPeerAuthCIDs :: Connection -> IORef AuthCIDs
connMyAuthCIDs :: Connection -> IORef AuthCIDs
negotiated :: Connection -> IORef Negotiated
currentKeyPhase :: Connection -> IORef (Bool, Int)
protectors :: Connection -> IOArray EncryptionLevel Protector
coders1RTT :: Connection -> IOArray Bool Coder1RTT
coders :: Connection -> IOArray EncryptionLevel Coder
ciphers :: Connection -> IOArray EncryptionLevel Cipher
pendingQ :: Connection -> Array EncryptionLevel (TVar [ReceivedPacket])
bytesRx :: Connection -> IORef Int
bytesTx :: Connection -> IORef Int
minIdleTimeout :: Connection -> IORef Microseconds
sentRetirePriorTo :: Connection -> IORef Bool
migrationState :: Connection -> TVar MigrationState
flowRx :: Connection -> IORef RxFlow
flowTx :: Connection -> TVar TxFlow
peerUniStreamId :: Connection -> IORef Concurrency
peerStreamId :: Connection -> IORef Concurrency
myUniStreamId :: Connection -> TVar Concurrency
myStreamId :: Connection -> TVar Concurrency
streamTable :: Connection -> IORef StreamTable
peerPacketNumber :: Connection -> IORef Int
delayedAckCancel :: Connection -> IORef (IO ())
delayedAckCount :: Connection -> IORef Int
shared :: Connection -> Shared
outputRate :: Connection -> Rate
outputQ :: Connection -> OutputQ
cryptoQ :: Connection -> CryptoQ
inputQ :: Connection -> InputQ
peerInfo :: Connection -> IORef PeerInfo
peerCIDDB :: Connection -> TVar CIDDB
peerParameters :: Connection -> IORef Parameters
myCIDDB :: Connection -> IORef CIDDB
myParameters :: Connection -> Parameters
origVersionInfo :: Connection -> VersionInfo
quicVersionInfo :: Connection -> IORef VersionInfo
roleInfo :: Connection -> IORef RoleInfo
controlRate :: Connection -> Rate
mainThreadId :: Connection -> ThreadId
readers :: Connection -> IORef (Map Word64 (Weak ThreadId))
genStatelessResetToken :: Connection -> CID -> StatelessResetToken
connSocket :: Connection -> IORef Socket
connRecvQ :: Connection -> RecvQ
connRecv :: Connection -> Recv
connSend :: Connection -> Send
connHooks :: Connection -> Hooks
connQLog :: Connection -> QLogger
connDebugLog :: Connection -> DebugLogger
connState :: Connection -> ConnState
connState :: ConnState
connDebugLog :: DebugLogger
connQLog :: QLogger
connHooks :: Hooks
connSend :: Send
connRecv :: Recv
connRecvQ :: RecvQ
connSocket :: IORef Socket
genStatelessResetToken :: CID -> StatelessResetToken
readers :: IORef (Map Word64 (Weak ThreadId))
mainThreadId :: ThreadId
controlRate :: Rate
roleInfo :: IORef RoleInfo
quicVersionInfo :: IORef VersionInfo
origVersionInfo :: VersionInfo
myParameters :: Parameters
myCIDDB :: IORef CIDDB
peerParameters :: IORef Parameters
peerCIDDB :: TVar CIDDB
peerInfo :: IORef PeerInfo
inputQ :: InputQ
cryptoQ :: CryptoQ
outputQ :: OutputQ
outputRate :: Rate
shared :: Shared
delayedAckCount :: IORef Int
delayedAckCancel :: IORef (IO ())
peerPacketNumber :: IORef Int
streamTable :: IORef StreamTable
myStreamId :: TVar Concurrency
myUniStreamId :: TVar Concurrency
peerStreamId :: IORef Concurrency
peerUniStreamId :: IORef Concurrency
flowTx :: TVar TxFlow
flowRx :: IORef RxFlow
migrationState :: TVar MigrationState
sentRetirePriorTo :: IORef Bool
minIdleTimeout :: IORef Microseconds
bytesTx :: IORef Int
bytesRx :: IORef Int
pendingQ :: Array EncryptionLevel (TVar [ReceivedPacket])
ciphers :: IOArray EncryptionLevel Cipher
coders :: IOArray EncryptionLevel Coder
coders1RTT :: IOArray Bool Coder1RTT
protectors :: IOArray EncryptionLevel Protector
currentKeyPhase :: IORef (Bool, Int)
negotiated :: IORef Negotiated
connMyAuthCIDs :: IORef AuthCIDs
connPeerAuthCIDs :: IORef AuthCIDs
encodeBuf :: Buffer
encryptRes :: SizedBuffer
decryptBuf :: Buffer
connResources :: IORef (IO ())
connLDCC :: LDCC
..} Int
n =
STM () -> IO ()
forall a. STM a -> IO a
atomically (STM () -> IO ()) -> STM () -> IO ()
forall a b. (a -> b) -> a -> b
$ TVar CIDDB -> (CIDDB -> CIDDB) -> STM ()
forall a. TVar a -> (a -> a) -> STM ()
modifyTVar' TVar CIDDB
peerCIDDB ((CIDDB -> CIDDB) -> STM ()) -> (CIDDB -> CIDDB) -> STM ()
forall a b. (a -> b) -> a -> b
$ Int -> CIDDB -> CIDDB
del Int
n
checkPeerCIDCapacity :: Connection -> IO Bool
checkPeerCIDCapacity :: Connection -> IO Bool
checkPeerCIDCapacity Connection{Recv
Buffer
Array EncryptionLevel (TVar [ReceivedPacket])
IOArray Bool Coder1RTT
IOArray EncryptionLevel Cipher
IOArray EncryptionLevel Protector
IOArray EncryptionLevel Coder
ThreadId
TVar TxFlow
TVar Concurrency
TVar MigrationState
TVar CIDDB
IORef Bool
IORef Int
IORef (IO ())
IORef (Bool, Int)
IORef (Map Word64 (Weak ThreadId))
IORef Socket
IORef RxFlow
IORef Microseconds
IORef VersionInfo
IORef AuthCIDs
IORef Parameters
IORef StreamTable
IORef PeerInfo
IORef Concurrency
IORef Negotiated
IORef CIDDB
IORef RoleInfo
Rate
OutputQ
CryptoQ
InputQ
VersionInfo
RecvQ
SizedBuffer
ConnState
Parameters
LDCC
Hooks
Shared
Send
DebugLogger
CID -> StatelessResetToken
QLogger
connLDCC :: Connection -> LDCC
connResources :: Connection -> IORef (IO ())
decryptBuf :: Connection -> Buffer
encryptRes :: Connection -> SizedBuffer
encodeBuf :: Connection -> Buffer
connPeerAuthCIDs :: Connection -> IORef AuthCIDs
connMyAuthCIDs :: Connection -> IORef AuthCIDs
negotiated :: Connection -> IORef Negotiated
currentKeyPhase :: Connection -> IORef (Bool, Int)
protectors :: Connection -> IOArray EncryptionLevel Protector
coders1RTT :: Connection -> IOArray Bool Coder1RTT
coders :: Connection -> IOArray EncryptionLevel Coder
ciphers :: Connection -> IOArray EncryptionLevel Cipher
pendingQ :: Connection -> Array EncryptionLevel (TVar [ReceivedPacket])
bytesRx :: Connection -> IORef Int
bytesTx :: Connection -> IORef Int
minIdleTimeout :: Connection -> IORef Microseconds
sentRetirePriorTo :: Connection -> IORef Bool
migrationState :: Connection -> TVar MigrationState
flowRx :: Connection -> IORef RxFlow
flowTx :: Connection -> TVar TxFlow
peerUniStreamId :: Connection -> IORef Concurrency
peerStreamId :: Connection -> IORef Concurrency
myUniStreamId :: Connection -> TVar Concurrency
myStreamId :: Connection -> TVar Concurrency
streamTable :: Connection -> IORef StreamTable
peerPacketNumber :: Connection -> IORef Int
delayedAckCancel :: Connection -> IORef (IO ())
delayedAckCount :: Connection -> IORef Int
shared :: Connection -> Shared
outputRate :: Connection -> Rate
outputQ :: Connection -> OutputQ
cryptoQ :: Connection -> CryptoQ
inputQ :: Connection -> InputQ
peerInfo :: Connection -> IORef PeerInfo
peerCIDDB :: Connection -> TVar CIDDB
peerParameters :: Connection -> IORef Parameters
myCIDDB :: Connection -> IORef CIDDB
myParameters :: Connection -> Parameters
origVersionInfo :: Connection -> VersionInfo
quicVersionInfo :: Connection -> IORef VersionInfo
roleInfo :: Connection -> IORef RoleInfo
controlRate :: Connection -> Rate
mainThreadId :: Connection -> ThreadId
readers :: Connection -> IORef (Map Word64 (Weak ThreadId))
genStatelessResetToken :: Connection -> CID -> StatelessResetToken
connSocket :: Connection -> IORef Socket
connRecvQ :: Connection -> RecvQ
connRecv :: Connection -> Recv
connSend :: Connection -> Send
connHooks :: Connection -> Hooks
connQLog :: Connection -> QLogger
connDebugLog :: Connection -> DebugLogger
connState :: Connection -> ConnState
connState :: ConnState
connDebugLog :: DebugLogger
connQLog :: QLogger
connHooks :: Hooks
connSend :: Send
connRecv :: Recv
connRecvQ :: RecvQ
connSocket :: IORef Socket
genStatelessResetToken :: CID -> StatelessResetToken
readers :: IORef (Map Word64 (Weak ThreadId))
mainThreadId :: ThreadId
controlRate :: Rate
roleInfo :: IORef RoleInfo
quicVersionInfo :: IORef VersionInfo
origVersionInfo :: VersionInfo
myParameters :: Parameters
myCIDDB :: IORef CIDDB
peerParameters :: IORef Parameters
peerCIDDB :: TVar CIDDB
peerInfo :: IORef PeerInfo
inputQ :: InputQ
cryptoQ :: CryptoQ
outputQ :: OutputQ
outputRate :: Rate
shared :: Shared
delayedAckCount :: IORef Int
delayedAckCancel :: IORef (IO ())
peerPacketNumber :: IORef Int
streamTable :: IORef StreamTable
myStreamId :: TVar Concurrency
myUniStreamId :: TVar Concurrency
peerStreamId :: IORef Concurrency
peerUniStreamId :: IORef Concurrency
flowTx :: TVar TxFlow
flowRx :: IORef RxFlow
migrationState :: TVar MigrationState
sentRetirePriorTo :: IORef Bool
minIdleTimeout :: IORef Microseconds
bytesTx :: IORef Int
bytesRx :: IORef Int
pendingQ :: Array EncryptionLevel (TVar [ReceivedPacket])
ciphers :: IOArray EncryptionLevel Cipher
coders :: IOArray EncryptionLevel Coder
coders1RTT :: IOArray Bool Coder1RTT
protectors :: IOArray EncryptionLevel Protector
currentKeyPhase :: IORef (Bool, Int)
negotiated :: IORef Negotiated
connMyAuthCIDs :: IORef AuthCIDs
connPeerAuthCIDs :: IORef AuthCIDs
encodeBuf :: Buffer
encryptRes :: SizedBuffer
decryptBuf :: Buffer
connResources :: IORef (IO ())
connLDCC :: LDCC
..} = do
Int
lim <- Parameters -> Int
activeConnectionIdLimit (Parameters -> Int) -> IO Parameters -> IO Int
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> IORef Parameters -> IO Parameters
forall a. IORef a -> IO a
readIORef IORef Parameters
peerParameters
Int
cap <- IntMap CIDInfo -> Int
forall a. IntMap a -> Int
IntMap.size (IntMap CIDInfo -> Int)
-> (CIDDB -> IntMap CIDInfo) -> CIDDB -> Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CIDDB -> IntMap CIDInfo
cidInfos (CIDDB -> Int) -> IO CIDDB -> IO Int
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> IORef CIDDB -> IO CIDDB
forall a. IORef a -> IO a
readIORef IORef CIDDB
myCIDDB
Bool -> IO Bool
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (Int
cap Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Int
lim)
getMyRetirePriorTo :: Connection -> IO Int
getMyRetirePriorTo :: Connection -> IO Int
getMyRetirePriorTo Connection{Recv
Buffer
Array EncryptionLevel (TVar [ReceivedPacket])
IOArray Bool Coder1RTT
IOArray EncryptionLevel Cipher
IOArray EncryptionLevel Protector
IOArray EncryptionLevel Coder
ThreadId
TVar TxFlow
TVar Concurrency
TVar MigrationState
TVar CIDDB
IORef Bool
IORef Int
IORef (IO ())
IORef (Bool, Int)
IORef (Map Word64 (Weak ThreadId))
IORef Socket
IORef RxFlow
IORef Microseconds
IORef VersionInfo
IORef AuthCIDs
IORef Parameters
IORef StreamTable
IORef PeerInfo
IORef Concurrency
IORef Negotiated
IORef CIDDB
IORef RoleInfo
Rate
OutputQ
CryptoQ
InputQ
VersionInfo
RecvQ
SizedBuffer
ConnState
Parameters
LDCC
Hooks
Shared
Send
DebugLogger
CID -> StatelessResetToken
QLogger
connLDCC :: Connection -> LDCC
connResources :: Connection -> IORef (IO ())
decryptBuf :: Connection -> Buffer
encryptRes :: Connection -> SizedBuffer
encodeBuf :: Connection -> Buffer
connPeerAuthCIDs :: Connection -> IORef AuthCIDs
connMyAuthCIDs :: Connection -> IORef AuthCIDs
negotiated :: Connection -> IORef Negotiated
currentKeyPhase :: Connection -> IORef (Bool, Int)
protectors :: Connection -> IOArray EncryptionLevel Protector
coders1RTT :: Connection -> IOArray Bool Coder1RTT
coders :: Connection -> IOArray EncryptionLevel Coder
ciphers :: Connection -> IOArray EncryptionLevel Cipher
pendingQ :: Connection -> Array EncryptionLevel (TVar [ReceivedPacket])
bytesRx :: Connection -> IORef Int
bytesTx :: Connection -> IORef Int
minIdleTimeout :: Connection -> IORef Microseconds
sentRetirePriorTo :: Connection -> IORef Bool
migrationState :: Connection -> TVar MigrationState
flowRx :: Connection -> IORef RxFlow
flowTx :: Connection -> TVar TxFlow
peerUniStreamId :: Connection -> IORef Concurrency
peerStreamId :: Connection -> IORef Concurrency
myUniStreamId :: Connection -> TVar Concurrency
myStreamId :: Connection -> TVar Concurrency
streamTable :: Connection -> IORef StreamTable
peerPacketNumber :: Connection -> IORef Int
delayedAckCancel :: Connection -> IORef (IO ())
delayedAckCount :: Connection -> IORef Int
shared :: Connection -> Shared
outputRate :: Connection -> Rate
outputQ :: Connection -> OutputQ
cryptoQ :: Connection -> CryptoQ
inputQ :: Connection -> InputQ
peerInfo :: Connection -> IORef PeerInfo
peerCIDDB :: Connection -> TVar CIDDB
peerParameters :: Connection -> IORef Parameters
myCIDDB :: Connection -> IORef CIDDB
myParameters :: Connection -> Parameters
origVersionInfo :: Connection -> VersionInfo
quicVersionInfo :: Connection -> IORef VersionInfo
roleInfo :: Connection -> IORef RoleInfo
controlRate :: Connection -> Rate
mainThreadId :: Connection -> ThreadId
readers :: Connection -> IORef (Map Word64 (Weak ThreadId))
genStatelessResetToken :: Connection -> CID -> StatelessResetToken
connSocket :: Connection -> IORef Socket
connRecvQ :: Connection -> RecvQ
connRecv :: Connection -> Recv
connSend :: Connection -> Send
connHooks :: Connection -> Hooks
connQLog :: Connection -> QLogger
connDebugLog :: Connection -> DebugLogger
connState :: Connection -> ConnState
connState :: ConnState
connDebugLog :: DebugLogger
connQLog :: QLogger
connHooks :: Hooks
connSend :: Send
connRecv :: Recv
connRecvQ :: RecvQ
connSocket :: IORef Socket
genStatelessResetToken :: CID -> StatelessResetToken
readers :: IORef (Map Word64 (Weak ThreadId))
mainThreadId :: ThreadId
controlRate :: Rate
roleInfo :: IORef RoleInfo
quicVersionInfo :: IORef VersionInfo
origVersionInfo :: VersionInfo
myParameters :: Parameters
myCIDDB :: IORef CIDDB
peerParameters :: IORef Parameters
peerCIDDB :: TVar CIDDB
peerInfo :: IORef PeerInfo
inputQ :: InputQ
cryptoQ :: CryptoQ
outputQ :: OutputQ
outputRate :: Rate
shared :: Shared
delayedAckCount :: IORef Int
delayedAckCancel :: IORef (IO ())
peerPacketNumber :: IORef Int
streamTable :: IORef StreamTable
myStreamId :: TVar Concurrency
myUniStreamId :: TVar Concurrency
peerStreamId :: IORef Concurrency
peerUniStreamId :: IORef Concurrency
flowTx :: TVar TxFlow
flowRx :: IORef RxFlow
migrationState :: TVar MigrationState
sentRetirePriorTo :: IORef Bool
minIdleTimeout :: IORef Microseconds
bytesTx :: IORef Int
bytesRx :: IORef Int
pendingQ :: Array EncryptionLevel (TVar [ReceivedPacket])
ciphers :: IOArray EncryptionLevel Cipher
coders :: IOArray EncryptionLevel Coder
coders1RTT :: IOArray Bool Coder1RTT
protectors :: IOArray EncryptionLevel Protector
currentKeyPhase :: IORef (Bool, Int)
negotiated :: IORef Negotiated
connMyAuthCIDs :: IORef AuthCIDs
connPeerAuthCIDs :: IORef AuthCIDs
encodeBuf :: Buffer
encryptRes :: SizedBuffer
decryptBuf :: Buffer
connResources :: IORef (IO ())
connLDCC :: LDCC
..} = CIDDB -> Int
retirePriorTo (CIDDB -> Int) -> IO CIDDB -> IO Int
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> IORef CIDDB -> IO CIDDB
forall a. IORef a -> IO a
readIORef IORef CIDDB
myCIDDB
setMyRetirePriorTo :: Connection -> Int -> IO ()
setMyRetirePriorTo :: Connection -> Int -> IO ()
setMyRetirePriorTo Connection{Recv
Buffer
Array EncryptionLevel (TVar [ReceivedPacket])
IOArray Bool Coder1RTT
IOArray EncryptionLevel Cipher
IOArray EncryptionLevel Protector
IOArray EncryptionLevel Coder
ThreadId
TVar TxFlow
TVar Concurrency
TVar MigrationState
TVar CIDDB
IORef Bool
IORef Int
IORef (IO ())
IORef (Bool, Int)
IORef (Map Word64 (Weak ThreadId))
IORef Socket
IORef RxFlow
IORef Microseconds
IORef VersionInfo
IORef AuthCIDs
IORef Parameters
IORef StreamTable
IORef PeerInfo
IORef Concurrency
IORef Negotiated
IORef CIDDB
IORef RoleInfo
Rate
OutputQ
CryptoQ
InputQ
VersionInfo
RecvQ
SizedBuffer
ConnState
Parameters
LDCC
Hooks
Shared
Send
DebugLogger
CID -> StatelessResetToken
QLogger
connLDCC :: Connection -> LDCC
connResources :: Connection -> IORef (IO ())
decryptBuf :: Connection -> Buffer
encryptRes :: Connection -> SizedBuffer
encodeBuf :: Connection -> Buffer
connPeerAuthCIDs :: Connection -> IORef AuthCIDs
connMyAuthCIDs :: Connection -> IORef AuthCIDs
negotiated :: Connection -> IORef Negotiated
currentKeyPhase :: Connection -> IORef (Bool, Int)
protectors :: Connection -> IOArray EncryptionLevel Protector
coders1RTT :: Connection -> IOArray Bool Coder1RTT
coders :: Connection -> IOArray EncryptionLevel Coder
ciphers :: Connection -> IOArray EncryptionLevel Cipher
pendingQ :: Connection -> Array EncryptionLevel (TVar [ReceivedPacket])
bytesRx :: Connection -> IORef Int
bytesTx :: Connection -> IORef Int
minIdleTimeout :: Connection -> IORef Microseconds
sentRetirePriorTo :: Connection -> IORef Bool
migrationState :: Connection -> TVar MigrationState
flowRx :: Connection -> IORef RxFlow
flowTx :: Connection -> TVar TxFlow
peerUniStreamId :: Connection -> IORef Concurrency
peerStreamId :: Connection -> IORef Concurrency
myUniStreamId :: Connection -> TVar Concurrency
myStreamId :: Connection -> TVar Concurrency
streamTable :: Connection -> IORef StreamTable
peerPacketNumber :: Connection -> IORef Int
delayedAckCancel :: Connection -> IORef (IO ())
delayedAckCount :: Connection -> IORef Int
shared :: Connection -> Shared
outputRate :: Connection -> Rate
outputQ :: Connection -> OutputQ
cryptoQ :: Connection -> CryptoQ
inputQ :: Connection -> InputQ
peerInfo :: Connection -> IORef PeerInfo
peerCIDDB :: Connection -> TVar CIDDB
peerParameters :: Connection -> IORef Parameters
myCIDDB :: Connection -> IORef CIDDB
myParameters :: Connection -> Parameters
origVersionInfo :: Connection -> VersionInfo
quicVersionInfo :: Connection -> IORef VersionInfo
roleInfo :: Connection -> IORef RoleInfo
controlRate :: Connection -> Rate
mainThreadId :: Connection -> ThreadId
readers :: Connection -> IORef (Map Word64 (Weak ThreadId))
genStatelessResetToken :: Connection -> CID -> StatelessResetToken
connSocket :: Connection -> IORef Socket
connRecvQ :: Connection -> RecvQ
connRecv :: Connection -> Recv
connSend :: Connection -> Send
connHooks :: Connection -> Hooks
connQLog :: Connection -> QLogger
connDebugLog :: Connection -> DebugLogger
connState :: Connection -> ConnState
connState :: ConnState
connDebugLog :: DebugLogger
connQLog :: QLogger
connHooks :: Hooks
connSend :: Send
connRecv :: Recv
connRecvQ :: RecvQ
connSocket :: IORef Socket
genStatelessResetToken :: CID -> StatelessResetToken
readers :: IORef (Map Word64 (Weak ThreadId))
mainThreadId :: ThreadId
controlRate :: Rate
roleInfo :: IORef RoleInfo
quicVersionInfo :: IORef VersionInfo
origVersionInfo :: VersionInfo
myParameters :: Parameters
myCIDDB :: IORef CIDDB
peerParameters :: IORef Parameters
peerCIDDB :: TVar CIDDB
peerInfo :: IORef PeerInfo
inputQ :: InputQ
cryptoQ :: CryptoQ
outputQ :: OutputQ
outputRate :: Rate
shared :: Shared
delayedAckCount :: IORef Int
delayedAckCancel :: IORef (IO ())
peerPacketNumber :: IORef Int
streamTable :: IORef StreamTable
myStreamId :: TVar Concurrency
myUniStreamId :: TVar Concurrency
peerStreamId :: IORef Concurrency
peerUniStreamId :: IORef Concurrency
flowTx :: TVar TxFlow
flowRx :: IORef RxFlow
migrationState :: TVar MigrationState
sentRetirePriorTo :: IORef Bool
minIdleTimeout :: IORef Microseconds
bytesTx :: IORef Int
bytesRx :: IORef Int
pendingQ :: Array EncryptionLevel (TVar [ReceivedPacket])
ciphers :: IOArray EncryptionLevel Cipher
coders :: IOArray EncryptionLevel Coder
coders1RTT :: IOArray Bool Coder1RTT
protectors :: IOArray EncryptionLevel Protector
currentKeyPhase :: IORef (Bool, Int)
negotiated :: IORef Negotiated
connMyAuthCIDs :: IORef AuthCIDs
connPeerAuthCIDs :: IORef AuthCIDs
encodeBuf :: Buffer
encryptRes :: SizedBuffer
decryptBuf :: Buffer
connResources :: IORef (IO ())
connLDCC :: LDCC
..} Int
rpt =
IORef CIDDB -> (CIDDB -> CIDDB) -> IO ()
forall a. IORef a -> (a -> a) -> IO ()
modifyIORef' IORef CIDDB
myCIDDB ((CIDDB -> CIDDB) -> IO ()) -> (CIDDB -> CIDDB) -> IO ()
forall a b. (a -> b) -> a -> b
$ \CIDDB
db -> CIDDB
db{retirePriorTo = rpt}
getPeerRetirePriorTo :: Connection -> IO Int
getPeerRetirePriorTo :: Connection -> IO Int
getPeerRetirePriorTo Connection{Recv
Buffer
Array EncryptionLevel (TVar [ReceivedPacket])
IOArray Bool Coder1RTT
IOArray EncryptionLevel Cipher
IOArray EncryptionLevel Protector
IOArray EncryptionLevel Coder
ThreadId
TVar TxFlow
TVar Concurrency
TVar MigrationState
TVar CIDDB
IORef Bool
IORef Int
IORef (IO ())
IORef (Bool, Int)
IORef (Map Word64 (Weak ThreadId))
IORef Socket
IORef RxFlow
IORef Microseconds
IORef VersionInfo
IORef AuthCIDs
IORef Parameters
IORef StreamTable
IORef PeerInfo
IORef Concurrency
IORef Negotiated
IORef CIDDB
IORef RoleInfo
Rate
OutputQ
CryptoQ
InputQ
VersionInfo
RecvQ
SizedBuffer
ConnState
Parameters
LDCC
Hooks
Shared
Send
DebugLogger
CID -> StatelessResetToken
QLogger
connLDCC :: Connection -> LDCC
connResources :: Connection -> IORef (IO ())
decryptBuf :: Connection -> Buffer
encryptRes :: Connection -> SizedBuffer
encodeBuf :: Connection -> Buffer
connPeerAuthCIDs :: Connection -> IORef AuthCIDs
connMyAuthCIDs :: Connection -> IORef AuthCIDs
negotiated :: Connection -> IORef Negotiated
currentKeyPhase :: Connection -> IORef (Bool, Int)
protectors :: Connection -> IOArray EncryptionLevel Protector
coders1RTT :: Connection -> IOArray Bool Coder1RTT
coders :: Connection -> IOArray EncryptionLevel Coder
ciphers :: Connection -> IOArray EncryptionLevel Cipher
pendingQ :: Connection -> Array EncryptionLevel (TVar [ReceivedPacket])
bytesRx :: Connection -> IORef Int
bytesTx :: Connection -> IORef Int
minIdleTimeout :: Connection -> IORef Microseconds
sentRetirePriorTo :: Connection -> IORef Bool
migrationState :: Connection -> TVar MigrationState
flowRx :: Connection -> IORef RxFlow
flowTx :: Connection -> TVar TxFlow
peerUniStreamId :: Connection -> IORef Concurrency
peerStreamId :: Connection -> IORef Concurrency
myUniStreamId :: Connection -> TVar Concurrency
myStreamId :: Connection -> TVar Concurrency
streamTable :: Connection -> IORef StreamTable
peerPacketNumber :: Connection -> IORef Int
delayedAckCancel :: Connection -> IORef (IO ())
delayedAckCount :: Connection -> IORef Int
shared :: Connection -> Shared
outputRate :: Connection -> Rate
outputQ :: Connection -> OutputQ
cryptoQ :: Connection -> CryptoQ
inputQ :: Connection -> InputQ
peerInfo :: Connection -> IORef PeerInfo
peerCIDDB :: Connection -> TVar CIDDB
peerParameters :: Connection -> IORef Parameters
myCIDDB :: Connection -> IORef CIDDB
myParameters :: Connection -> Parameters
origVersionInfo :: Connection -> VersionInfo
quicVersionInfo :: Connection -> IORef VersionInfo
roleInfo :: Connection -> IORef RoleInfo
controlRate :: Connection -> Rate
mainThreadId :: Connection -> ThreadId
readers :: Connection -> IORef (Map Word64 (Weak ThreadId))
genStatelessResetToken :: Connection -> CID -> StatelessResetToken
connSocket :: Connection -> IORef Socket
connRecvQ :: Connection -> RecvQ
connRecv :: Connection -> Recv
connSend :: Connection -> Send
connHooks :: Connection -> Hooks
connQLog :: Connection -> QLogger
connDebugLog :: Connection -> DebugLogger
connState :: Connection -> ConnState
connState :: ConnState
connDebugLog :: DebugLogger
connQLog :: QLogger
connHooks :: Hooks
connSend :: Send
connRecv :: Recv
connRecvQ :: RecvQ
connSocket :: IORef Socket
genStatelessResetToken :: CID -> StatelessResetToken
readers :: IORef (Map Word64 (Weak ThreadId))
mainThreadId :: ThreadId
controlRate :: Rate
roleInfo :: IORef RoleInfo
quicVersionInfo :: IORef VersionInfo
origVersionInfo :: VersionInfo
myParameters :: Parameters
myCIDDB :: IORef CIDDB
peerParameters :: IORef Parameters
peerCIDDB :: TVar CIDDB
peerInfo :: IORef PeerInfo
inputQ :: InputQ
cryptoQ :: CryptoQ
outputQ :: OutputQ
outputRate :: Rate
shared :: Shared
delayedAckCount :: IORef Int
delayedAckCancel :: IORef (IO ())
peerPacketNumber :: IORef Int
streamTable :: IORef StreamTable
myStreamId :: TVar Concurrency
myUniStreamId :: TVar Concurrency
peerStreamId :: IORef Concurrency
peerUniStreamId :: IORef Concurrency
flowTx :: TVar TxFlow
flowRx :: IORef RxFlow
migrationState :: TVar MigrationState
sentRetirePriorTo :: IORef Bool
minIdleTimeout :: IORef Microseconds
bytesTx :: IORef Int
bytesRx :: IORef Int
pendingQ :: Array EncryptionLevel (TVar [ReceivedPacket])
ciphers :: IOArray EncryptionLevel Cipher
coders :: IOArray EncryptionLevel Coder
coders1RTT :: IOArray Bool Coder1RTT
protectors :: IOArray EncryptionLevel Protector
currentKeyPhase :: IORef (Bool, Int)
negotiated :: IORef Negotiated
connMyAuthCIDs :: IORef AuthCIDs
connPeerAuthCIDs :: IORef AuthCIDs
encodeBuf :: Buffer
encryptRes :: SizedBuffer
decryptBuf :: Buffer
connResources :: IORef (IO ())
connLDCC :: LDCC
..} = CIDDB -> Int
retirePriorTo (CIDDB -> Int) -> IO CIDDB -> IO Int
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> TVar CIDDB -> IO CIDDB
forall a. TVar a -> IO a
readTVarIO TVar CIDDB
peerCIDDB
setPeerRetirePriorTo :: Connection -> Int -> IO ()
setPeerRetirePriorTo :: Connection -> Int -> IO ()
setPeerRetirePriorTo Connection{Recv
Buffer
Array EncryptionLevel (TVar [ReceivedPacket])
IOArray Bool Coder1RTT
IOArray EncryptionLevel Cipher
IOArray EncryptionLevel Protector
IOArray EncryptionLevel Coder
ThreadId
TVar TxFlow
TVar Concurrency
TVar MigrationState
TVar CIDDB
IORef Bool
IORef Int
IORef (IO ())
IORef (Bool, Int)
IORef (Map Word64 (Weak ThreadId))
IORef Socket
IORef RxFlow
IORef Microseconds
IORef VersionInfo
IORef AuthCIDs
IORef Parameters
IORef StreamTable
IORef PeerInfo
IORef Concurrency
IORef Negotiated
IORef CIDDB
IORef RoleInfo
Rate
OutputQ
CryptoQ
InputQ
VersionInfo
RecvQ
SizedBuffer
ConnState
Parameters
LDCC
Hooks
Shared
Send
DebugLogger
CID -> StatelessResetToken
QLogger
connLDCC :: Connection -> LDCC
connResources :: Connection -> IORef (IO ())
decryptBuf :: Connection -> Buffer
encryptRes :: Connection -> SizedBuffer
encodeBuf :: Connection -> Buffer
connPeerAuthCIDs :: Connection -> IORef AuthCIDs
connMyAuthCIDs :: Connection -> IORef AuthCIDs
negotiated :: Connection -> IORef Negotiated
currentKeyPhase :: Connection -> IORef (Bool, Int)
protectors :: Connection -> IOArray EncryptionLevel Protector
coders1RTT :: Connection -> IOArray Bool Coder1RTT
coders :: Connection -> IOArray EncryptionLevel Coder
ciphers :: Connection -> IOArray EncryptionLevel Cipher
pendingQ :: Connection -> Array EncryptionLevel (TVar [ReceivedPacket])
bytesRx :: Connection -> IORef Int
bytesTx :: Connection -> IORef Int
minIdleTimeout :: Connection -> IORef Microseconds
sentRetirePriorTo :: Connection -> IORef Bool
migrationState :: Connection -> TVar MigrationState
flowRx :: Connection -> IORef RxFlow
flowTx :: Connection -> TVar TxFlow
peerUniStreamId :: Connection -> IORef Concurrency
peerStreamId :: Connection -> IORef Concurrency
myUniStreamId :: Connection -> TVar Concurrency
myStreamId :: Connection -> TVar Concurrency
streamTable :: Connection -> IORef StreamTable
peerPacketNumber :: Connection -> IORef Int
delayedAckCancel :: Connection -> IORef (IO ())
delayedAckCount :: Connection -> IORef Int
shared :: Connection -> Shared
outputRate :: Connection -> Rate
outputQ :: Connection -> OutputQ
cryptoQ :: Connection -> CryptoQ
inputQ :: Connection -> InputQ
peerInfo :: Connection -> IORef PeerInfo
peerCIDDB :: Connection -> TVar CIDDB
peerParameters :: Connection -> IORef Parameters
myCIDDB :: Connection -> IORef CIDDB
myParameters :: Connection -> Parameters
origVersionInfo :: Connection -> VersionInfo
quicVersionInfo :: Connection -> IORef VersionInfo
roleInfo :: Connection -> IORef RoleInfo
controlRate :: Connection -> Rate
mainThreadId :: Connection -> ThreadId
readers :: Connection -> IORef (Map Word64 (Weak ThreadId))
genStatelessResetToken :: Connection -> CID -> StatelessResetToken
connSocket :: Connection -> IORef Socket
connRecvQ :: Connection -> RecvQ
connRecv :: Connection -> Recv
connSend :: Connection -> Send
connHooks :: Connection -> Hooks
connQLog :: Connection -> QLogger
connDebugLog :: Connection -> DebugLogger
connState :: Connection -> ConnState
connState :: ConnState
connDebugLog :: DebugLogger
connQLog :: QLogger
connHooks :: Hooks
connSend :: Send
connRecv :: Recv
connRecvQ :: RecvQ
connSocket :: IORef Socket
genStatelessResetToken :: CID -> StatelessResetToken
readers :: IORef (Map Word64 (Weak ThreadId))
mainThreadId :: ThreadId
controlRate :: Rate
roleInfo :: IORef RoleInfo
quicVersionInfo :: IORef VersionInfo
origVersionInfo :: VersionInfo
myParameters :: Parameters
myCIDDB :: IORef CIDDB
peerParameters :: IORef Parameters
peerCIDDB :: TVar CIDDB
peerInfo :: IORef PeerInfo
inputQ :: InputQ
cryptoQ :: CryptoQ
outputQ :: OutputQ
outputRate :: Rate
shared :: Shared
delayedAckCount :: IORef Int
delayedAckCancel :: IORef (IO ())
peerPacketNumber :: IORef Int
streamTable :: IORef StreamTable
myStreamId :: TVar Concurrency
myUniStreamId :: TVar Concurrency
peerStreamId :: IORef Concurrency
peerUniStreamId :: IORef Concurrency
flowTx :: TVar TxFlow
flowRx :: IORef RxFlow
migrationState :: TVar MigrationState
sentRetirePriorTo :: IORef Bool
minIdleTimeout :: IORef Microseconds
bytesTx :: IORef Int
bytesRx :: IORef Int
pendingQ :: Array EncryptionLevel (TVar [ReceivedPacket])
ciphers :: IOArray EncryptionLevel Cipher
coders :: IOArray EncryptionLevel Coder
coders1RTT :: IOArray Bool Coder1RTT
protectors :: IOArray EncryptionLevel Protector
currentKeyPhase :: IORef (Bool, Int)
negotiated :: IORef Negotiated
connMyAuthCIDs :: IORef AuthCIDs
connPeerAuthCIDs :: IORef AuthCIDs
encodeBuf :: Buffer
encryptRes :: SizedBuffer
decryptBuf :: Buffer
connResources :: IORef (IO ())
connLDCC :: LDCC
..} Int
rpt =
STM () -> IO ()
forall a. STM a -> IO a
atomically (STM () -> IO ()) -> STM () -> IO ()
forall a b. (a -> b) -> a -> b
$ TVar CIDDB -> (CIDDB -> CIDDB) -> STM ()
forall a. TVar a -> (a -> a) -> STM ()
modifyTVar' TVar CIDDB
peerCIDDB ((CIDDB -> CIDDB) -> STM ()) -> (CIDDB -> CIDDB) -> STM ()
forall a b. (a -> b) -> a -> b
$ \CIDDB
db -> CIDDB
db{retirePriorTo = rpt}
setPeerCIDAndRetireCIDs :: Connection -> Int -> IO [Int]
setPeerCIDAndRetireCIDs :: Connection -> Int -> IO [Int]
setPeerCIDAndRetireCIDs Connection{Recv
Buffer
Array EncryptionLevel (TVar [ReceivedPacket])
IOArray Bool Coder1RTT
IOArray EncryptionLevel Cipher
IOArray EncryptionLevel Protector
IOArray EncryptionLevel Coder
ThreadId
TVar TxFlow
TVar Concurrency
TVar MigrationState
TVar CIDDB
IORef Bool
IORef Int
IORef (IO ())
IORef (Bool, Int)
IORef (Map Word64 (Weak ThreadId))
IORef Socket
IORef RxFlow
IORef Microseconds
IORef VersionInfo
IORef AuthCIDs
IORef Parameters
IORef StreamTable
IORef PeerInfo
IORef Concurrency
IORef Negotiated
IORef CIDDB
IORef RoleInfo
Rate
OutputQ
CryptoQ
InputQ
VersionInfo
RecvQ
SizedBuffer
ConnState
Parameters
LDCC
Hooks
Shared
Send
DebugLogger
CID -> StatelessResetToken
QLogger
connLDCC :: Connection -> LDCC
connResources :: Connection -> IORef (IO ())
decryptBuf :: Connection -> Buffer
encryptRes :: Connection -> SizedBuffer
encodeBuf :: Connection -> Buffer
connPeerAuthCIDs :: Connection -> IORef AuthCIDs
connMyAuthCIDs :: Connection -> IORef AuthCIDs
negotiated :: Connection -> IORef Negotiated
currentKeyPhase :: Connection -> IORef (Bool, Int)
protectors :: Connection -> IOArray EncryptionLevel Protector
coders1RTT :: Connection -> IOArray Bool Coder1RTT
coders :: Connection -> IOArray EncryptionLevel Coder
ciphers :: Connection -> IOArray EncryptionLevel Cipher
pendingQ :: Connection -> Array EncryptionLevel (TVar [ReceivedPacket])
bytesRx :: Connection -> IORef Int
bytesTx :: Connection -> IORef Int
minIdleTimeout :: Connection -> IORef Microseconds
sentRetirePriorTo :: Connection -> IORef Bool
migrationState :: Connection -> TVar MigrationState
flowRx :: Connection -> IORef RxFlow
flowTx :: Connection -> TVar TxFlow
peerUniStreamId :: Connection -> IORef Concurrency
peerStreamId :: Connection -> IORef Concurrency
myUniStreamId :: Connection -> TVar Concurrency
myStreamId :: Connection -> TVar Concurrency
streamTable :: Connection -> IORef StreamTable
peerPacketNumber :: Connection -> IORef Int
delayedAckCancel :: Connection -> IORef (IO ())
delayedAckCount :: Connection -> IORef Int
shared :: Connection -> Shared
outputRate :: Connection -> Rate
outputQ :: Connection -> OutputQ
cryptoQ :: Connection -> CryptoQ
inputQ :: Connection -> InputQ
peerInfo :: Connection -> IORef PeerInfo
peerCIDDB :: Connection -> TVar CIDDB
peerParameters :: Connection -> IORef Parameters
myCIDDB :: Connection -> IORef CIDDB
myParameters :: Connection -> Parameters
origVersionInfo :: Connection -> VersionInfo
quicVersionInfo :: Connection -> IORef VersionInfo
roleInfo :: Connection -> IORef RoleInfo
controlRate :: Connection -> Rate
mainThreadId :: Connection -> ThreadId
readers :: Connection -> IORef (Map Word64 (Weak ThreadId))
genStatelessResetToken :: Connection -> CID -> StatelessResetToken
connSocket :: Connection -> IORef Socket
connRecvQ :: Connection -> RecvQ
connRecv :: Connection -> Recv
connSend :: Connection -> Send
connHooks :: Connection -> Hooks
connQLog :: Connection -> QLogger
connDebugLog :: Connection -> DebugLogger
connState :: Connection -> ConnState
connState :: ConnState
connDebugLog :: DebugLogger
connQLog :: QLogger
connHooks :: Hooks
connSend :: Send
connRecv :: Recv
connRecvQ :: RecvQ
connSocket :: IORef Socket
genStatelessResetToken :: CID -> StatelessResetToken
readers :: IORef (Map Word64 (Weak ThreadId))
mainThreadId :: ThreadId
controlRate :: Rate
roleInfo :: IORef RoleInfo
quicVersionInfo :: IORef VersionInfo
origVersionInfo :: VersionInfo
myParameters :: Parameters
myCIDDB :: IORef CIDDB
peerParameters :: IORef Parameters
peerCIDDB :: TVar CIDDB
peerInfo :: IORef PeerInfo
inputQ :: InputQ
cryptoQ :: CryptoQ
outputQ :: OutputQ
outputRate :: Rate
shared :: Shared
delayedAckCount :: IORef Int
delayedAckCancel :: IORef (IO ())
peerPacketNumber :: IORef Int
streamTable :: IORef StreamTable
myStreamId :: TVar Concurrency
myUniStreamId :: TVar Concurrency
peerStreamId :: IORef Concurrency
peerUniStreamId :: IORef Concurrency
flowTx :: TVar TxFlow
flowRx :: IORef RxFlow
migrationState :: TVar MigrationState
sentRetirePriorTo :: IORef Bool
minIdleTimeout :: IORef Microseconds
bytesTx :: IORef Int
bytesRx :: IORef Int
pendingQ :: Array EncryptionLevel (TVar [ReceivedPacket])
ciphers :: IOArray EncryptionLevel Cipher
coders :: IOArray EncryptionLevel Coder
coders1RTT :: IOArray Bool Coder1RTT
protectors :: IOArray EncryptionLevel Protector
currentKeyPhase :: IORef (Bool, Int)
negotiated :: IORef Negotiated
connMyAuthCIDs :: IORef AuthCIDs
connPeerAuthCIDs :: IORef AuthCIDs
encodeBuf :: Buffer
encryptRes :: SizedBuffer
decryptBuf :: Buffer
connResources :: IORef (IO ())
connLDCC :: LDCC
..} Int
rpt = STM [Int] -> IO [Int]
forall a. STM a -> IO a
atomically (STM [Int] -> IO [Int]) -> STM [Int] -> IO [Int]
forall a b. (a -> b) -> a -> b
$ do
CIDDB
db <- TVar CIDDB -> STM CIDDB
forall a. TVar a -> STM a
readTVar TVar CIDDB
peerCIDDB
let (CIDDB
db', [Int]
ns) = Int -> CIDDB -> (CIDDB, [Int])
arrange Int
rpt CIDDB
db
TVar CIDDB -> CIDDB -> STM ()
forall a. TVar a -> a -> STM ()
writeTVar TVar CIDDB
peerCIDDB CIDDB
db'
[Int] -> STM [Int]
forall a. a -> STM a
forall (m :: * -> *) a. Monad m => a -> m a
return [Int]
ns
arrange :: Int -> CIDDB -> (CIDDB, [Int])
arrange :: Int -> CIDDB -> (CIDDB, [Int])
arrange Int
rpt db :: CIDDB
db@CIDDB{Bool
Int
Map CID Int
IntMap CIDInfo
CIDInfo
usedCIDInfo :: CIDDB -> CIDInfo
revInfos :: CIDDB -> Map CID Int
triggeredByMe :: CIDDB -> Bool
cidInfos :: CIDDB -> IntMap CIDInfo
retirePriorTo :: CIDDB -> Int
usedCIDInfo :: CIDInfo
cidInfos :: IntMap CIDInfo
revInfos :: Map CID Int
nextSeqNum :: Int
retirePriorTo :: Int
triggeredByMe :: Bool
nextSeqNum :: CIDDB -> Int
..} = (CIDDB
db', [Int]
dropSeqnums)
where
(IntMap CIDInfo
toDrops, IntMap CIDInfo
cidInfos') = (Int -> CIDInfo -> Bool)
-> IntMap CIDInfo -> (IntMap CIDInfo, IntMap CIDInfo)
forall a. (Int -> a -> Bool) -> IntMap a -> (IntMap a, IntMap a)
IntMap.partitionWithKey (\Int
k CIDInfo
_ -> Int
k Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Int
rpt) IntMap CIDInfo
cidInfos
dropSeqnums :: [Int]
dropSeqnums = (Int -> CIDInfo -> [Int] -> [Int])
-> [Int] -> IntMap CIDInfo -> [Int]
forall a b. (Int -> a -> b -> b) -> b -> IntMap a -> b
IntMap.foldrWithKey (\Int
k CIDInfo
_ [Int]
ks -> Int
k Int -> [Int] -> [Int]
forall a. a -> [a] -> [a]
: [Int]
ks) [] IntMap CIDInfo
toDrops
dropCIDs :: [CID]
dropCIDs = (CIDInfo -> [CID] -> [CID]) -> [CID] -> IntMap CIDInfo -> [CID]
forall a b. (a -> b -> b) -> b -> IntMap a -> b
IntMap.foldr (\CIDInfo
c [CID]
r -> CIDInfo -> CID
cidInfoCID CIDInfo
c CID -> [CID] -> [CID]
forall a. a -> [a] -> [a]
: [CID]
r) [] IntMap CIDInfo
toDrops
usedCIDInfo' :: CIDInfo
usedCIDInfo'
| CIDInfo -> Int
cidInfoSeq CIDInfo
usedCIDInfo Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= Int
rpt = CIDInfo
usedCIDInfo
| Bool
otherwise = (Int, CIDInfo) -> CIDInfo
forall a b. (a, b) -> b
snd ((Int, CIDInfo) -> CIDInfo) -> (Int, CIDInfo) -> CIDInfo
forall a b. (a -> b) -> a -> b
$ IntMap CIDInfo -> (Int, CIDInfo)
forall a. IntMap a -> (Int, a)
IntMap.findMin IntMap CIDInfo
cidInfos'
revInfos' :: Map CID Int
revInfos' = (CID -> Map CID Int -> Map CID Int)
-> Map CID Int -> [CID] -> Map CID Int
forall a b. (a -> b -> b) -> b -> [a] -> b
forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
foldr CID -> Map CID Int -> Map CID Int
forall k a. Ord k => k -> Map k a -> Map k a
Map.delete Map CID Int
revInfos [CID]
dropCIDs
db' :: CIDDB
db' =
CIDDB
db
{ usedCIDInfo = usedCIDInfo'
, cidInfos = cidInfos'
, revInfos = revInfos'
, retirePriorTo = rpt
}
setMyCID :: Connection -> CID -> IO ()
setMyCID :: Connection -> CID -> IO ()
setMyCID conn :: Connection
conn@Connection{Recv
Buffer
Array EncryptionLevel (TVar [ReceivedPacket])
IOArray Bool Coder1RTT
IOArray EncryptionLevel Cipher
IOArray EncryptionLevel Protector
IOArray EncryptionLevel Coder
ThreadId
TVar TxFlow
TVar Concurrency
TVar MigrationState
TVar CIDDB
IORef Bool
IORef Int
IORef (IO ())
IORef (Bool, Int)
IORef (Map Word64 (Weak ThreadId))
IORef Socket
IORef RxFlow
IORef Microseconds
IORef VersionInfo
IORef AuthCIDs
IORef Parameters
IORef StreamTable
IORef PeerInfo
IORef Concurrency
IORef Negotiated
IORef CIDDB
IORef RoleInfo
Rate
OutputQ
CryptoQ
InputQ
VersionInfo
RecvQ
SizedBuffer
ConnState
Parameters
LDCC
Hooks
Shared
Send
DebugLogger
CID -> StatelessResetToken
QLogger
connLDCC :: Connection -> LDCC
connResources :: Connection -> IORef (IO ())
decryptBuf :: Connection -> Buffer
encryptRes :: Connection -> SizedBuffer
encodeBuf :: Connection -> Buffer
connPeerAuthCIDs :: Connection -> IORef AuthCIDs
connMyAuthCIDs :: Connection -> IORef AuthCIDs
negotiated :: Connection -> IORef Negotiated
currentKeyPhase :: Connection -> IORef (Bool, Int)
protectors :: Connection -> IOArray EncryptionLevel Protector
coders1RTT :: Connection -> IOArray Bool Coder1RTT
coders :: Connection -> IOArray EncryptionLevel Coder
ciphers :: Connection -> IOArray EncryptionLevel Cipher
pendingQ :: Connection -> Array EncryptionLevel (TVar [ReceivedPacket])
bytesRx :: Connection -> IORef Int
bytesTx :: Connection -> IORef Int
minIdleTimeout :: Connection -> IORef Microseconds
sentRetirePriorTo :: Connection -> IORef Bool
migrationState :: Connection -> TVar MigrationState
flowRx :: Connection -> IORef RxFlow
flowTx :: Connection -> TVar TxFlow
peerUniStreamId :: Connection -> IORef Concurrency
peerStreamId :: Connection -> IORef Concurrency
myUniStreamId :: Connection -> TVar Concurrency
myStreamId :: Connection -> TVar Concurrency
streamTable :: Connection -> IORef StreamTable
peerPacketNumber :: Connection -> IORef Int
delayedAckCancel :: Connection -> IORef (IO ())
delayedAckCount :: Connection -> IORef Int
shared :: Connection -> Shared
outputRate :: Connection -> Rate
outputQ :: Connection -> OutputQ
cryptoQ :: Connection -> CryptoQ
inputQ :: Connection -> InputQ
peerInfo :: Connection -> IORef PeerInfo
peerCIDDB :: Connection -> TVar CIDDB
peerParameters :: Connection -> IORef Parameters
myCIDDB :: Connection -> IORef CIDDB
myParameters :: Connection -> Parameters
origVersionInfo :: Connection -> VersionInfo
quicVersionInfo :: Connection -> IORef VersionInfo
roleInfo :: Connection -> IORef RoleInfo
controlRate :: Connection -> Rate
mainThreadId :: Connection -> ThreadId
readers :: Connection -> IORef (Map Word64 (Weak ThreadId))
genStatelessResetToken :: Connection -> CID -> StatelessResetToken
connSocket :: Connection -> IORef Socket
connRecvQ :: Connection -> RecvQ
connRecv :: Connection -> Recv
connSend :: Connection -> Send
connHooks :: Connection -> Hooks
connQLog :: Connection -> QLogger
connDebugLog :: Connection -> DebugLogger
connState :: Connection -> ConnState
connState :: ConnState
connDebugLog :: DebugLogger
connQLog :: QLogger
connHooks :: Hooks
connSend :: Send
connRecv :: Recv
connRecvQ :: RecvQ
connSocket :: IORef Socket
genStatelessResetToken :: CID -> StatelessResetToken
readers :: IORef (Map Word64 (Weak ThreadId))
mainThreadId :: ThreadId
controlRate :: Rate
roleInfo :: IORef RoleInfo
quicVersionInfo :: IORef VersionInfo
origVersionInfo :: VersionInfo
myParameters :: Parameters
myCIDDB :: IORef CIDDB
peerParameters :: IORef Parameters
peerCIDDB :: TVar CIDDB
peerInfo :: IORef PeerInfo
inputQ :: InputQ
cryptoQ :: CryptoQ
outputQ :: OutputQ
outputRate :: Rate
shared :: Shared
delayedAckCount :: IORef Int
delayedAckCancel :: IORef (IO ())
peerPacketNumber :: IORef Int
streamTable :: IORef StreamTable
myStreamId :: TVar Concurrency
myUniStreamId :: TVar Concurrency
peerStreamId :: IORef Concurrency
peerUniStreamId :: IORef Concurrency
flowTx :: TVar TxFlow
flowRx :: IORef RxFlow
migrationState :: TVar MigrationState
sentRetirePriorTo :: IORef Bool
minIdleTimeout :: IORef Microseconds
bytesTx :: IORef Int
bytesRx :: IORef Int
pendingQ :: Array EncryptionLevel (TVar [ReceivedPacket])
ciphers :: IOArray EncryptionLevel Cipher
coders :: IOArray EncryptionLevel Coder
coders1RTT :: IOArray Bool Coder1RTT
protectors :: IOArray EncryptionLevel Protector
currentKeyPhase :: IORef (Bool, Int)
negotiated :: IORef Negotiated
connMyAuthCIDs :: IORef AuthCIDs
connPeerAuthCIDs :: IORef AuthCIDs
encodeBuf :: Buffer
encryptRes :: SizedBuffer
decryptBuf :: Buffer
connResources :: IORef (IO ())
connLDCC :: LDCC
..} CID
ncid = do
Bool
r <- IORef CIDDB -> (CIDDB -> (CIDDB, Bool)) -> IO Bool
forall a b. IORef a -> (a -> (a, b)) -> IO b
atomicModifyIORef' IORef CIDDB
myCIDDB CIDDB -> (CIDDB, Bool)
findSet
Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when Bool
r (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$ Connection -> LR -> IO ()
forall q. KeepQlog q => q -> LR -> IO ()
qlogCIDUpdate Connection
conn (LR -> IO ()) -> LR -> IO ()
forall a b. (a -> b) -> a -> b
$ CID -> LR
Local CID
ncid
where
findSet :: CIDDB -> (CIDDB, Bool)
findSet db :: CIDDB
db@CIDDB{Bool
Int
Map CID Int
IntMap CIDInfo
CIDInfo
usedCIDInfo :: CIDDB -> CIDInfo
revInfos :: CIDDB -> Map CID Int
triggeredByMe :: CIDDB -> Bool
cidInfos :: CIDDB -> IntMap CIDInfo
retirePriorTo :: CIDDB -> Int
nextSeqNum :: CIDDB -> Int
usedCIDInfo :: CIDInfo
cidInfos :: IntMap CIDInfo
revInfos :: Map CID Int
nextSeqNum :: Int
retirePriorTo :: Int
triggeredByMe :: Bool
..}
| CIDInfo -> CID
cidInfoCID CIDInfo
usedCIDInfo CID -> CID -> Bool
forall a. Eq a => a -> a -> Bool
== CID
ncid = (CIDDB
db, Bool
False)
| Bool
otherwise = case CID -> Map CID Int -> Maybe Int
forall k a. Ord k => k -> Map k a -> Maybe a
Map.lookup CID
ncid Map CID Int
revInfos of
Maybe Int
Nothing -> (CIDDB
db, Bool
False)
Just Int
n -> case Int -> IntMap CIDInfo -> Maybe CIDInfo
forall a. Int -> IntMap a -> Maybe a
IntMap.lookup Int
n IntMap CIDInfo
cidInfos of
Maybe CIDInfo
Nothing -> (CIDDB
db, Bool
False)
Just CIDInfo
ncidinfo -> (CIDInfo -> Bool -> CIDDB -> CIDDB
set CIDInfo
ncidinfo Bool
False CIDDB
db, Bool
True)
retireMyCID :: Connection -> Int -> IO (Maybe CIDInfo)
retireMyCID :: Connection -> Int -> IO (Maybe CIDInfo)
retireMyCID Connection{Recv
Buffer
Array EncryptionLevel (TVar [ReceivedPacket])
IOArray Bool Coder1RTT
IOArray EncryptionLevel Cipher
IOArray EncryptionLevel Protector
IOArray EncryptionLevel Coder
ThreadId
TVar TxFlow
TVar Concurrency
TVar MigrationState
TVar CIDDB
IORef Bool
IORef Int
IORef (IO ())
IORef (Bool, Int)
IORef (Map Word64 (Weak ThreadId))
IORef Socket
IORef RxFlow
IORef Microseconds
IORef VersionInfo
IORef AuthCIDs
IORef Parameters
IORef StreamTable
IORef PeerInfo
IORef Concurrency
IORef Negotiated
IORef CIDDB
IORef RoleInfo
Rate
OutputQ
CryptoQ
InputQ
VersionInfo
RecvQ
SizedBuffer
ConnState
Parameters
LDCC
Hooks
Shared
Send
DebugLogger
CID -> StatelessResetToken
QLogger
connLDCC :: Connection -> LDCC
connResources :: Connection -> IORef (IO ())
decryptBuf :: Connection -> Buffer
encryptRes :: Connection -> SizedBuffer
encodeBuf :: Connection -> Buffer
connPeerAuthCIDs :: Connection -> IORef AuthCIDs
connMyAuthCIDs :: Connection -> IORef AuthCIDs
negotiated :: Connection -> IORef Negotiated
currentKeyPhase :: Connection -> IORef (Bool, Int)
protectors :: Connection -> IOArray EncryptionLevel Protector
coders1RTT :: Connection -> IOArray Bool Coder1RTT
coders :: Connection -> IOArray EncryptionLevel Coder
ciphers :: Connection -> IOArray EncryptionLevel Cipher
pendingQ :: Connection -> Array EncryptionLevel (TVar [ReceivedPacket])
bytesRx :: Connection -> IORef Int
bytesTx :: Connection -> IORef Int
minIdleTimeout :: Connection -> IORef Microseconds
sentRetirePriorTo :: Connection -> IORef Bool
migrationState :: Connection -> TVar MigrationState
flowRx :: Connection -> IORef RxFlow
flowTx :: Connection -> TVar TxFlow
peerUniStreamId :: Connection -> IORef Concurrency
peerStreamId :: Connection -> IORef Concurrency
myUniStreamId :: Connection -> TVar Concurrency
myStreamId :: Connection -> TVar Concurrency
streamTable :: Connection -> IORef StreamTable
peerPacketNumber :: Connection -> IORef Int
delayedAckCancel :: Connection -> IORef (IO ())
delayedAckCount :: Connection -> IORef Int
shared :: Connection -> Shared
outputRate :: Connection -> Rate
outputQ :: Connection -> OutputQ
cryptoQ :: Connection -> CryptoQ
inputQ :: Connection -> InputQ
peerInfo :: Connection -> IORef PeerInfo
peerCIDDB :: Connection -> TVar CIDDB
peerParameters :: Connection -> IORef Parameters
myCIDDB :: Connection -> IORef CIDDB
myParameters :: Connection -> Parameters
origVersionInfo :: Connection -> VersionInfo
quicVersionInfo :: Connection -> IORef VersionInfo
roleInfo :: Connection -> IORef RoleInfo
controlRate :: Connection -> Rate
mainThreadId :: Connection -> ThreadId
readers :: Connection -> IORef (Map Word64 (Weak ThreadId))
genStatelessResetToken :: Connection -> CID -> StatelessResetToken
connSocket :: Connection -> IORef Socket
connRecvQ :: Connection -> RecvQ
connRecv :: Connection -> Recv
connSend :: Connection -> Send
connHooks :: Connection -> Hooks
connQLog :: Connection -> QLogger
connDebugLog :: Connection -> DebugLogger
connState :: Connection -> ConnState
connState :: ConnState
connDebugLog :: DebugLogger
connQLog :: QLogger
connHooks :: Hooks
connSend :: Send
connRecv :: Recv
connRecvQ :: RecvQ
connSocket :: IORef Socket
genStatelessResetToken :: CID -> StatelessResetToken
readers :: IORef (Map Word64 (Weak ThreadId))
mainThreadId :: ThreadId
controlRate :: Rate
roleInfo :: IORef RoleInfo
quicVersionInfo :: IORef VersionInfo
origVersionInfo :: VersionInfo
myParameters :: Parameters
myCIDDB :: IORef CIDDB
peerParameters :: IORef Parameters
peerCIDDB :: TVar CIDDB
peerInfo :: IORef PeerInfo
inputQ :: InputQ
cryptoQ :: CryptoQ
outputQ :: OutputQ
outputRate :: Rate
shared :: Shared
delayedAckCount :: IORef Int
delayedAckCancel :: IORef (IO ())
peerPacketNumber :: IORef Int
streamTable :: IORef StreamTable
myStreamId :: TVar Concurrency
myUniStreamId :: TVar Concurrency
peerStreamId :: IORef Concurrency
peerUniStreamId :: IORef Concurrency
flowTx :: TVar TxFlow
flowRx :: IORef RxFlow
migrationState :: TVar MigrationState
sentRetirePriorTo :: IORef Bool
minIdleTimeout :: IORef Microseconds
bytesTx :: IORef Int
bytesRx :: IORef Int
pendingQ :: Array EncryptionLevel (TVar [ReceivedPacket])
ciphers :: IOArray EncryptionLevel Cipher
coders :: IOArray EncryptionLevel Coder
coders1RTT :: IOArray Bool Coder1RTT
protectors :: IOArray EncryptionLevel Protector
currentKeyPhase :: IORef (Bool, Int)
negotiated :: IORef Negotiated
connMyAuthCIDs :: IORef AuthCIDs
connPeerAuthCIDs :: IORef AuthCIDs
encodeBuf :: Buffer
encryptRes :: SizedBuffer
decryptBuf :: Buffer
connResources :: IORef (IO ())
connLDCC :: LDCC
..} Int
n = IORef CIDDB
-> (CIDDB -> (CIDDB, Maybe CIDInfo)) -> IO (Maybe CIDInfo)
forall a b. IORef a -> (a -> (a, b)) -> IO b
atomicModifyIORef' IORef CIDDB
myCIDDB ((CIDDB -> (CIDDB, Maybe CIDInfo)) -> IO (Maybe CIDInfo))
-> (CIDDB -> (CIDDB, Maybe CIDInfo)) -> IO (Maybe CIDInfo)
forall a b. (a -> b) -> a -> b
$ Int -> CIDDB -> (CIDDB, Maybe CIDInfo)
del' Int
n
set :: CIDInfo -> Bool -> CIDDB -> CIDDB
set :: CIDInfo -> Bool -> CIDDB -> CIDDB
set CIDInfo
cidInfo Bool
pri CIDDB
db = CIDDB
db'
where
db' :: CIDDB
db' =
CIDDB
db
{ usedCIDInfo = cidInfo
, triggeredByMe = pri
}
add :: CIDInfo -> CIDDB -> CIDDB
add :: CIDInfo -> CIDDB -> CIDDB
add CIDInfo
cidInfo db :: CIDDB
db@CIDDB{Bool
Int
Map CID Int
IntMap CIDInfo
CIDInfo
usedCIDInfo :: CIDDB -> CIDInfo
revInfos :: CIDDB -> Map CID Int
triggeredByMe :: CIDDB -> Bool
cidInfos :: CIDDB -> IntMap CIDInfo
retirePriorTo :: CIDDB -> Int
nextSeqNum :: CIDDB -> Int
usedCIDInfo :: CIDInfo
cidInfos :: IntMap CIDInfo
revInfos :: Map CID Int
nextSeqNum :: Int
retirePriorTo :: Int
triggeredByMe :: Bool
..} = CIDDB
db'
where
db' :: CIDDB
db' =
CIDDB
db
{ cidInfos = IntMap.insert (cidInfoSeq cidInfo) cidInfo cidInfos
, revInfos = Map.insert (cidInfoCID cidInfo) (cidInfoSeq cidInfo) revInfos
}
new :: CID -> StatelessResetToken -> CIDDB -> (CIDDB, CIDInfo)
new :: CID -> StatelessResetToken -> CIDDB -> (CIDDB, CIDInfo)
new CID
cid StatelessResetToken
srt db :: CIDDB
db@CIDDB{Bool
Int
Map CID Int
IntMap CIDInfo
CIDInfo
usedCIDInfo :: CIDDB -> CIDInfo
revInfos :: CIDDB -> Map CID Int
triggeredByMe :: CIDDB -> Bool
cidInfos :: CIDDB -> IntMap CIDInfo
retirePriorTo :: CIDDB -> Int
nextSeqNum :: CIDDB -> Int
usedCIDInfo :: CIDInfo
cidInfos :: IntMap CIDInfo
revInfos :: Map CID Int
nextSeqNum :: Int
retirePriorTo :: Int
triggeredByMe :: Bool
..} = (CIDDB
db', CIDInfo
cidInfo)
where
cidInfo :: CIDInfo
cidInfo = Int -> CID -> StatelessResetToken -> CIDInfo
newCIDInfo Int
nextSeqNum CID
cid StatelessResetToken
srt
db' :: CIDDB
db' =
CIDDB
db
{ nextSeqNum = nextSeqNum + 1
, cidInfos = IntMap.insert nextSeqNum cidInfo cidInfos
, revInfos = Map.insert cid nextSeqNum revInfos
}
del :: Int -> CIDDB -> CIDDB
del :: Int -> CIDDB -> CIDDB
del Int
n db :: CIDDB
db@CIDDB{Bool
Int
Map CID Int
IntMap CIDInfo
CIDInfo
usedCIDInfo :: CIDDB -> CIDInfo
revInfos :: CIDDB -> Map CID Int
triggeredByMe :: CIDDB -> Bool
cidInfos :: CIDDB -> IntMap CIDInfo
retirePriorTo :: CIDDB -> Int
nextSeqNum :: CIDDB -> Int
usedCIDInfo :: CIDInfo
cidInfos :: IntMap CIDInfo
revInfos :: Map CID Int
nextSeqNum :: Int
retirePriorTo :: Int
triggeredByMe :: Bool
..} = CIDDB
db'
where
db' :: CIDDB
db' = case Int -> IntMap CIDInfo -> Maybe CIDInfo
forall a. Int -> IntMap a -> Maybe a
IntMap.lookup Int
n IntMap CIDInfo
cidInfos of
Maybe CIDInfo
Nothing -> CIDDB
db
Just CIDInfo
cidInfo ->
CIDDB
db
{ cidInfos = IntMap.delete n cidInfos
, revInfos = Map.delete (cidInfoCID cidInfo) revInfos
}
del' :: Int -> CIDDB -> (CIDDB, Maybe CIDInfo)
del' :: Int -> CIDDB -> (CIDDB, Maybe CIDInfo)
del' Int
n db :: CIDDB
db@CIDDB{Bool
Int
Map CID Int
IntMap CIDInfo
CIDInfo
usedCIDInfo :: CIDDB -> CIDInfo
revInfos :: CIDDB -> Map CID Int
triggeredByMe :: CIDDB -> Bool
cidInfos :: CIDDB -> IntMap CIDInfo
retirePriorTo :: CIDDB -> Int
nextSeqNum :: CIDDB -> Int
usedCIDInfo :: CIDInfo
cidInfos :: IntMap CIDInfo
revInfos :: Map CID Int
nextSeqNum :: Int
retirePriorTo :: Int
triggeredByMe :: Bool
..} = (CIDDB
db', Maybe CIDInfo
mcidInfo)
where
mcidInfo :: Maybe CIDInfo
mcidInfo = Int -> IntMap CIDInfo -> Maybe CIDInfo
forall a. Int -> IntMap a -> Maybe a
IntMap.lookup Int
n IntMap CIDInfo
cidInfos
db' :: CIDDB
db' = case Maybe CIDInfo
mcidInfo of
Maybe CIDInfo
Nothing -> CIDDB
db
Just CIDInfo
cidInfo ->
CIDDB
db
{ cidInfos = IntMap.delete n cidInfos
, revInfos = Map.delete (cidInfoCID cidInfo) revInfos
}
setPeerStatelessResetToken :: Connection -> StatelessResetToken -> IO ()
setPeerStatelessResetToken :: Connection -> StatelessResetToken -> IO ()
setPeerStatelessResetToken Connection{Recv
Buffer
Array EncryptionLevel (TVar [ReceivedPacket])
IOArray Bool Coder1RTT
IOArray EncryptionLevel Cipher
IOArray EncryptionLevel Protector
IOArray EncryptionLevel Coder
ThreadId
TVar TxFlow
TVar Concurrency
TVar MigrationState
TVar CIDDB
IORef Bool
IORef Int
IORef (IO ())
IORef (Bool, Int)
IORef (Map Word64 (Weak ThreadId))
IORef Socket
IORef RxFlow
IORef Microseconds
IORef VersionInfo
IORef AuthCIDs
IORef Parameters
IORef StreamTable
IORef PeerInfo
IORef Concurrency
IORef Negotiated
IORef CIDDB
IORef RoleInfo
Rate
OutputQ
CryptoQ
InputQ
VersionInfo
RecvQ
SizedBuffer
ConnState
Parameters
LDCC
Hooks
Shared
Send
DebugLogger
CID -> StatelessResetToken
QLogger
connLDCC :: Connection -> LDCC
connResources :: Connection -> IORef (IO ())
decryptBuf :: Connection -> Buffer
encryptRes :: Connection -> SizedBuffer
encodeBuf :: Connection -> Buffer
connPeerAuthCIDs :: Connection -> IORef AuthCIDs
connMyAuthCIDs :: Connection -> IORef AuthCIDs
negotiated :: Connection -> IORef Negotiated
currentKeyPhase :: Connection -> IORef (Bool, Int)
protectors :: Connection -> IOArray EncryptionLevel Protector
coders1RTT :: Connection -> IOArray Bool Coder1RTT
coders :: Connection -> IOArray EncryptionLevel Coder
ciphers :: Connection -> IOArray EncryptionLevel Cipher
pendingQ :: Connection -> Array EncryptionLevel (TVar [ReceivedPacket])
bytesRx :: Connection -> IORef Int
bytesTx :: Connection -> IORef Int
minIdleTimeout :: Connection -> IORef Microseconds
sentRetirePriorTo :: Connection -> IORef Bool
migrationState :: Connection -> TVar MigrationState
flowRx :: Connection -> IORef RxFlow
flowTx :: Connection -> TVar TxFlow
peerUniStreamId :: Connection -> IORef Concurrency
peerStreamId :: Connection -> IORef Concurrency
myUniStreamId :: Connection -> TVar Concurrency
myStreamId :: Connection -> TVar Concurrency
streamTable :: Connection -> IORef StreamTable
peerPacketNumber :: Connection -> IORef Int
delayedAckCancel :: Connection -> IORef (IO ())
delayedAckCount :: Connection -> IORef Int
shared :: Connection -> Shared
outputRate :: Connection -> Rate
outputQ :: Connection -> OutputQ
cryptoQ :: Connection -> CryptoQ
inputQ :: Connection -> InputQ
peerInfo :: Connection -> IORef PeerInfo
peerCIDDB :: Connection -> TVar CIDDB
peerParameters :: Connection -> IORef Parameters
myCIDDB :: Connection -> IORef CIDDB
myParameters :: Connection -> Parameters
origVersionInfo :: Connection -> VersionInfo
quicVersionInfo :: Connection -> IORef VersionInfo
roleInfo :: Connection -> IORef RoleInfo
controlRate :: Connection -> Rate
mainThreadId :: Connection -> ThreadId
readers :: Connection -> IORef (Map Word64 (Weak ThreadId))
genStatelessResetToken :: Connection -> CID -> StatelessResetToken
connSocket :: Connection -> IORef Socket
connRecvQ :: Connection -> RecvQ
connRecv :: Connection -> Recv
connSend :: Connection -> Send
connHooks :: Connection -> Hooks
connQLog :: Connection -> QLogger
connDebugLog :: Connection -> DebugLogger
connState :: Connection -> ConnState
connState :: ConnState
connDebugLog :: DebugLogger
connQLog :: QLogger
connHooks :: Hooks
connSend :: Send
connRecv :: Recv
connRecvQ :: RecvQ
connSocket :: IORef Socket
genStatelessResetToken :: CID -> StatelessResetToken
readers :: IORef (Map Word64 (Weak ThreadId))
mainThreadId :: ThreadId
controlRate :: Rate
roleInfo :: IORef RoleInfo
quicVersionInfo :: IORef VersionInfo
origVersionInfo :: VersionInfo
myParameters :: Parameters
myCIDDB :: IORef CIDDB
peerParameters :: IORef Parameters
peerCIDDB :: TVar CIDDB
peerInfo :: IORef PeerInfo
inputQ :: InputQ
cryptoQ :: CryptoQ
outputQ :: OutputQ
outputRate :: Rate
shared :: Shared
delayedAckCount :: IORef Int
delayedAckCancel :: IORef (IO ())
peerPacketNumber :: IORef Int
streamTable :: IORef StreamTable
myStreamId :: TVar Concurrency
myUniStreamId :: TVar Concurrency
peerStreamId :: IORef Concurrency
peerUniStreamId :: IORef Concurrency
flowTx :: TVar TxFlow
flowRx :: IORef RxFlow
migrationState :: TVar MigrationState
sentRetirePriorTo :: IORef Bool
minIdleTimeout :: IORef Microseconds
bytesTx :: IORef Int
bytesRx :: IORef Int
pendingQ :: Array EncryptionLevel (TVar [ReceivedPacket])
ciphers :: IOArray EncryptionLevel Cipher
coders :: IOArray EncryptionLevel Coder
coders1RTT :: IOArray Bool Coder1RTT
protectors :: IOArray EncryptionLevel Protector
currentKeyPhase :: IORef (Bool, Int)
negotiated :: IORef Negotiated
connMyAuthCIDs :: IORef AuthCIDs
connPeerAuthCIDs :: IORef AuthCIDs
encodeBuf :: Buffer
encryptRes :: SizedBuffer
decryptBuf :: Buffer
connResources :: IORef (IO ())
connLDCC :: LDCC
..} StatelessResetToken
srt =
STM () -> IO ()
forall a. STM a -> IO a
atomically (STM () -> IO ()) -> STM () -> IO ()
forall a b. (a -> b) -> a -> b
$ TVar CIDDB -> (CIDDB -> CIDDB) -> STM ()
forall a. TVar a -> (a -> a) -> STM ()
modifyTVar' TVar CIDDB
peerCIDDB CIDDB -> CIDDB
adjust
where
adjust :: CIDDB -> CIDDB
adjust db :: CIDDB
db@CIDDB{Bool
Int
Map CID Int
IntMap CIDInfo
CIDInfo
usedCIDInfo :: CIDDB -> CIDInfo
revInfos :: CIDDB -> Map CID Int
triggeredByMe :: CIDDB -> Bool
cidInfos :: CIDDB -> IntMap CIDInfo
retirePriorTo :: CIDDB -> Int
nextSeqNum :: CIDDB -> Int
usedCIDInfo :: CIDInfo
cidInfos :: IntMap CIDInfo
revInfos :: Map CID Int
nextSeqNum :: Int
retirePriorTo :: Int
triggeredByMe :: Bool
..} = CIDDB
db'
where
db' :: CIDDB
db' = case Int -> IntMap CIDInfo -> Maybe CIDInfo
forall a. Int -> IntMap a -> Maybe a
IntMap.lookup Int
0 IntMap CIDInfo
cidInfos of
Maybe CIDInfo
Nothing -> CIDDB
db
Just CIDInfo
cidinfo ->
let cidinfo' :: CIDInfo
cidinfo' = CIDInfo
cidinfo{cidInfoSRT = srt}
in CIDDB
db
{ cidInfos =
IntMap.insert 0 cidinfo' $
IntMap.delete 0 cidInfos
, usedCIDInfo = cidinfo'
}
isStatelessRestTokenValid :: Connection -> StatelessResetToken -> IO Bool
isStatelessRestTokenValid :: Connection -> StatelessResetToken -> IO Bool
isStatelessRestTokenValid Connection{Recv
Buffer
Array EncryptionLevel (TVar [ReceivedPacket])
IOArray Bool Coder1RTT
IOArray EncryptionLevel Cipher
IOArray EncryptionLevel Protector
IOArray EncryptionLevel Coder
ThreadId
TVar TxFlow
TVar Concurrency
TVar MigrationState
TVar CIDDB
IORef Bool
IORef Int
IORef (IO ())
IORef (Bool, Int)
IORef (Map Word64 (Weak ThreadId))
IORef Socket
IORef RxFlow
IORef Microseconds
IORef VersionInfo
IORef AuthCIDs
IORef Parameters
IORef StreamTable
IORef PeerInfo
IORef Concurrency
IORef Negotiated
IORef CIDDB
IORef RoleInfo
Rate
OutputQ
CryptoQ
InputQ
VersionInfo
RecvQ
SizedBuffer
ConnState
Parameters
LDCC
Hooks
Shared
Send
DebugLogger
CID -> StatelessResetToken
QLogger
connLDCC :: Connection -> LDCC
connResources :: Connection -> IORef (IO ())
decryptBuf :: Connection -> Buffer
encryptRes :: Connection -> SizedBuffer
encodeBuf :: Connection -> Buffer
connPeerAuthCIDs :: Connection -> IORef AuthCIDs
connMyAuthCIDs :: Connection -> IORef AuthCIDs
negotiated :: Connection -> IORef Negotiated
currentKeyPhase :: Connection -> IORef (Bool, Int)
protectors :: Connection -> IOArray EncryptionLevel Protector
coders1RTT :: Connection -> IOArray Bool Coder1RTT
coders :: Connection -> IOArray EncryptionLevel Coder
ciphers :: Connection -> IOArray EncryptionLevel Cipher
pendingQ :: Connection -> Array EncryptionLevel (TVar [ReceivedPacket])
bytesRx :: Connection -> IORef Int
bytesTx :: Connection -> IORef Int
minIdleTimeout :: Connection -> IORef Microseconds
sentRetirePriorTo :: Connection -> IORef Bool
migrationState :: Connection -> TVar MigrationState
flowRx :: Connection -> IORef RxFlow
flowTx :: Connection -> TVar TxFlow
peerUniStreamId :: Connection -> IORef Concurrency
peerStreamId :: Connection -> IORef Concurrency
myUniStreamId :: Connection -> TVar Concurrency
myStreamId :: Connection -> TVar Concurrency
streamTable :: Connection -> IORef StreamTable
peerPacketNumber :: Connection -> IORef Int
delayedAckCancel :: Connection -> IORef (IO ())
delayedAckCount :: Connection -> IORef Int
shared :: Connection -> Shared
outputRate :: Connection -> Rate
outputQ :: Connection -> OutputQ
cryptoQ :: Connection -> CryptoQ
inputQ :: Connection -> InputQ
peerInfo :: Connection -> IORef PeerInfo
peerCIDDB :: Connection -> TVar CIDDB
peerParameters :: Connection -> IORef Parameters
myCIDDB :: Connection -> IORef CIDDB
myParameters :: Connection -> Parameters
origVersionInfo :: Connection -> VersionInfo
quicVersionInfo :: Connection -> IORef VersionInfo
roleInfo :: Connection -> IORef RoleInfo
controlRate :: Connection -> Rate
mainThreadId :: Connection -> ThreadId
readers :: Connection -> IORef (Map Word64 (Weak ThreadId))
genStatelessResetToken :: Connection -> CID -> StatelessResetToken
connSocket :: Connection -> IORef Socket
connRecvQ :: Connection -> RecvQ
connRecv :: Connection -> Recv
connSend :: Connection -> Send
connHooks :: Connection -> Hooks
connQLog :: Connection -> QLogger
connDebugLog :: Connection -> DebugLogger
connState :: Connection -> ConnState
connState :: ConnState
connDebugLog :: DebugLogger
connQLog :: QLogger
connHooks :: Hooks
connSend :: Send
connRecv :: Recv
connRecvQ :: RecvQ
connSocket :: IORef Socket
genStatelessResetToken :: CID -> StatelessResetToken
readers :: IORef (Map Word64 (Weak ThreadId))
mainThreadId :: ThreadId
controlRate :: Rate
roleInfo :: IORef RoleInfo
quicVersionInfo :: IORef VersionInfo
origVersionInfo :: VersionInfo
myParameters :: Parameters
myCIDDB :: IORef CIDDB
peerParameters :: IORef Parameters
peerCIDDB :: TVar CIDDB
peerInfo :: IORef PeerInfo
inputQ :: InputQ
cryptoQ :: CryptoQ
outputQ :: OutputQ
outputRate :: Rate
shared :: Shared
delayedAckCount :: IORef Int
delayedAckCancel :: IORef (IO ())
peerPacketNumber :: IORef Int
streamTable :: IORef StreamTable
myStreamId :: TVar Concurrency
myUniStreamId :: TVar Concurrency
peerStreamId :: IORef Concurrency
peerUniStreamId :: IORef Concurrency
flowTx :: TVar TxFlow
flowRx :: IORef RxFlow
migrationState :: TVar MigrationState
sentRetirePriorTo :: IORef Bool
minIdleTimeout :: IORef Microseconds
bytesTx :: IORef Int
bytesRx :: IORef Int
pendingQ :: Array EncryptionLevel (TVar [ReceivedPacket])
ciphers :: IOArray EncryptionLevel Cipher
coders :: IOArray EncryptionLevel Coder
coders1RTT :: IOArray Bool Coder1RTT
protectors :: IOArray EncryptionLevel Protector
currentKeyPhase :: IORef (Bool, Int)
negotiated :: IORef Negotiated
connMyAuthCIDs :: IORef AuthCIDs
connPeerAuthCIDs :: IORef AuthCIDs
encodeBuf :: Buffer
encryptRes :: SizedBuffer
decryptBuf :: Buffer
connResources :: IORef (IO ())
connLDCC :: LDCC
..} StatelessResetToken
srt = CIDDB -> Bool
srtCheck (CIDDB -> Bool) -> IO CIDDB -> IO Bool
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> TVar CIDDB -> IO CIDDB
forall a. TVar a -> IO a
readTVarIO TVar CIDDB
peerCIDDB
where
srtCheck :: CIDDB -> Bool
srtCheck CIDDB{Bool
Int
Map CID Int
IntMap CIDInfo
CIDInfo
usedCIDInfo :: CIDDB -> CIDInfo
revInfos :: CIDDB -> Map CID Int
triggeredByMe :: CIDDB -> Bool
cidInfos :: CIDDB -> IntMap CIDInfo
retirePriorTo :: CIDDB -> Int
nextSeqNum :: CIDDB -> Int
usedCIDInfo :: CIDInfo
cidInfos :: IntMap CIDInfo
revInfos :: Map CID Int
nextSeqNum :: Int
retirePriorTo :: Int
triggeredByMe :: Bool
..} = (CIDInfo -> Bool -> Bool) -> Bool -> IntMap CIDInfo -> Bool
forall a b. (a -> b -> b) -> b -> IntMap a -> b
forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
foldr CIDInfo -> Bool -> Bool
chk Bool
False IntMap CIDInfo
cidInfos
chk :: CIDInfo -> Bool -> Bool
chk CIDInfo
_ Bool
True = Bool
True
chk CIDInfo
cidInfo Bool
_ = CIDInfo -> StatelessResetToken
cidInfoSRT CIDInfo
cidInfo StatelessResetToken -> StatelessResetToken -> Bool
forall a. Eq a => a -> a -> Bool
== StatelessResetToken
srt
validatePath :: Connection -> PathInfo -> Maybe CIDInfo -> IO ()
validatePath :: Connection -> PathInfo -> Maybe CIDInfo -> IO ()
validatePath Connection
conn PathInfo
pathInfo Maybe CIDInfo
Nothing = do
PathData
pdat <- IO PathData
newPathData
Connection -> PathInfo -> PathData -> IO ()
setChallenges Connection
conn PathInfo
pathInfo PathData
pdat
Connection -> Output -> IO ()
putOutput Connection
conn (Output -> IO ()) -> Output -> IO ()
forall a b. (a -> b) -> a -> b
$ EncryptionLevel -> [Frame] -> Output
OutControl EncryptionLevel
RTT1Level [PathData -> Frame
PathChallenge PathData
pdat]
Connection -> IO ()
waitResponse Connection
conn
validatePath Connection
conn PathInfo
pathInfo (Just CIDInfo
cidInfo) = do
PathData
pdat <- IO PathData
newPathData
Connection -> PathInfo -> PathData -> IO ()
setChallenges Connection
conn PathInfo
pathInfo PathData
pdat
let retiredSeqNum :: Int
retiredSeqNum = CIDInfo -> Int
cidInfoSeq CIDInfo
cidInfo
Connection -> Int -> IO ()
retirePeerCID Connection
conn Int
retiredSeqNum
[Frame]
extra <-
if Connection -> Bool
forall a. Connector a => a -> Bool
isClient Connection
conn
then do
CIDInfo
myCidInfo <- Connection -> IO CIDInfo
getNewMyCID Connection
conn
Int
retirePriorTo' <- (Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1) (Int -> Int) -> IO Int -> IO Int
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Connection -> IO Int
getMyCIDSeqNum Connection
conn
Connection -> Int -> IO ()
setMyRetirePriorTo Connection
conn Int
retirePriorTo'
IORef Bool -> Bool -> IO ()
forall a. IORef a -> a -> IO ()
writeIORef (Connection -> IORef Bool
sentRetirePriorTo Connection
conn) Bool
True
[Frame] -> IO [Frame]
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return [CIDInfo -> Int -> Frame
NewConnectionID CIDInfo
myCidInfo Int
retirePriorTo']
else
[Frame] -> IO [Frame]
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return []
let frames :: [Frame]
frames = [Frame]
extra [Frame] -> [Frame] -> [Frame]
forall a. [a] -> [a] -> [a]
++ [PathData -> Frame
PathChallenge PathData
pdat, Int -> Frame
RetireConnectionID Int
retiredSeqNum]
Connection -> Output -> IO ()
putOutput Connection
conn (Output -> IO ()) -> Output -> IO ()
forall a b. (a -> b) -> a -> b
$ EncryptionLevel -> [Frame] -> Output
OutControl EncryptionLevel
RTT1Level [Frame]
frames
Connection -> IO ()
waitResponse Connection
conn
setChallenges :: Connection -> PathInfo -> PathData -> IO ()
setChallenges :: Connection -> PathInfo -> PathData -> IO ()
setChallenges Connection{Recv
Buffer
Array EncryptionLevel (TVar [ReceivedPacket])
IOArray Bool Coder1RTT
IOArray EncryptionLevel Cipher
IOArray EncryptionLevel Protector
IOArray EncryptionLevel Coder
ThreadId
TVar TxFlow
TVar Concurrency
TVar MigrationState
TVar CIDDB
IORef Bool
IORef Int
IORef (IO ())
IORef (Bool, Int)
IORef (Map Word64 (Weak ThreadId))
IORef Socket
IORef RxFlow
IORef Microseconds
IORef VersionInfo
IORef AuthCIDs
IORef Parameters
IORef StreamTable
IORef PeerInfo
IORef Concurrency
IORef Negotiated
IORef CIDDB
IORef RoleInfo
Rate
OutputQ
CryptoQ
InputQ
VersionInfo
RecvQ
SizedBuffer
ConnState
Parameters
LDCC
Hooks
Shared
Send
DebugLogger
CID -> StatelessResetToken
QLogger
connLDCC :: Connection -> LDCC
connResources :: Connection -> IORef (IO ())
decryptBuf :: Connection -> Buffer
encryptRes :: Connection -> SizedBuffer
encodeBuf :: Connection -> Buffer
connPeerAuthCIDs :: Connection -> IORef AuthCIDs
connMyAuthCIDs :: Connection -> IORef AuthCIDs
negotiated :: Connection -> IORef Negotiated
currentKeyPhase :: Connection -> IORef (Bool, Int)
protectors :: Connection -> IOArray EncryptionLevel Protector
coders1RTT :: Connection -> IOArray Bool Coder1RTT
coders :: Connection -> IOArray EncryptionLevel Coder
ciphers :: Connection -> IOArray EncryptionLevel Cipher
pendingQ :: Connection -> Array EncryptionLevel (TVar [ReceivedPacket])
bytesRx :: Connection -> IORef Int
bytesTx :: Connection -> IORef Int
minIdleTimeout :: Connection -> IORef Microseconds
sentRetirePriorTo :: Connection -> IORef Bool
migrationState :: Connection -> TVar MigrationState
flowRx :: Connection -> IORef RxFlow
flowTx :: Connection -> TVar TxFlow
peerUniStreamId :: Connection -> IORef Concurrency
peerStreamId :: Connection -> IORef Concurrency
myUniStreamId :: Connection -> TVar Concurrency
myStreamId :: Connection -> TVar Concurrency
streamTable :: Connection -> IORef StreamTable
peerPacketNumber :: Connection -> IORef Int
delayedAckCancel :: Connection -> IORef (IO ())
delayedAckCount :: Connection -> IORef Int
shared :: Connection -> Shared
outputRate :: Connection -> Rate
outputQ :: Connection -> OutputQ
cryptoQ :: Connection -> CryptoQ
inputQ :: Connection -> InputQ
peerInfo :: Connection -> IORef PeerInfo
peerCIDDB :: Connection -> TVar CIDDB
peerParameters :: Connection -> IORef Parameters
myCIDDB :: Connection -> IORef CIDDB
myParameters :: Connection -> Parameters
origVersionInfo :: Connection -> VersionInfo
quicVersionInfo :: Connection -> IORef VersionInfo
roleInfo :: Connection -> IORef RoleInfo
controlRate :: Connection -> Rate
mainThreadId :: Connection -> ThreadId
readers :: Connection -> IORef (Map Word64 (Weak ThreadId))
genStatelessResetToken :: Connection -> CID -> StatelessResetToken
connSocket :: Connection -> IORef Socket
connRecvQ :: Connection -> RecvQ
connRecv :: Connection -> Recv
connSend :: Connection -> Send
connHooks :: Connection -> Hooks
connQLog :: Connection -> QLogger
connDebugLog :: Connection -> DebugLogger
connState :: Connection -> ConnState
connState :: ConnState
connDebugLog :: DebugLogger
connQLog :: QLogger
connHooks :: Hooks
connSend :: Send
connRecv :: Recv
connRecvQ :: RecvQ
connSocket :: IORef Socket
genStatelessResetToken :: CID -> StatelessResetToken
readers :: IORef (Map Word64 (Weak ThreadId))
mainThreadId :: ThreadId
controlRate :: Rate
roleInfo :: IORef RoleInfo
quicVersionInfo :: IORef VersionInfo
origVersionInfo :: VersionInfo
myParameters :: Parameters
myCIDDB :: IORef CIDDB
peerParameters :: IORef Parameters
peerCIDDB :: TVar CIDDB
peerInfo :: IORef PeerInfo
inputQ :: InputQ
cryptoQ :: CryptoQ
outputQ :: OutputQ
outputRate :: Rate
shared :: Shared
delayedAckCount :: IORef Int
delayedAckCancel :: IORef (IO ())
peerPacketNumber :: IORef Int
streamTable :: IORef StreamTable
myStreamId :: TVar Concurrency
myUniStreamId :: TVar Concurrency
peerStreamId :: IORef Concurrency
peerUniStreamId :: IORef Concurrency
flowTx :: TVar TxFlow
flowRx :: IORef RxFlow
migrationState :: TVar MigrationState
sentRetirePriorTo :: IORef Bool
minIdleTimeout :: IORef Microseconds
bytesTx :: IORef Int
bytesRx :: IORef Int
pendingQ :: Array EncryptionLevel (TVar [ReceivedPacket])
ciphers :: IOArray EncryptionLevel Cipher
coders :: IOArray EncryptionLevel Coder
coders1RTT :: IOArray Bool Coder1RTT
protectors :: IOArray EncryptionLevel Protector
currentKeyPhase :: IORef (Bool, Int)
negotiated :: IORef Negotiated
connMyAuthCIDs :: IORef AuthCIDs
connPeerAuthCIDs :: IORef AuthCIDs
encodeBuf :: Buffer
encryptRes :: SizedBuffer
decryptBuf :: Buffer
connResources :: IORef (IO ())
connLDCC :: LDCC
..} PathInfo
pathInfo PathData
pdat =
STM () -> IO ()
forall a. STM a -> IO a
atomically (STM () -> IO ()) -> STM () -> IO ()
forall a b. (a -> b) -> a -> b
$ TVar MigrationState -> MigrationState -> STM ()
forall a. TVar a -> a -> STM ()
writeTVar TVar MigrationState
migrationState (MigrationState -> STM ()) -> MigrationState -> STM ()
forall a b. (a -> b) -> a -> b
$ PathInfo -> PathData -> MigrationState
SendChallenge PathInfo
pathInfo PathData
pdat
setMigrationStarted :: Connection -> IO ()
setMigrationStarted :: Connection -> IO ()
setMigrationStarted Connection{Recv
Buffer
Array EncryptionLevel (TVar [ReceivedPacket])
IOArray Bool Coder1RTT
IOArray EncryptionLevel Cipher
IOArray EncryptionLevel Protector
IOArray EncryptionLevel Coder
ThreadId
TVar TxFlow
TVar Concurrency
TVar MigrationState
TVar CIDDB
IORef Bool
IORef Int
IORef (IO ())
IORef (Bool, Int)
IORef (Map Word64 (Weak ThreadId))
IORef Socket
IORef RxFlow
IORef Microseconds
IORef VersionInfo
IORef AuthCIDs
IORef Parameters
IORef StreamTable
IORef PeerInfo
IORef Concurrency
IORef Negotiated
IORef CIDDB
IORef RoleInfo
Rate
OutputQ
CryptoQ
InputQ
VersionInfo
RecvQ
SizedBuffer
ConnState
Parameters
LDCC
Hooks
Shared
Send
DebugLogger
CID -> StatelessResetToken
QLogger
connLDCC :: Connection -> LDCC
connResources :: Connection -> IORef (IO ())
decryptBuf :: Connection -> Buffer
encryptRes :: Connection -> SizedBuffer
encodeBuf :: Connection -> Buffer
connPeerAuthCIDs :: Connection -> IORef AuthCIDs
connMyAuthCIDs :: Connection -> IORef AuthCIDs
negotiated :: Connection -> IORef Negotiated
currentKeyPhase :: Connection -> IORef (Bool, Int)
protectors :: Connection -> IOArray EncryptionLevel Protector
coders1RTT :: Connection -> IOArray Bool Coder1RTT
coders :: Connection -> IOArray EncryptionLevel Coder
ciphers :: Connection -> IOArray EncryptionLevel Cipher
pendingQ :: Connection -> Array EncryptionLevel (TVar [ReceivedPacket])
bytesRx :: Connection -> IORef Int
bytesTx :: Connection -> IORef Int
minIdleTimeout :: Connection -> IORef Microseconds
sentRetirePriorTo :: Connection -> IORef Bool
migrationState :: Connection -> TVar MigrationState
flowRx :: Connection -> IORef RxFlow
flowTx :: Connection -> TVar TxFlow
peerUniStreamId :: Connection -> IORef Concurrency
peerStreamId :: Connection -> IORef Concurrency
myUniStreamId :: Connection -> TVar Concurrency
myStreamId :: Connection -> TVar Concurrency
streamTable :: Connection -> IORef StreamTable
peerPacketNumber :: Connection -> IORef Int
delayedAckCancel :: Connection -> IORef (IO ())
delayedAckCount :: Connection -> IORef Int
shared :: Connection -> Shared
outputRate :: Connection -> Rate
outputQ :: Connection -> OutputQ
cryptoQ :: Connection -> CryptoQ
inputQ :: Connection -> InputQ
peerInfo :: Connection -> IORef PeerInfo
peerCIDDB :: Connection -> TVar CIDDB
peerParameters :: Connection -> IORef Parameters
myCIDDB :: Connection -> IORef CIDDB
myParameters :: Connection -> Parameters
origVersionInfo :: Connection -> VersionInfo
quicVersionInfo :: Connection -> IORef VersionInfo
roleInfo :: Connection -> IORef RoleInfo
controlRate :: Connection -> Rate
mainThreadId :: Connection -> ThreadId
readers :: Connection -> IORef (Map Word64 (Weak ThreadId))
genStatelessResetToken :: Connection -> CID -> StatelessResetToken
connSocket :: Connection -> IORef Socket
connRecvQ :: Connection -> RecvQ
connRecv :: Connection -> Recv
connSend :: Connection -> Send
connHooks :: Connection -> Hooks
connQLog :: Connection -> QLogger
connDebugLog :: Connection -> DebugLogger
connState :: Connection -> ConnState
connState :: ConnState
connDebugLog :: DebugLogger
connQLog :: QLogger
connHooks :: Hooks
connSend :: Send
connRecv :: Recv
connRecvQ :: RecvQ
connSocket :: IORef Socket
genStatelessResetToken :: CID -> StatelessResetToken
readers :: IORef (Map Word64 (Weak ThreadId))
mainThreadId :: ThreadId
controlRate :: Rate
roleInfo :: IORef RoleInfo
quicVersionInfo :: IORef VersionInfo
origVersionInfo :: VersionInfo
myParameters :: Parameters
myCIDDB :: IORef CIDDB
peerParameters :: IORef Parameters
peerCIDDB :: TVar CIDDB
peerInfo :: IORef PeerInfo
inputQ :: InputQ
cryptoQ :: CryptoQ
outputQ :: OutputQ
outputRate :: Rate
shared :: Shared
delayedAckCount :: IORef Int
delayedAckCancel :: IORef (IO ())
peerPacketNumber :: IORef Int
streamTable :: IORef StreamTable
myStreamId :: TVar Concurrency
myUniStreamId :: TVar Concurrency
peerStreamId :: IORef Concurrency
peerUniStreamId :: IORef Concurrency
flowTx :: TVar TxFlow
flowRx :: IORef RxFlow
migrationState :: TVar MigrationState
sentRetirePriorTo :: IORef Bool
minIdleTimeout :: IORef Microseconds
bytesTx :: IORef Int
bytesRx :: IORef Int
pendingQ :: Array EncryptionLevel (TVar [ReceivedPacket])
ciphers :: IOArray EncryptionLevel Cipher
coders :: IOArray EncryptionLevel Coder
coders1RTT :: IOArray Bool Coder1RTT
protectors :: IOArray EncryptionLevel Protector
currentKeyPhase :: IORef (Bool, Int)
negotiated :: IORef Negotiated
connMyAuthCIDs :: IORef AuthCIDs
connPeerAuthCIDs :: IORef AuthCIDs
encodeBuf :: Buffer
encryptRes :: SizedBuffer
decryptBuf :: Buffer
connResources :: IORef (IO ())
connLDCC :: LDCC
..} =
STM () -> IO ()
forall a. STM a -> IO a
atomically (STM () -> IO ()) -> STM () -> IO ()
forall a b. (a -> b) -> a -> b
$ TVar MigrationState -> MigrationState -> STM ()
forall a. TVar a -> a -> STM ()
writeTVar TVar MigrationState
migrationState MigrationState
MigrationStarted
isPathValidating :: Connection -> IO Bool
isPathValidating :: Connection -> IO Bool
isPathValidating Connection{Recv
Buffer
Array EncryptionLevel (TVar [ReceivedPacket])
IOArray Bool Coder1RTT
IOArray EncryptionLevel Cipher
IOArray EncryptionLevel Protector
IOArray EncryptionLevel Coder
ThreadId
TVar TxFlow
TVar Concurrency
TVar MigrationState
TVar CIDDB
IORef Bool
IORef Int
IORef (IO ())
IORef (Bool, Int)
IORef (Map Word64 (Weak ThreadId))
IORef Socket
IORef RxFlow
IORef Microseconds
IORef VersionInfo
IORef AuthCIDs
IORef Parameters
IORef StreamTable
IORef PeerInfo
IORef Concurrency
IORef Negotiated
IORef CIDDB
IORef RoleInfo
Rate
OutputQ
CryptoQ
InputQ
VersionInfo
RecvQ
SizedBuffer
ConnState
Parameters
LDCC
Hooks
Shared
Send
DebugLogger
CID -> StatelessResetToken
QLogger
connLDCC :: Connection -> LDCC
connResources :: Connection -> IORef (IO ())
decryptBuf :: Connection -> Buffer
encryptRes :: Connection -> SizedBuffer
encodeBuf :: Connection -> Buffer
connPeerAuthCIDs :: Connection -> IORef AuthCIDs
connMyAuthCIDs :: Connection -> IORef AuthCIDs
negotiated :: Connection -> IORef Negotiated
currentKeyPhase :: Connection -> IORef (Bool, Int)
protectors :: Connection -> IOArray EncryptionLevel Protector
coders1RTT :: Connection -> IOArray Bool Coder1RTT
coders :: Connection -> IOArray EncryptionLevel Coder
ciphers :: Connection -> IOArray EncryptionLevel Cipher
pendingQ :: Connection -> Array EncryptionLevel (TVar [ReceivedPacket])
bytesRx :: Connection -> IORef Int
bytesTx :: Connection -> IORef Int
minIdleTimeout :: Connection -> IORef Microseconds
sentRetirePriorTo :: Connection -> IORef Bool
migrationState :: Connection -> TVar MigrationState
flowRx :: Connection -> IORef RxFlow
flowTx :: Connection -> TVar TxFlow
peerUniStreamId :: Connection -> IORef Concurrency
peerStreamId :: Connection -> IORef Concurrency
myUniStreamId :: Connection -> TVar Concurrency
myStreamId :: Connection -> TVar Concurrency
streamTable :: Connection -> IORef StreamTable
peerPacketNumber :: Connection -> IORef Int
delayedAckCancel :: Connection -> IORef (IO ())
delayedAckCount :: Connection -> IORef Int
shared :: Connection -> Shared
outputRate :: Connection -> Rate
outputQ :: Connection -> OutputQ
cryptoQ :: Connection -> CryptoQ
inputQ :: Connection -> InputQ
peerInfo :: Connection -> IORef PeerInfo
peerCIDDB :: Connection -> TVar CIDDB
peerParameters :: Connection -> IORef Parameters
myCIDDB :: Connection -> IORef CIDDB
myParameters :: Connection -> Parameters
origVersionInfo :: Connection -> VersionInfo
quicVersionInfo :: Connection -> IORef VersionInfo
roleInfo :: Connection -> IORef RoleInfo
controlRate :: Connection -> Rate
mainThreadId :: Connection -> ThreadId
readers :: Connection -> IORef (Map Word64 (Weak ThreadId))
genStatelessResetToken :: Connection -> CID -> StatelessResetToken
connSocket :: Connection -> IORef Socket
connRecvQ :: Connection -> RecvQ
connRecv :: Connection -> Recv
connSend :: Connection -> Send
connHooks :: Connection -> Hooks
connQLog :: Connection -> QLogger
connDebugLog :: Connection -> DebugLogger
connState :: Connection -> ConnState
connState :: ConnState
connDebugLog :: DebugLogger
connQLog :: QLogger
connHooks :: Hooks
connSend :: Send
connRecv :: Recv
connRecvQ :: RecvQ
connSocket :: IORef Socket
genStatelessResetToken :: CID -> StatelessResetToken
readers :: IORef (Map Word64 (Weak ThreadId))
mainThreadId :: ThreadId
controlRate :: Rate
roleInfo :: IORef RoleInfo
quicVersionInfo :: IORef VersionInfo
origVersionInfo :: VersionInfo
myParameters :: Parameters
myCIDDB :: IORef CIDDB
peerParameters :: IORef Parameters
peerCIDDB :: TVar CIDDB
peerInfo :: IORef PeerInfo
inputQ :: InputQ
cryptoQ :: CryptoQ
outputQ :: OutputQ
outputRate :: Rate
shared :: Shared
delayedAckCount :: IORef Int
delayedAckCancel :: IORef (IO ())
peerPacketNumber :: IORef Int
streamTable :: IORef StreamTable
myStreamId :: TVar Concurrency
myUniStreamId :: TVar Concurrency
peerStreamId :: IORef Concurrency
peerUniStreamId :: IORef Concurrency
flowTx :: TVar TxFlow
flowRx :: IORef RxFlow
migrationState :: TVar MigrationState
sentRetirePriorTo :: IORef Bool
minIdleTimeout :: IORef Microseconds
bytesTx :: IORef Int
bytesRx :: IORef Int
pendingQ :: Array EncryptionLevel (TVar [ReceivedPacket])
ciphers :: IOArray EncryptionLevel Cipher
coders :: IOArray EncryptionLevel Coder
coders1RTT :: IOArray Bool Coder1RTT
protectors :: IOArray EncryptionLevel Protector
currentKeyPhase :: IORef (Bool, Int)
negotiated :: IORef Negotiated
connMyAuthCIDs :: IORef AuthCIDs
connPeerAuthCIDs :: IORef AuthCIDs
encodeBuf :: Buffer
encryptRes :: SizedBuffer
decryptBuf :: Buffer
connResources :: IORef (IO ())
connLDCC :: LDCC
..} = do
MigrationState
s <- TVar MigrationState -> IO MigrationState
forall a. TVar a -> IO a
readTVarIO TVar MigrationState
migrationState
case MigrationState
s of
SendChallenge{} -> Bool -> IO Bool
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
True
MigrationState
MigrationStarted -> Bool -> IO Bool
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
True
MigrationState
_ -> Bool -> IO Bool
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
False
waitResponse :: Connection -> IO ()
waitResponse :: Connection -> IO ()
waitResponse Connection{Recv
Buffer
Array EncryptionLevel (TVar [ReceivedPacket])
IOArray Bool Coder1RTT
IOArray EncryptionLevel Cipher
IOArray EncryptionLevel Protector
IOArray EncryptionLevel Coder
ThreadId
TVar TxFlow
TVar Concurrency
TVar MigrationState
TVar CIDDB
IORef Bool
IORef Int
IORef (IO ())
IORef (Bool, Int)
IORef (Map Word64 (Weak ThreadId))
IORef Socket
IORef RxFlow
IORef Microseconds
IORef VersionInfo
IORef AuthCIDs
IORef Parameters
IORef StreamTable
IORef PeerInfo
IORef Concurrency
IORef Negotiated
IORef CIDDB
IORef RoleInfo
Rate
OutputQ
CryptoQ
InputQ
VersionInfo
RecvQ
SizedBuffer
ConnState
Parameters
LDCC
Hooks
Shared
Send
DebugLogger
CID -> StatelessResetToken
QLogger
connLDCC :: Connection -> LDCC
connResources :: Connection -> IORef (IO ())
decryptBuf :: Connection -> Buffer
encryptRes :: Connection -> SizedBuffer
encodeBuf :: Connection -> Buffer
connPeerAuthCIDs :: Connection -> IORef AuthCIDs
connMyAuthCIDs :: Connection -> IORef AuthCIDs
negotiated :: Connection -> IORef Negotiated
currentKeyPhase :: Connection -> IORef (Bool, Int)
protectors :: Connection -> IOArray EncryptionLevel Protector
coders1RTT :: Connection -> IOArray Bool Coder1RTT
coders :: Connection -> IOArray EncryptionLevel Coder
ciphers :: Connection -> IOArray EncryptionLevel Cipher
pendingQ :: Connection -> Array EncryptionLevel (TVar [ReceivedPacket])
bytesRx :: Connection -> IORef Int
bytesTx :: Connection -> IORef Int
minIdleTimeout :: Connection -> IORef Microseconds
sentRetirePriorTo :: Connection -> IORef Bool
migrationState :: Connection -> TVar MigrationState
flowRx :: Connection -> IORef RxFlow
flowTx :: Connection -> TVar TxFlow
peerUniStreamId :: Connection -> IORef Concurrency
peerStreamId :: Connection -> IORef Concurrency
myUniStreamId :: Connection -> TVar Concurrency
myStreamId :: Connection -> TVar Concurrency
streamTable :: Connection -> IORef StreamTable
peerPacketNumber :: Connection -> IORef Int
delayedAckCancel :: Connection -> IORef (IO ())
delayedAckCount :: Connection -> IORef Int
shared :: Connection -> Shared
outputRate :: Connection -> Rate
outputQ :: Connection -> OutputQ
cryptoQ :: Connection -> CryptoQ
inputQ :: Connection -> InputQ
peerInfo :: Connection -> IORef PeerInfo
peerCIDDB :: Connection -> TVar CIDDB
peerParameters :: Connection -> IORef Parameters
myCIDDB :: Connection -> IORef CIDDB
myParameters :: Connection -> Parameters
origVersionInfo :: Connection -> VersionInfo
quicVersionInfo :: Connection -> IORef VersionInfo
roleInfo :: Connection -> IORef RoleInfo
controlRate :: Connection -> Rate
mainThreadId :: Connection -> ThreadId
readers :: Connection -> IORef (Map Word64 (Weak ThreadId))
genStatelessResetToken :: Connection -> CID -> StatelessResetToken
connSocket :: Connection -> IORef Socket
connRecvQ :: Connection -> RecvQ
connRecv :: Connection -> Recv
connSend :: Connection -> Send
connHooks :: Connection -> Hooks
connQLog :: Connection -> QLogger
connDebugLog :: Connection -> DebugLogger
connState :: Connection -> ConnState
connState :: ConnState
connDebugLog :: DebugLogger
connQLog :: QLogger
connHooks :: Hooks
connSend :: Send
connRecv :: Recv
connRecvQ :: RecvQ
connSocket :: IORef Socket
genStatelessResetToken :: CID -> StatelessResetToken
readers :: IORef (Map Word64 (Weak ThreadId))
mainThreadId :: ThreadId
controlRate :: Rate
roleInfo :: IORef RoleInfo
quicVersionInfo :: IORef VersionInfo
origVersionInfo :: VersionInfo
myParameters :: Parameters
myCIDDB :: IORef CIDDB
peerParameters :: IORef Parameters
peerCIDDB :: TVar CIDDB
peerInfo :: IORef PeerInfo
inputQ :: InputQ
cryptoQ :: CryptoQ
outputQ :: OutputQ
outputRate :: Rate
shared :: Shared
delayedAckCount :: IORef Int
delayedAckCancel :: IORef (IO ())
peerPacketNumber :: IORef Int
streamTable :: IORef StreamTable
myStreamId :: TVar Concurrency
myUniStreamId :: TVar Concurrency
peerStreamId :: IORef Concurrency
peerUniStreamId :: IORef Concurrency
flowTx :: TVar TxFlow
flowRx :: IORef RxFlow
migrationState :: TVar MigrationState
sentRetirePriorTo :: IORef Bool
minIdleTimeout :: IORef Microseconds
bytesTx :: IORef Int
bytesRx :: IORef Int
pendingQ :: Array EncryptionLevel (TVar [ReceivedPacket])
ciphers :: IOArray EncryptionLevel Cipher
coders :: IOArray EncryptionLevel Coder
coders1RTT :: IOArray Bool Coder1RTT
protectors :: IOArray EncryptionLevel Protector
currentKeyPhase :: IORef (Bool, Int)
negotiated :: IORef Negotiated
connMyAuthCIDs :: IORef AuthCIDs
connPeerAuthCIDs :: IORef AuthCIDs
encodeBuf :: Buffer
encryptRes :: SizedBuffer
decryptBuf :: Buffer
connResources :: IORef (IO ())
connLDCC :: LDCC
..} = STM () -> IO ()
forall a. STM a -> IO a
atomically (STM () -> IO ()) -> STM () -> IO ()
forall a b. (a -> b) -> a -> b
$ do
MigrationState
state <- TVar MigrationState -> STM MigrationState
forall a. TVar a -> STM a
readTVar TVar MigrationState
migrationState
Bool -> STM ()
check (MigrationState
state MigrationState -> MigrationState -> Bool
forall a. Eq a => a -> a -> Bool
== MigrationState
RecvResponse)
TVar MigrationState -> MigrationState -> STM ()
forall a. TVar a -> a -> STM ()
writeTVar TVar MigrationState
migrationState MigrationState
NonMigration
checkResponse :: Connection -> PathData -> IO ()
checkResponse :: Connection -> PathData -> IO ()
checkResponse Connection{Recv
Buffer
Array EncryptionLevel (TVar [ReceivedPacket])
IOArray Bool Coder1RTT
IOArray EncryptionLevel Cipher
IOArray EncryptionLevel Protector
IOArray EncryptionLevel Coder
ThreadId
TVar TxFlow
TVar Concurrency
TVar MigrationState
TVar CIDDB
IORef Bool
IORef Int
IORef (IO ())
IORef (Bool, Int)
IORef (Map Word64 (Weak ThreadId))
IORef Socket
IORef RxFlow
IORef Microseconds
IORef VersionInfo
IORef AuthCIDs
IORef Parameters
IORef StreamTable
IORef PeerInfo
IORef Concurrency
IORef Negotiated
IORef CIDDB
IORef RoleInfo
Rate
OutputQ
CryptoQ
InputQ
VersionInfo
RecvQ
SizedBuffer
ConnState
Parameters
LDCC
Hooks
Shared
Send
DebugLogger
CID -> StatelessResetToken
QLogger
connLDCC :: Connection -> LDCC
connResources :: Connection -> IORef (IO ())
decryptBuf :: Connection -> Buffer
encryptRes :: Connection -> SizedBuffer
encodeBuf :: Connection -> Buffer
connPeerAuthCIDs :: Connection -> IORef AuthCIDs
connMyAuthCIDs :: Connection -> IORef AuthCIDs
negotiated :: Connection -> IORef Negotiated
currentKeyPhase :: Connection -> IORef (Bool, Int)
protectors :: Connection -> IOArray EncryptionLevel Protector
coders1RTT :: Connection -> IOArray Bool Coder1RTT
coders :: Connection -> IOArray EncryptionLevel Coder
ciphers :: Connection -> IOArray EncryptionLevel Cipher
pendingQ :: Connection -> Array EncryptionLevel (TVar [ReceivedPacket])
bytesRx :: Connection -> IORef Int
bytesTx :: Connection -> IORef Int
minIdleTimeout :: Connection -> IORef Microseconds
sentRetirePriorTo :: Connection -> IORef Bool
migrationState :: Connection -> TVar MigrationState
flowRx :: Connection -> IORef RxFlow
flowTx :: Connection -> TVar TxFlow
peerUniStreamId :: Connection -> IORef Concurrency
peerStreamId :: Connection -> IORef Concurrency
myUniStreamId :: Connection -> TVar Concurrency
myStreamId :: Connection -> TVar Concurrency
streamTable :: Connection -> IORef StreamTable
peerPacketNumber :: Connection -> IORef Int
delayedAckCancel :: Connection -> IORef (IO ())
delayedAckCount :: Connection -> IORef Int
shared :: Connection -> Shared
outputRate :: Connection -> Rate
outputQ :: Connection -> OutputQ
cryptoQ :: Connection -> CryptoQ
inputQ :: Connection -> InputQ
peerInfo :: Connection -> IORef PeerInfo
peerCIDDB :: Connection -> TVar CIDDB
peerParameters :: Connection -> IORef Parameters
myCIDDB :: Connection -> IORef CIDDB
myParameters :: Connection -> Parameters
origVersionInfo :: Connection -> VersionInfo
quicVersionInfo :: Connection -> IORef VersionInfo
roleInfo :: Connection -> IORef RoleInfo
controlRate :: Connection -> Rate
mainThreadId :: Connection -> ThreadId
readers :: Connection -> IORef (Map Word64 (Weak ThreadId))
genStatelessResetToken :: Connection -> CID -> StatelessResetToken
connSocket :: Connection -> IORef Socket
connRecvQ :: Connection -> RecvQ
connRecv :: Connection -> Recv
connSend :: Connection -> Send
connHooks :: Connection -> Hooks
connQLog :: Connection -> QLogger
connDebugLog :: Connection -> DebugLogger
connState :: Connection -> ConnState
connState :: ConnState
connDebugLog :: DebugLogger
connQLog :: QLogger
connHooks :: Hooks
connSend :: Send
connRecv :: Recv
connRecvQ :: RecvQ
connSocket :: IORef Socket
genStatelessResetToken :: CID -> StatelessResetToken
readers :: IORef (Map Word64 (Weak ThreadId))
mainThreadId :: ThreadId
controlRate :: Rate
roleInfo :: IORef RoleInfo
quicVersionInfo :: IORef VersionInfo
origVersionInfo :: VersionInfo
myParameters :: Parameters
myCIDDB :: IORef CIDDB
peerParameters :: IORef Parameters
peerCIDDB :: TVar CIDDB
peerInfo :: IORef PeerInfo
inputQ :: InputQ
cryptoQ :: CryptoQ
outputQ :: OutputQ
outputRate :: Rate
shared :: Shared
delayedAckCount :: IORef Int
delayedAckCancel :: IORef (IO ())
peerPacketNumber :: IORef Int
streamTable :: IORef StreamTable
myStreamId :: TVar Concurrency
myUniStreamId :: TVar Concurrency
peerStreamId :: IORef Concurrency
peerUniStreamId :: IORef Concurrency
flowTx :: TVar TxFlow
flowRx :: IORef RxFlow
migrationState :: TVar MigrationState
sentRetirePriorTo :: IORef Bool
minIdleTimeout :: IORef Microseconds
bytesTx :: IORef Int
bytesRx :: IORef Int
pendingQ :: Array EncryptionLevel (TVar [ReceivedPacket])
ciphers :: IOArray EncryptionLevel Cipher
coders :: IOArray EncryptionLevel Coder
coders1RTT :: IOArray Bool Coder1RTT
protectors :: IOArray EncryptionLevel Protector
currentKeyPhase :: IORef (Bool, Int)
negotiated :: IORef Negotiated
connMyAuthCIDs :: IORef AuthCIDs
connPeerAuthCIDs :: IORef AuthCIDs
encodeBuf :: Buffer
encryptRes :: SizedBuffer
decryptBuf :: Buffer
connResources :: IORef (IO ())
connLDCC :: LDCC
..} PathData
pdat = do
MigrationState
state <- TVar MigrationState -> IO MigrationState
forall a. TVar a -> IO a
readTVarIO TVar MigrationState
migrationState
case MigrationState
state of
SendChallenge PathInfo
pathInfo PathData
pdat'
| PathData
pdat PathData -> PathData -> Bool
forall a. Eq a => a -> a -> Bool
== PathData
pdat' -> STM () -> IO ()
forall a. STM a -> IO a
atomically (STM () -> IO ()) -> STM () -> IO ()
forall a b. (a -> b) -> a -> b
$ do
TVar MigrationState -> MigrationState -> STM ()
forall a. TVar a -> a -> STM ()
writeTVar TVar MigrationState
migrationState MigrationState
RecvResponse
TVar Bool -> Bool -> STM ()
forall a. TVar a -> a -> STM ()
writeTVar (PathInfo -> TVar Bool
addressValidated PathInfo
pathInfo) Bool
True
MigrationState
_ -> () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()