{-# LANGUAGE RecordWildCards #-}
module Network.QUIC.Connection.State (
setConnection0RTTReady,
isConnection1RTTReady,
setConnection1RTTReady,
isConnectionEstablished,
setConnectionEstablished,
wait0RTTReady,
wait1RTTReady,
waitEstablished,
readConnectionFlowTx,
addTxData,
setTxMaxData,
getRxMaxData,
updateFlowRx,
checkRxMaxData,
addTxBytes,
getTxBytes,
addRxBytes,
getRxBytes,
setAddressValidated,
waitAntiAmplificationFree,
checkAntiAmplificationFree,
) where
import Control.Concurrent.STM
import Network.Control
import Network.QUIC.Connection.Types
import Network.QUIC.Connector
import Network.QUIC.Imports
import Network.QUIC.Recovery
setConnectionState :: Connection -> ConnectionState -> IO ()
setConnectionState :: Connection -> ConnectionState -> IO ()
setConnectionState Connection{Recv
Buffer
Array EncryptionLevel (TVar [ReceivedPacket])
IOArray Bool Coder1RTT
IOArray EncryptionLevel Cipher
IOArray EncryptionLevel Protector
IOArray EncryptionLevel Coder
ThreadId
TVar Bool
TVar Int
TVar TxFlow
TVar Concurrency
TVar MigrationState
TVar CIDDB
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
OutputQLim
MigrationQ
OutputQ
CryptoQ
InputQ
VersionInfo
RecvQ
SizedBuffer
ConnState
Parameters
LDCC
Hooks
Shared
Send
DebugLogger
QLogger
connState :: ConnState
connDebugLog :: DebugLogger
connQLog :: QLogger
connHooks :: Hooks
connSend :: Send
connRecv :: Recv
connRecvQ :: RecvQ
connSocket :: IORef Socket
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
outputQLim :: OutputQLim
migrationQ :: MigrationQ
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
minIdleTimeout :: IORef Microseconds
bytesTx :: TVar Int
bytesRx :: TVar Int
addressValidated :: TVar Bool
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
connResources :: IORef (IO ())
encodeBuf :: Buffer
encryptRes :: SizedBuffer
decryptBuf :: Buffer
connLDCC :: LDCC
connState :: Connection -> ConnState
connDebugLog :: Connection -> DebugLogger
connQLog :: Connection -> QLogger
connHooks :: Connection -> Hooks
connSend :: Connection -> Send
connRecv :: Connection -> Recv
connRecvQ :: Connection -> RecvQ
connSocket :: Connection -> IORef Socket
readers :: Connection -> IORef (Map Word64 (Weak ThreadId))
mainThreadId :: Connection -> ThreadId
controlRate :: Connection -> Rate
roleInfo :: Connection -> IORef RoleInfo
quicVersionInfo :: Connection -> IORef VersionInfo
origVersionInfo :: Connection -> VersionInfo
myParameters :: Connection -> Parameters
myCIDDB :: Connection -> IORef CIDDB
peerParameters :: Connection -> IORef Parameters
peerCIDDB :: Connection -> TVar CIDDB
peerInfo :: Connection -> IORef PeerInfo
inputQ :: Connection -> InputQ
cryptoQ :: Connection -> CryptoQ
outputQ :: Connection -> OutputQ
outputQLim :: Connection -> OutputQLim
migrationQ :: Connection -> MigrationQ
shared :: Connection -> Shared
delayedAckCount :: Connection -> IORef Int
delayedAckCancel :: Connection -> IORef (IO ())
peerPacketNumber :: Connection -> IORef Int
streamTable :: Connection -> IORef StreamTable
myStreamId :: Connection -> TVar Concurrency
myUniStreamId :: Connection -> TVar Concurrency
peerStreamId :: Connection -> IORef Concurrency
peerUniStreamId :: Connection -> IORef Concurrency
flowTx :: Connection -> TVar TxFlow
flowRx :: Connection -> IORef RxFlow
migrationState :: Connection -> TVar MigrationState
minIdleTimeout :: Connection -> IORef Microseconds
bytesTx :: Connection -> TVar Int
bytesRx :: Connection -> TVar Int
addressValidated :: Connection -> TVar Bool
pendingQ :: Connection -> Array EncryptionLevel (TVar [ReceivedPacket])
ciphers :: Connection -> IOArray EncryptionLevel Cipher
coders :: Connection -> IOArray EncryptionLevel Coder
coders1RTT :: Connection -> IOArray Bool Coder1RTT
protectors :: Connection -> IOArray EncryptionLevel Protector
currentKeyPhase :: Connection -> IORef (Bool, Int)
negotiated :: Connection -> IORef Negotiated
connMyAuthCIDs :: Connection -> IORef AuthCIDs
connPeerAuthCIDs :: Connection -> IORef AuthCIDs
connResources :: Connection -> IORef (IO ())
encodeBuf :: Connection -> Buffer
encryptRes :: Connection -> SizedBuffer
decryptBuf :: Connection -> Buffer
connLDCC :: Connection -> LDCC
..} ConnectionState
st =
STM () -> IO ()
forall a. STM a -> IO a
atomically (STM () -> IO ()) -> STM () -> IO ()
forall a b. (a -> b) -> a -> b
$ TVar ConnectionState -> ConnectionState -> STM ()
forall a. TVar a -> a -> STM ()
writeTVar (ConnState -> TVar ConnectionState
connectionState ConnState
connState) ConnectionState
st
setConnection0RTTReady :: Connection -> IO ()
setConnection0RTTReady :: Connection -> IO ()
setConnection0RTTReady Connection
conn = Connection -> ConnectionState -> IO ()
setConnectionState Connection
conn ConnectionState
ReadyFor0RTT
setConnection1RTTReady :: Connection -> IO ()
setConnection1RTTReady :: Connection -> IO ()
setConnection1RTTReady Connection
conn = do
Connection -> ConnectionState -> IO ()
setConnectionState Connection
conn ConnectionState
ReadyFor1RTT
IORef Bool -> Bool -> IO ()
forall a. IORef a -> a -> IO ()
writeIORef (Shared -> IORef Bool
shared1RTTReady (Shared -> IORef Bool) -> Shared -> IORef Bool
forall a b. (a -> b) -> a -> b
$ Connection -> Shared
shared Connection
conn) Bool
True
setConnectionEstablished :: Connection -> IO ()
setConnectionEstablished :: Connection -> IO ()
setConnectionEstablished Connection
conn = Connection -> ConnectionState -> IO ()
setConnectionState Connection
conn ConnectionState
Established
isConnection1RTTReady :: Connection -> IO Bool
isConnection1RTTReady :: Connection -> IO Bool
isConnection1RTTReady Connection{Recv
Buffer
Array EncryptionLevel (TVar [ReceivedPacket])
IOArray Bool Coder1RTT
IOArray EncryptionLevel Cipher
IOArray EncryptionLevel Protector
IOArray EncryptionLevel Coder
ThreadId
TVar Bool
TVar Int
TVar TxFlow
TVar Concurrency
TVar MigrationState
TVar CIDDB
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
OutputQLim
MigrationQ
OutputQ
CryptoQ
InputQ
VersionInfo
RecvQ
SizedBuffer
ConnState
Parameters
LDCC
Hooks
Shared
Send
DebugLogger
QLogger
connState :: Connection -> ConnState
connDebugLog :: Connection -> DebugLogger
connQLog :: Connection -> QLogger
connHooks :: Connection -> Hooks
connSend :: Connection -> Send
connRecv :: Connection -> Recv
connRecvQ :: Connection -> RecvQ
connSocket :: Connection -> IORef Socket
readers :: Connection -> IORef (Map Word64 (Weak ThreadId))
mainThreadId :: Connection -> ThreadId
controlRate :: Connection -> Rate
roleInfo :: Connection -> IORef RoleInfo
quicVersionInfo :: Connection -> IORef VersionInfo
origVersionInfo :: Connection -> VersionInfo
myParameters :: Connection -> Parameters
myCIDDB :: Connection -> IORef CIDDB
peerParameters :: Connection -> IORef Parameters
peerCIDDB :: Connection -> TVar CIDDB
peerInfo :: Connection -> IORef PeerInfo
inputQ :: Connection -> InputQ
cryptoQ :: Connection -> CryptoQ
outputQ :: Connection -> OutputQ
outputQLim :: Connection -> OutputQLim
migrationQ :: Connection -> MigrationQ
shared :: Connection -> Shared
delayedAckCount :: Connection -> IORef Int
delayedAckCancel :: Connection -> IORef (IO ())
peerPacketNumber :: Connection -> IORef Int
streamTable :: Connection -> IORef StreamTable
myStreamId :: Connection -> TVar Concurrency
myUniStreamId :: Connection -> TVar Concurrency
peerStreamId :: Connection -> IORef Concurrency
peerUniStreamId :: Connection -> IORef Concurrency
flowTx :: Connection -> TVar TxFlow
flowRx :: Connection -> IORef RxFlow
migrationState :: Connection -> TVar MigrationState
minIdleTimeout :: Connection -> IORef Microseconds
bytesTx :: Connection -> TVar Int
bytesRx :: Connection -> TVar Int
addressValidated :: Connection -> TVar Bool
pendingQ :: Connection -> Array EncryptionLevel (TVar [ReceivedPacket])
ciphers :: Connection -> IOArray EncryptionLevel Cipher
coders :: Connection -> IOArray EncryptionLevel Coder
coders1RTT :: Connection -> IOArray Bool Coder1RTT
protectors :: Connection -> IOArray EncryptionLevel Protector
currentKeyPhase :: Connection -> IORef (Bool, Int)
negotiated :: Connection -> IORef Negotiated
connMyAuthCIDs :: Connection -> IORef AuthCIDs
connPeerAuthCIDs :: Connection -> IORef AuthCIDs
connResources :: Connection -> IORef (IO ())
encodeBuf :: Connection -> Buffer
encryptRes :: Connection -> SizedBuffer
decryptBuf :: Connection -> Buffer
connLDCC :: Connection -> LDCC
connState :: ConnState
connDebugLog :: DebugLogger
connQLog :: QLogger
connHooks :: Hooks
connSend :: Send
connRecv :: Recv
connRecvQ :: RecvQ
connSocket :: IORef Socket
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
outputQLim :: OutputQLim
migrationQ :: MigrationQ
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
minIdleTimeout :: IORef Microseconds
bytesTx :: TVar Int
bytesRx :: TVar Int
addressValidated :: TVar Bool
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
connResources :: IORef (IO ())
encodeBuf :: Buffer
encryptRes :: SizedBuffer
decryptBuf :: Buffer
connLDCC :: LDCC
..} = 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
ConnectionState
st <- TVar ConnectionState -> STM ConnectionState
forall a. TVar a -> STM a
readTVar (TVar ConnectionState -> STM ConnectionState)
-> TVar ConnectionState -> STM ConnectionState
forall a b. (a -> b) -> a -> b
$ ConnState -> TVar ConnectionState
connectionState ConnState
connState
Bool -> STM Bool
forall a. a -> STM a
forall (m :: * -> *) a. Monad m => a -> m a
return (ConnectionState
st ConnectionState -> ConnectionState -> Bool
forall a. Ord a => a -> a -> Bool
>= ConnectionState
ReadyFor1RTT)
wait0RTTReady :: Connection -> IO ()
wait0RTTReady :: Connection -> IO ()
wait0RTTReady Connection{Recv
Buffer
Array EncryptionLevel (TVar [ReceivedPacket])
IOArray Bool Coder1RTT
IOArray EncryptionLevel Cipher
IOArray EncryptionLevel Protector
IOArray EncryptionLevel Coder
ThreadId
TVar Bool
TVar Int
TVar TxFlow
TVar Concurrency
TVar MigrationState
TVar CIDDB
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
OutputQLim
MigrationQ
OutputQ
CryptoQ
InputQ
VersionInfo
RecvQ
SizedBuffer
ConnState
Parameters
LDCC
Hooks
Shared
Send
DebugLogger
QLogger
connState :: Connection -> ConnState
connDebugLog :: Connection -> DebugLogger
connQLog :: Connection -> QLogger
connHooks :: Connection -> Hooks
connSend :: Connection -> Send
connRecv :: Connection -> Recv
connRecvQ :: Connection -> RecvQ
connSocket :: Connection -> IORef Socket
readers :: Connection -> IORef (Map Word64 (Weak ThreadId))
mainThreadId :: Connection -> ThreadId
controlRate :: Connection -> Rate
roleInfo :: Connection -> IORef RoleInfo
quicVersionInfo :: Connection -> IORef VersionInfo
origVersionInfo :: Connection -> VersionInfo
myParameters :: Connection -> Parameters
myCIDDB :: Connection -> IORef CIDDB
peerParameters :: Connection -> IORef Parameters
peerCIDDB :: Connection -> TVar CIDDB
peerInfo :: Connection -> IORef PeerInfo
inputQ :: Connection -> InputQ
cryptoQ :: Connection -> CryptoQ
outputQ :: Connection -> OutputQ
outputQLim :: Connection -> OutputQLim
migrationQ :: Connection -> MigrationQ
shared :: Connection -> Shared
delayedAckCount :: Connection -> IORef Int
delayedAckCancel :: Connection -> IORef (IO ())
peerPacketNumber :: Connection -> IORef Int
streamTable :: Connection -> IORef StreamTable
myStreamId :: Connection -> TVar Concurrency
myUniStreamId :: Connection -> TVar Concurrency
peerStreamId :: Connection -> IORef Concurrency
peerUniStreamId :: Connection -> IORef Concurrency
flowTx :: Connection -> TVar TxFlow
flowRx :: Connection -> IORef RxFlow
migrationState :: Connection -> TVar MigrationState
minIdleTimeout :: Connection -> IORef Microseconds
bytesTx :: Connection -> TVar Int
bytesRx :: Connection -> TVar Int
addressValidated :: Connection -> TVar Bool
pendingQ :: Connection -> Array EncryptionLevel (TVar [ReceivedPacket])
ciphers :: Connection -> IOArray EncryptionLevel Cipher
coders :: Connection -> IOArray EncryptionLevel Coder
coders1RTT :: Connection -> IOArray Bool Coder1RTT
protectors :: Connection -> IOArray EncryptionLevel Protector
currentKeyPhase :: Connection -> IORef (Bool, Int)
negotiated :: Connection -> IORef Negotiated
connMyAuthCIDs :: Connection -> IORef AuthCIDs
connPeerAuthCIDs :: Connection -> IORef AuthCIDs
connResources :: Connection -> IORef (IO ())
encodeBuf :: Connection -> Buffer
encryptRes :: Connection -> SizedBuffer
decryptBuf :: Connection -> Buffer
connLDCC :: Connection -> LDCC
connState :: ConnState
connDebugLog :: DebugLogger
connQLog :: QLogger
connHooks :: Hooks
connSend :: Send
connRecv :: Recv
connRecvQ :: RecvQ
connSocket :: IORef Socket
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
outputQLim :: OutputQLim
migrationQ :: MigrationQ
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
minIdleTimeout :: IORef Microseconds
bytesTx :: TVar Int
bytesRx :: TVar Int
addressValidated :: TVar Bool
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
connResources :: IORef (IO ())
encodeBuf :: Buffer
encryptRes :: SizedBuffer
decryptBuf :: Buffer
connLDCC :: LDCC
..} = STM () -> IO ()
forall a. STM a -> IO a
atomically (STM () -> IO ()) -> STM () -> IO ()
forall a b. (a -> b) -> a -> b
$ do
ConnectionState
cs <- TVar ConnectionState -> STM ConnectionState
forall a. TVar a -> STM a
readTVar (TVar ConnectionState -> STM ConnectionState)
-> TVar ConnectionState -> STM ConnectionState
forall a b. (a -> b) -> a -> b
$ ConnState -> TVar ConnectionState
connectionState ConnState
connState
Bool -> STM ()
check (ConnectionState
cs ConnectionState -> ConnectionState -> Bool
forall a. Ord a => a -> a -> Bool
>= ConnectionState
ReadyFor0RTT)
wait1RTTReady :: Connection -> IO ()
wait1RTTReady :: Connection -> IO ()
wait1RTTReady Connection{Recv
Buffer
Array EncryptionLevel (TVar [ReceivedPacket])
IOArray Bool Coder1RTT
IOArray EncryptionLevel Cipher
IOArray EncryptionLevel Protector
IOArray EncryptionLevel Coder
ThreadId
TVar Bool
TVar Int
TVar TxFlow
TVar Concurrency
TVar MigrationState
TVar CIDDB
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
OutputQLim
MigrationQ
OutputQ
CryptoQ
InputQ
VersionInfo
RecvQ
SizedBuffer
ConnState
Parameters
LDCC
Hooks
Shared
Send
DebugLogger
QLogger
connState :: Connection -> ConnState
connDebugLog :: Connection -> DebugLogger
connQLog :: Connection -> QLogger
connHooks :: Connection -> Hooks
connSend :: Connection -> Send
connRecv :: Connection -> Recv
connRecvQ :: Connection -> RecvQ
connSocket :: Connection -> IORef Socket
readers :: Connection -> IORef (Map Word64 (Weak ThreadId))
mainThreadId :: Connection -> ThreadId
controlRate :: Connection -> Rate
roleInfo :: Connection -> IORef RoleInfo
quicVersionInfo :: Connection -> IORef VersionInfo
origVersionInfo :: Connection -> VersionInfo
myParameters :: Connection -> Parameters
myCIDDB :: Connection -> IORef CIDDB
peerParameters :: Connection -> IORef Parameters
peerCIDDB :: Connection -> TVar CIDDB
peerInfo :: Connection -> IORef PeerInfo
inputQ :: Connection -> InputQ
cryptoQ :: Connection -> CryptoQ
outputQ :: Connection -> OutputQ
outputQLim :: Connection -> OutputQLim
migrationQ :: Connection -> MigrationQ
shared :: Connection -> Shared
delayedAckCount :: Connection -> IORef Int
delayedAckCancel :: Connection -> IORef (IO ())
peerPacketNumber :: Connection -> IORef Int
streamTable :: Connection -> IORef StreamTable
myStreamId :: Connection -> TVar Concurrency
myUniStreamId :: Connection -> TVar Concurrency
peerStreamId :: Connection -> IORef Concurrency
peerUniStreamId :: Connection -> IORef Concurrency
flowTx :: Connection -> TVar TxFlow
flowRx :: Connection -> IORef RxFlow
migrationState :: Connection -> TVar MigrationState
minIdleTimeout :: Connection -> IORef Microseconds
bytesTx :: Connection -> TVar Int
bytesRx :: Connection -> TVar Int
addressValidated :: Connection -> TVar Bool
pendingQ :: Connection -> Array EncryptionLevel (TVar [ReceivedPacket])
ciphers :: Connection -> IOArray EncryptionLevel Cipher
coders :: Connection -> IOArray EncryptionLevel Coder
coders1RTT :: Connection -> IOArray Bool Coder1RTT
protectors :: Connection -> IOArray EncryptionLevel Protector
currentKeyPhase :: Connection -> IORef (Bool, Int)
negotiated :: Connection -> IORef Negotiated
connMyAuthCIDs :: Connection -> IORef AuthCIDs
connPeerAuthCIDs :: Connection -> IORef AuthCIDs
connResources :: Connection -> IORef (IO ())
encodeBuf :: Connection -> Buffer
encryptRes :: Connection -> SizedBuffer
decryptBuf :: Connection -> Buffer
connLDCC :: Connection -> LDCC
connState :: ConnState
connDebugLog :: DebugLogger
connQLog :: QLogger
connHooks :: Hooks
connSend :: Send
connRecv :: Recv
connRecvQ :: RecvQ
connSocket :: IORef Socket
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
outputQLim :: OutputQLim
migrationQ :: MigrationQ
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
minIdleTimeout :: IORef Microseconds
bytesTx :: TVar Int
bytesRx :: TVar Int
addressValidated :: TVar Bool
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
connResources :: IORef (IO ())
encodeBuf :: Buffer
encryptRes :: SizedBuffer
decryptBuf :: Buffer
connLDCC :: LDCC
..} = STM () -> IO ()
forall a. STM a -> IO a
atomically (STM () -> IO ()) -> STM () -> IO ()
forall a b. (a -> b) -> a -> b
$ do
ConnectionState
cs <- TVar ConnectionState -> STM ConnectionState
forall a. TVar a -> STM a
readTVar (TVar ConnectionState -> STM ConnectionState)
-> TVar ConnectionState -> STM ConnectionState
forall a b. (a -> b) -> a -> b
$ ConnState -> TVar ConnectionState
connectionState ConnState
connState
Bool -> STM ()
check (ConnectionState
cs ConnectionState -> ConnectionState -> Bool
forall a. Ord a => a -> a -> Bool
>= ConnectionState
ReadyFor1RTT)
waitEstablished :: Connection -> IO ()
waitEstablished :: Connection -> IO ()
waitEstablished Connection{Recv
Buffer
Array EncryptionLevel (TVar [ReceivedPacket])
IOArray Bool Coder1RTT
IOArray EncryptionLevel Cipher
IOArray EncryptionLevel Protector
IOArray EncryptionLevel Coder
ThreadId
TVar Bool
TVar Int
TVar TxFlow
TVar Concurrency
TVar MigrationState
TVar CIDDB
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
OutputQLim
MigrationQ
OutputQ
CryptoQ
InputQ
VersionInfo
RecvQ
SizedBuffer
ConnState
Parameters
LDCC
Hooks
Shared
Send
DebugLogger
QLogger
connState :: Connection -> ConnState
connDebugLog :: Connection -> DebugLogger
connQLog :: Connection -> QLogger
connHooks :: Connection -> Hooks
connSend :: Connection -> Send
connRecv :: Connection -> Recv
connRecvQ :: Connection -> RecvQ
connSocket :: Connection -> IORef Socket
readers :: Connection -> IORef (Map Word64 (Weak ThreadId))
mainThreadId :: Connection -> ThreadId
controlRate :: Connection -> Rate
roleInfo :: Connection -> IORef RoleInfo
quicVersionInfo :: Connection -> IORef VersionInfo
origVersionInfo :: Connection -> VersionInfo
myParameters :: Connection -> Parameters
myCIDDB :: Connection -> IORef CIDDB
peerParameters :: Connection -> IORef Parameters
peerCIDDB :: Connection -> TVar CIDDB
peerInfo :: Connection -> IORef PeerInfo
inputQ :: Connection -> InputQ
cryptoQ :: Connection -> CryptoQ
outputQ :: Connection -> OutputQ
outputQLim :: Connection -> OutputQLim
migrationQ :: Connection -> MigrationQ
shared :: Connection -> Shared
delayedAckCount :: Connection -> IORef Int
delayedAckCancel :: Connection -> IORef (IO ())
peerPacketNumber :: Connection -> IORef Int
streamTable :: Connection -> IORef StreamTable
myStreamId :: Connection -> TVar Concurrency
myUniStreamId :: Connection -> TVar Concurrency
peerStreamId :: Connection -> IORef Concurrency
peerUniStreamId :: Connection -> IORef Concurrency
flowTx :: Connection -> TVar TxFlow
flowRx :: Connection -> IORef RxFlow
migrationState :: Connection -> TVar MigrationState
minIdleTimeout :: Connection -> IORef Microseconds
bytesTx :: Connection -> TVar Int
bytesRx :: Connection -> TVar Int
addressValidated :: Connection -> TVar Bool
pendingQ :: Connection -> Array EncryptionLevel (TVar [ReceivedPacket])
ciphers :: Connection -> IOArray EncryptionLevel Cipher
coders :: Connection -> IOArray EncryptionLevel Coder
coders1RTT :: Connection -> IOArray Bool Coder1RTT
protectors :: Connection -> IOArray EncryptionLevel Protector
currentKeyPhase :: Connection -> IORef (Bool, Int)
negotiated :: Connection -> IORef Negotiated
connMyAuthCIDs :: Connection -> IORef AuthCIDs
connPeerAuthCIDs :: Connection -> IORef AuthCIDs
connResources :: Connection -> IORef (IO ())
encodeBuf :: Connection -> Buffer
encryptRes :: Connection -> SizedBuffer
decryptBuf :: Connection -> Buffer
connLDCC :: Connection -> LDCC
connState :: ConnState
connDebugLog :: DebugLogger
connQLog :: QLogger
connHooks :: Hooks
connSend :: Send
connRecv :: Recv
connRecvQ :: RecvQ
connSocket :: IORef Socket
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
outputQLim :: OutputQLim
migrationQ :: MigrationQ
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
minIdleTimeout :: IORef Microseconds
bytesTx :: TVar Int
bytesRx :: TVar Int
addressValidated :: TVar Bool
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
connResources :: IORef (IO ())
encodeBuf :: Buffer
encryptRes :: SizedBuffer
decryptBuf :: Buffer
connLDCC :: LDCC
..} = STM () -> IO ()
forall a. STM a -> IO a
atomically (STM () -> IO ()) -> STM () -> IO ()
forall a b. (a -> b) -> a -> b
$ do
ConnectionState
cs <- TVar ConnectionState -> STM ConnectionState
forall a. TVar a -> STM a
readTVar (TVar ConnectionState -> STM ConnectionState)
-> TVar ConnectionState -> STM ConnectionState
forall a b. (a -> b) -> a -> b
$ ConnState -> TVar ConnectionState
connectionState ConnState
connState
Bool -> STM ()
check (ConnectionState
cs ConnectionState -> ConnectionState -> Bool
forall a. Ord a => a -> a -> Bool
>= ConnectionState
Established)
readConnectionFlowTx :: Connection -> STM TxFlow
readConnectionFlowTx :: Connection -> STM TxFlow
readConnectionFlowTx Connection{Recv
Buffer
Array EncryptionLevel (TVar [ReceivedPacket])
IOArray Bool Coder1RTT
IOArray EncryptionLevel Cipher
IOArray EncryptionLevel Protector
IOArray EncryptionLevel Coder
ThreadId
TVar Bool
TVar Int
TVar TxFlow
TVar Concurrency
TVar MigrationState
TVar CIDDB
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
OutputQLim
MigrationQ
OutputQ
CryptoQ
InputQ
VersionInfo
RecvQ
SizedBuffer
ConnState
Parameters
LDCC
Hooks
Shared
Send
DebugLogger
QLogger
connState :: Connection -> ConnState
connDebugLog :: Connection -> DebugLogger
connQLog :: Connection -> QLogger
connHooks :: Connection -> Hooks
connSend :: Connection -> Send
connRecv :: Connection -> Recv
connRecvQ :: Connection -> RecvQ
connSocket :: Connection -> IORef Socket
readers :: Connection -> IORef (Map Word64 (Weak ThreadId))
mainThreadId :: Connection -> ThreadId
controlRate :: Connection -> Rate
roleInfo :: Connection -> IORef RoleInfo
quicVersionInfo :: Connection -> IORef VersionInfo
origVersionInfo :: Connection -> VersionInfo
myParameters :: Connection -> Parameters
myCIDDB :: Connection -> IORef CIDDB
peerParameters :: Connection -> IORef Parameters
peerCIDDB :: Connection -> TVar CIDDB
peerInfo :: Connection -> IORef PeerInfo
inputQ :: Connection -> InputQ
cryptoQ :: Connection -> CryptoQ
outputQ :: Connection -> OutputQ
outputQLim :: Connection -> OutputQLim
migrationQ :: Connection -> MigrationQ
shared :: Connection -> Shared
delayedAckCount :: Connection -> IORef Int
delayedAckCancel :: Connection -> IORef (IO ())
peerPacketNumber :: Connection -> IORef Int
streamTable :: Connection -> IORef StreamTable
myStreamId :: Connection -> TVar Concurrency
myUniStreamId :: Connection -> TVar Concurrency
peerStreamId :: Connection -> IORef Concurrency
peerUniStreamId :: Connection -> IORef Concurrency
flowTx :: Connection -> TVar TxFlow
flowRx :: Connection -> IORef RxFlow
migrationState :: Connection -> TVar MigrationState
minIdleTimeout :: Connection -> IORef Microseconds
bytesTx :: Connection -> TVar Int
bytesRx :: Connection -> TVar Int
addressValidated :: Connection -> TVar Bool
pendingQ :: Connection -> Array EncryptionLevel (TVar [ReceivedPacket])
ciphers :: Connection -> IOArray EncryptionLevel Cipher
coders :: Connection -> IOArray EncryptionLevel Coder
coders1RTT :: Connection -> IOArray Bool Coder1RTT
protectors :: Connection -> IOArray EncryptionLevel Protector
currentKeyPhase :: Connection -> IORef (Bool, Int)
negotiated :: Connection -> IORef Negotiated
connMyAuthCIDs :: Connection -> IORef AuthCIDs
connPeerAuthCIDs :: Connection -> IORef AuthCIDs
connResources :: Connection -> IORef (IO ())
encodeBuf :: Connection -> Buffer
encryptRes :: Connection -> SizedBuffer
decryptBuf :: Connection -> Buffer
connLDCC :: Connection -> LDCC
connState :: ConnState
connDebugLog :: DebugLogger
connQLog :: QLogger
connHooks :: Hooks
connSend :: Send
connRecv :: Recv
connRecvQ :: RecvQ
connSocket :: IORef Socket
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
outputQLim :: OutputQLim
migrationQ :: MigrationQ
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
minIdleTimeout :: IORef Microseconds
bytesTx :: TVar Int
bytesRx :: TVar Int
addressValidated :: TVar Bool
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
connResources :: IORef (IO ())
encodeBuf :: Buffer
encryptRes :: SizedBuffer
decryptBuf :: Buffer
connLDCC :: LDCC
..} = TVar TxFlow -> STM TxFlow
forall a. TVar a -> STM a
readTVar TVar TxFlow
flowTx
addTxData :: Connection -> Int -> STM ()
addTxData :: Connection -> Int -> STM ()
addTxData Connection{Recv
Buffer
Array EncryptionLevel (TVar [ReceivedPacket])
IOArray Bool Coder1RTT
IOArray EncryptionLevel Cipher
IOArray EncryptionLevel Protector
IOArray EncryptionLevel Coder
ThreadId
TVar Bool
TVar Int
TVar TxFlow
TVar Concurrency
TVar MigrationState
TVar CIDDB
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
OutputQLim
MigrationQ
OutputQ
CryptoQ
InputQ
VersionInfo
RecvQ
SizedBuffer
ConnState
Parameters
LDCC
Hooks
Shared
Send
DebugLogger
QLogger
connState :: Connection -> ConnState
connDebugLog :: Connection -> DebugLogger
connQLog :: Connection -> QLogger
connHooks :: Connection -> Hooks
connSend :: Connection -> Send
connRecv :: Connection -> Recv
connRecvQ :: Connection -> RecvQ
connSocket :: Connection -> IORef Socket
readers :: Connection -> IORef (Map Word64 (Weak ThreadId))
mainThreadId :: Connection -> ThreadId
controlRate :: Connection -> Rate
roleInfo :: Connection -> IORef RoleInfo
quicVersionInfo :: Connection -> IORef VersionInfo
origVersionInfo :: Connection -> VersionInfo
myParameters :: Connection -> Parameters
myCIDDB :: Connection -> IORef CIDDB
peerParameters :: Connection -> IORef Parameters
peerCIDDB :: Connection -> TVar CIDDB
peerInfo :: Connection -> IORef PeerInfo
inputQ :: Connection -> InputQ
cryptoQ :: Connection -> CryptoQ
outputQ :: Connection -> OutputQ
outputQLim :: Connection -> OutputQLim
migrationQ :: Connection -> MigrationQ
shared :: Connection -> Shared
delayedAckCount :: Connection -> IORef Int
delayedAckCancel :: Connection -> IORef (IO ())
peerPacketNumber :: Connection -> IORef Int
streamTable :: Connection -> IORef StreamTable
myStreamId :: Connection -> TVar Concurrency
myUniStreamId :: Connection -> TVar Concurrency
peerStreamId :: Connection -> IORef Concurrency
peerUniStreamId :: Connection -> IORef Concurrency
flowTx :: Connection -> TVar TxFlow
flowRx :: Connection -> IORef RxFlow
migrationState :: Connection -> TVar MigrationState
minIdleTimeout :: Connection -> IORef Microseconds
bytesTx :: Connection -> TVar Int
bytesRx :: Connection -> TVar Int
addressValidated :: Connection -> TVar Bool
pendingQ :: Connection -> Array EncryptionLevel (TVar [ReceivedPacket])
ciphers :: Connection -> IOArray EncryptionLevel Cipher
coders :: Connection -> IOArray EncryptionLevel Coder
coders1RTT :: Connection -> IOArray Bool Coder1RTT
protectors :: Connection -> IOArray EncryptionLevel Protector
currentKeyPhase :: Connection -> IORef (Bool, Int)
negotiated :: Connection -> IORef Negotiated
connMyAuthCIDs :: Connection -> IORef AuthCIDs
connPeerAuthCIDs :: Connection -> IORef AuthCIDs
connResources :: Connection -> IORef (IO ())
encodeBuf :: Connection -> Buffer
encryptRes :: Connection -> SizedBuffer
decryptBuf :: Connection -> Buffer
connLDCC :: Connection -> LDCC
connState :: ConnState
connDebugLog :: DebugLogger
connQLog :: QLogger
connHooks :: Hooks
connSend :: Send
connRecv :: Recv
connRecvQ :: RecvQ
connSocket :: IORef Socket
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
outputQLim :: OutputQLim
migrationQ :: MigrationQ
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
minIdleTimeout :: IORef Microseconds
bytesTx :: TVar Int
bytesRx :: TVar Int
addressValidated :: TVar Bool
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
connResources :: IORef (IO ())
encodeBuf :: Buffer
encryptRes :: SizedBuffer
decryptBuf :: Buffer
connLDCC :: LDCC
..} Int
n = TVar TxFlow -> (TxFlow -> TxFlow) -> STM ()
forall a. TVar a -> (a -> a) -> STM ()
modifyTVar' TVar TxFlow
flowTx TxFlow -> TxFlow
add
where
add :: TxFlow -> TxFlow
add TxFlow
flow = TxFlow
flow{txfSent = txfSent flow + n}
setTxMaxData :: Connection -> Int -> IO ()
setTxMaxData :: Connection -> Int -> IO ()
setTxMaxData Connection{Recv
Buffer
Array EncryptionLevel (TVar [ReceivedPacket])
IOArray Bool Coder1RTT
IOArray EncryptionLevel Cipher
IOArray EncryptionLevel Protector
IOArray EncryptionLevel Coder
ThreadId
TVar Bool
TVar Int
TVar TxFlow
TVar Concurrency
TVar MigrationState
TVar CIDDB
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
OutputQLim
MigrationQ
OutputQ
CryptoQ
InputQ
VersionInfo
RecvQ
SizedBuffer
ConnState
Parameters
LDCC
Hooks
Shared
Send
DebugLogger
QLogger
connState :: Connection -> ConnState
connDebugLog :: Connection -> DebugLogger
connQLog :: Connection -> QLogger
connHooks :: Connection -> Hooks
connSend :: Connection -> Send
connRecv :: Connection -> Recv
connRecvQ :: Connection -> RecvQ
connSocket :: Connection -> IORef Socket
readers :: Connection -> IORef (Map Word64 (Weak ThreadId))
mainThreadId :: Connection -> ThreadId
controlRate :: Connection -> Rate
roleInfo :: Connection -> IORef RoleInfo
quicVersionInfo :: Connection -> IORef VersionInfo
origVersionInfo :: Connection -> VersionInfo
myParameters :: Connection -> Parameters
myCIDDB :: Connection -> IORef CIDDB
peerParameters :: Connection -> IORef Parameters
peerCIDDB :: Connection -> TVar CIDDB
peerInfo :: Connection -> IORef PeerInfo
inputQ :: Connection -> InputQ
cryptoQ :: Connection -> CryptoQ
outputQ :: Connection -> OutputQ
outputQLim :: Connection -> OutputQLim
migrationQ :: Connection -> MigrationQ
shared :: Connection -> Shared
delayedAckCount :: Connection -> IORef Int
delayedAckCancel :: Connection -> IORef (IO ())
peerPacketNumber :: Connection -> IORef Int
streamTable :: Connection -> IORef StreamTable
myStreamId :: Connection -> TVar Concurrency
myUniStreamId :: Connection -> TVar Concurrency
peerStreamId :: Connection -> IORef Concurrency
peerUniStreamId :: Connection -> IORef Concurrency
flowTx :: Connection -> TVar TxFlow
flowRx :: Connection -> IORef RxFlow
migrationState :: Connection -> TVar MigrationState
minIdleTimeout :: Connection -> IORef Microseconds
bytesTx :: Connection -> TVar Int
bytesRx :: Connection -> TVar Int
addressValidated :: Connection -> TVar Bool
pendingQ :: Connection -> Array EncryptionLevel (TVar [ReceivedPacket])
ciphers :: Connection -> IOArray EncryptionLevel Cipher
coders :: Connection -> IOArray EncryptionLevel Coder
coders1RTT :: Connection -> IOArray Bool Coder1RTT
protectors :: Connection -> IOArray EncryptionLevel Protector
currentKeyPhase :: Connection -> IORef (Bool, Int)
negotiated :: Connection -> IORef Negotiated
connMyAuthCIDs :: Connection -> IORef AuthCIDs
connPeerAuthCIDs :: Connection -> IORef AuthCIDs
connResources :: Connection -> IORef (IO ())
encodeBuf :: Connection -> Buffer
encryptRes :: Connection -> SizedBuffer
decryptBuf :: Connection -> Buffer
connLDCC :: Connection -> LDCC
connState :: ConnState
connDebugLog :: DebugLogger
connQLog :: QLogger
connHooks :: Hooks
connSend :: Send
connRecv :: Recv
connRecvQ :: RecvQ
connSocket :: IORef Socket
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
outputQLim :: OutputQLim
migrationQ :: MigrationQ
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
minIdleTimeout :: IORef Microseconds
bytesTx :: TVar Int
bytesRx :: TVar Int
addressValidated :: TVar Bool
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
connResources :: IORef (IO ())
encodeBuf :: Buffer
encryptRes :: SizedBuffer
decryptBuf :: Buffer
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 TxFlow -> (TxFlow -> TxFlow) -> STM ()
forall a. TVar a -> (a -> a) -> STM ()
modifyTVar' TVar TxFlow
flowTx TxFlow -> TxFlow
set
where
set :: TxFlow -> TxFlow
set TxFlow
flow
| TxFlow -> Int
txfLimit TxFlow
flow Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Int
n = TxFlow
flow{txfLimit = n}
| Bool
otherwise = TxFlow
flow
getRxMaxData :: Connection -> IO Int
getRxMaxData :: Connection -> IO Int
getRxMaxData Connection{Recv
Buffer
Array EncryptionLevel (TVar [ReceivedPacket])
IOArray Bool Coder1RTT
IOArray EncryptionLevel Cipher
IOArray EncryptionLevel Protector
IOArray EncryptionLevel Coder
ThreadId
TVar Bool
TVar Int
TVar TxFlow
TVar Concurrency
TVar MigrationState
TVar CIDDB
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
OutputQLim
MigrationQ
OutputQ
CryptoQ
InputQ
VersionInfo
RecvQ
SizedBuffer
ConnState
Parameters
LDCC
Hooks
Shared
Send
DebugLogger
QLogger
connState :: Connection -> ConnState
connDebugLog :: Connection -> DebugLogger
connQLog :: Connection -> QLogger
connHooks :: Connection -> Hooks
connSend :: Connection -> Send
connRecv :: Connection -> Recv
connRecvQ :: Connection -> RecvQ
connSocket :: Connection -> IORef Socket
readers :: Connection -> IORef (Map Word64 (Weak ThreadId))
mainThreadId :: Connection -> ThreadId
controlRate :: Connection -> Rate
roleInfo :: Connection -> IORef RoleInfo
quicVersionInfo :: Connection -> IORef VersionInfo
origVersionInfo :: Connection -> VersionInfo
myParameters :: Connection -> Parameters
myCIDDB :: Connection -> IORef CIDDB
peerParameters :: Connection -> IORef Parameters
peerCIDDB :: Connection -> TVar CIDDB
peerInfo :: Connection -> IORef PeerInfo
inputQ :: Connection -> InputQ
cryptoQ :: Connection -> CryptoQ
outputQ :: Connection -> OutputQ
outputQLim :: Connection -> OutputQLim
migrationQ :: Connection -> MigrationQ
shared :: Connection -> Shared
delayedAckCount :: Connection -> IORef Int
delayedAckCancel :: Connection -> IORef (IO ())
peerPacketNumber :: Connection -> IORef Int
streamTable :: Connection -> IORef StreamTable
myStreamId :: Connection -> TVar Concurrency
myUniStreamId :: Connection -> TVar Concurrency
peerStreamId :: Connection -> IORef Concurrency
peerUniStreamId :: Connection -> IORef Concurrency
flowTx :: Connection -> TVar TxFlow
flowRx :: Connection -> IORef RxFlow
migrationState :: Connection -> TVar MigrationState
minIdleTimeout :: Connection -> IORef Microseconds
bytesTx :: Connection -> TVar Int
bytesRx :: Connection -> TVar Int
addressValidated :: Connection -> TVar Bool
pendingQ :: Connection -> Array EncryptionLevel (TVar [ReceivedPacket])
ciphers :: Connection -> IOArray EncryptionLevel Cipher
coders :: Connection -> IOArray EncryptionLevel Coder
coders1RTT :: Connection -> IOArray Bool Coder1RTT
protectors :: Connection -> IOArray EncryptionLevel Protector
currentKeyPhase :: Connection -> IORef (Bool, Int)
negotiated :: Connection -> IORef Negotiated
connMyAuthCIDs :: Connection -> IORef AuthCIDs
connPeerAuthCIDs :: Connection -> IORef AuthCIDs
connResources :: Connection -> IORef (IO ())
encodeBuf :: Connection -> Buffer
encryptRes :: Connection -> SizedBuffer
decryptBuf :: Connection -> Buffer
connLDCC :: Connection -> LDCC
connState :: ConnState
connDebugLog :: DebugLogger
connQLog :: QLogger
connHooks :: Hooks
connSend :: Send
connRecv :: Recv
connRecvQ :: RecvQ
connSocket :: IORef Socket
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
outputQLim :: OutputQLim
migrationQ :: MigrationQ
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
minIdleTimeout :: IORef Microseconds
bytesTx :: TVar Int
bytesRx :: TVar Int
addressValidated :: TVar Bool
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
connResources :: IORef (IO ())
encodeBuf :: Buffer
encryptRes :: SizedBuffer
decryptBuf :: Buffer
connLDCC :: LDCC
..} = RxFlow -> Int
rxfLimit (RxFlow -> Int) -> IO RxFlow -> IO Int
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> IORef RxFlow -> IO RxFlow
forall a. IORef a -> IO a
readIORef IORef RxFlow
flowRx
updateFlowRx :: Connection -> Int -> IO (Maybe Int)
updateFlowRx :: Connection -> Int -> IO (Maybe Int)
updateFlowRx Connection{Recv
Buffer
Array EncryptionLevel (TVar [ReceivedPacket])
IOArray Bool Coder1RTT
IOArray EncryptionLevel Cipher
IOArray EncryptionLevel Protector
IOArray EncryptionLevel Coder
ThreadId
TVar Bool
TVar Int
TVar TxFlow
TVar Concurrency
TVar MigrationState
TVar CIDDB
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
OutputQLim
MigrationQ
OutputQ
CryptoQ
InputQ
VersionInfo
RecvQ
SizedBuffer
ConnState
Parameters
LDCC
Hooks
Shared
Send
DebugLogger
QLogger
connState :: Connection -> ConnState
connDebugLog :: Connection -> DebugLogger
connQLog :: Connection -> QLogger
connHooks :: Connection -> Hooks
connSend :: Connection -> Send
connRecv :: Connection -> Recv
connRecvQ :: Connection -> RecvQ
connSocket :: Connection -> IORef Socket
readers :: Connection -> IORef (Map Word64 (Weak ThreadId))
mainThreadId :: Connection -> ThreadId
controlRate :: Connection -> Rate
roleInfo :: Connection -> IORef RoleInfo
quicVersionInfo :: Connection -> IORef VersionInfo
origVersionInfo :: Connection -> VersionInfo
myParameters :: Connection -> Parameters
myCIDDB :: Connection -> IORef CIDDB
peerParameters :: Connection -> IORef Parameters
peerCIDDB :: Connection -> TVar CIDDB
peerInfo :: Connection -> IORef PeerInfo
inputQ :: Connection -> InputQ
cryptoQ :: Connection -> CryptoQ
outputQ :: Connection -> OutputQ
outputQLim :: Connection -> OutputQLim
migrationQ :: Connection -> MigrationQ
shared :: Connection -> Shared
delayedAckCount :: Connection -> IORef Int
delayedAckCancel :: Connection -> IORef (IO ())
peerPacketNumber :: Connection -> IORef Int
streamTable :: Connection -> IORef StreamTable
myStreamId :: Connection -> TVar Concurrency
myUniStreamId :: Connection -> TVar Concurrency
peerStreamId :: Connection -> IORef Concurrency
peerUniStreamId :: Connection -> IORef Concurrency
flowTx :: Connection -> TVar TxFlow
flowRx :: Connection -> IORef RxFlow
migrationState :: Connection -> TVar MigrationState
minIdleTimeout :: Connection -> IORef Microseconds
bytesTx :: Connection -> TVar Int
bytesRx :: Connection -> TVar Int
addressValidated :: Connection -> TVar Bool
pendingQ :: Connection -> Array EncryptionLevel (TVar [ReceivedPacket])
ciphers :: Connection -> IOArray EncryptionLevel Cipher
coders :: Connection -> IOArray EncryptionLevel Coder
coders1RTT :: Connection -> IOArray Bool Coder1RTT
protectors :: Connection -> IOArray EncryptionLevel Protector
currentKeyPhase :: Connection -> IORef (Bool, Int)
negotiated :: Connection -> IORef Negotiated
connMyAuthCIDs :: Connection -> IORef AuthCIDs
connPeerAuthCIDs :: Connection -> IORef AuthCIDs
connResources :: Connection -> IORef (IO ())
encodeBuf :: Connection -> Buffer
encryptRes :: Connection -> SizedBuffer
decryptBuf :: Connection -> Buffer
connLDCC :: Connection -> LDCC
connState :: ConnState
connDebugLog :: DebugLogger
connQLog :: QLogger
connHooks :: Hooks
connSend :: Send
connRecv :: Recv
connRecvQ :: RecvQ
connSocket :: IORef Socket
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
outputQLim :: OutputQLim
migrationQ :: MigrationQ
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
minIdleTimeout :: IORef Microseconds
bytesTx :: TVar Int
bytesRx :: TVar Int
addressValidated :: TVar Bool
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
connResources :: IORef (IO ())
encodeBuf :: Buffer
encryptRes :: SizedBuffer
decryptBuf :: Buffer
connLDCC :: LDCC
..} Int
consumed =
IORef RxFlow -> (RxFlow -> (RxFlow, Maybe Int)) -> IO (Maybe Int)
forall a b. IORef a -> (a -> (a, b)) -> IO b
atomicModifyIORef' IORef RxFlow
flowRx ((RxFlow -> (RxFlow, Maybe Int)) -> IO (Maybe Int))
-> (RxFlow -> (RxFlow, Maybe Int)) -> IO (Maybe Int)
forall a b. (a -> b) -> a -> b
$ Int -> FlowControlType -> RxFlow -> (RxFlow, Maybe Int)
maybeOpenRxWindow Int
consumed FlowControlType
FCTMaxData
checkRxMaxData :: Connection -> Int -> IO Bool
checkRxMaxData :: Connection -> Int -> IO Bool
checkRxMaxData Connection{Recv
Buffer
Array EncryptionLevel (TVar [ReceivedPacket])
IOArray Bool Coder1RTT
IOArray EncryptionLevel Cipher
IOArray EncryptionLevel Protector
IOArray EncryptionLevel Coder
ThreadId
TVar Bool
TVar Int
TVar TxFlow
TVar Concurrency
TVar MigrationState
TVar CIDDB
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
OutputQLim
MigrationQ
OutputQ
CryptoQ
InputQ
VersionInfo
RecvQ
SizedBuffer
ConnState
Parameters
LDCC
Hooks
Shared
Send
DebugLogger
QLogger
connState :: Connection -> ConnState
connDebugLog :: Connection -> DebugLogger
connQLog :: Connection -> QLogger
connHooks :: Connection -> Hooks
connSend :: Connection -> Send
connRecv :: Connection -> Recv
connRecvQ :: Connection -> RecvQ
connSocket :: Connection -> IORef Socket
readers :: Connection -> IORef (Map Word64 (Weak ThreadId))
mainThreadId :: Connection -> ThreadId
controlRate :: Connection -> Rate
roleInfo :: Connection -> IORef RoleInfo
quicVersionInfo :: Connection -> IORef VersionInfo
origVersionInfo :: Connection -> VersionInfo
myParameters :: Connection -> Parameters
myCIDDB :: Connection -> IORef CIDDB
peerParameters :: Connection -> IORef Parameters
peerCIDDB :: Connection -> TVar CIDDB
peerInfo :: Connection -> IORef PeerInfo
inputQ :: Connection -> InputQ
cryptoQ :: Connection -> CryptoQ
outputQ :: Connection -> OutputQ
outputQLim :: Connection -> OutputQLim
migrationQ :: Connection -> MigrationQ
shared :: Connection -> Shared
delayedAckCount :: Connection -> IORef Int
delayedAckCancel :: Connection -> IORef (IO ())
peerPacketNumber :: Connection -> IORef Int
streamTable :: Connection -> IORef StreamTable
myStreamId :: Connection -> TVar Concurrency
myUniStreamId :: Connection -> TVar Concurrency
peerStreamId :: Connection -> IORef Concurrency
peerUniStreamId :: Connection -> IORef Concurrency
flowTx :: Connection -> TVar TxFlow
flowRx :: Connection -> IORef RxFlow
migrationState :: Connection -> TVar MigrationState
minIdleTimeout :: Connection -> IORef Microseconds
bytesTx :: Connection -> TVar Int
bytesRx :: Connection -> TVar Int
addressValidated :: Connection -> TVar Bool
pendingQ :: Connection -> Array EncryptionLevel (TVar [ReceivedPacket])
ciphers :: Connection -> IOArray EncryptionLevel Cipher
coders :: Connection -> IOArray EncryptionLevel Coder
coders1RTT :: Connection -> IOArray Bool Coder1RTT
protectors :: Connection -> IOArray EncryptionLevel Protector
currentKeyPhase :: Connection -> IORef (Bool, Int)
negotiated :: Connection -> IORef Negotiated
connMyAuthCIDs :: Connection -> IORef AuthCIDs
connPeerAuthCIDs :: Connection -> IORef AuthCIDs
connResources :: Connection -> IORef (IO ())
encodeBuf :: Connection -> Buffer
encryptRes :: Connection -> SizedBuffer
decryptBuf :: Connection -> Buffer
connLDCC :: Connection -> LDCC
connState :: ConnState
connDebugLog :: DebugLogger
connQLog :: QLogger
connHooks :: Hooks
connSend :: Send
connRecv :: Recv
connRecvQ :: RecvQ
connSocket :: IORef Socket
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
outputQLim :: OutputQLim
migrationQ :: MigrationQ
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
minIdleTimeout :: IORef Microseconds
bytesTx :: TVar Int
bytesRx :: TVar Int
addressValidated :: TVar Bool
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
connResources :: IORef (IO ())
encodeBuf :: Buffer
encryptRes :: SizedBuffer
decryptBuf :: Buffer
connLDCC :: LDCC
..} Int
len =
IORef RxFlow -> (RxFlow -> (RxFlow, Bool)) -> IO Bool
forall a b. IORef a -> (a -> (a, b)) -> IO b
atomicModifyIORef' IORef RxFlow
flowRx ((RxFlow -> (RxFlow, Bool)) -> IO Bool)
-> (RxFlow -> (RxFlow, Bool)) -> IO Bool
forall a b. (a -> b) -> a -> b
$ Int -> RxFlow -> (RxFlow, Bool)
checkRxLimit Int
len
addTxBytes :: Connection -> Int -> IO ()
addTxBytes :: Connection -> Int -> IO ()
addTxBytes Connection{Recv
Buffer
Array EncryptionLevel (TVar [ReceivedPacket])
IOArray Bool Coder1RTT
IOArray EncryptionLevel Cipher
IOArray EncryptionLevel Protector
IOArray EncryptionLevel Coder
ThreadId
TVar Bool
TVar Int
TVar TxFlow
TVar Concurrency
TVar MigrationState
TVar CIDDB
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
OutputQLim
MigrationQ
OutputQ
CryptoQ
InputQ
VersionInfo
RecvQ
SizedBuffer
ConnState
Parameters
LDCC
Hooks
Shared
Send
DebugLogger
QLogger
connState :: Connection -> ConnState
connDebugLog :: Connection -> DebugLogger
connQLog :: Connection -> QLogger
connHooks :: Connection -> Hooks
connSend :: Connection -> Send
connRecv :: Connection -> Recv
connRecvQ :: Connection -> RecvQ
connSocket :: Connection -> IORef Socket
readers :: Connection -> IORef (Map Word64 (Weak ThreadId))
mainThreadId :: Connection -> ThreadId
controlRate :: Connection -> Rate
roleInfo :: Connection -> IORef RoleInfo
quicVersionInfo :: Connection -> IORef VersionInfo
origVersionInfo :: Connection -> VersionInfo
myParameters :: Connection -> Parameters
myCIDDB :: Connection -> IORef CIDDB
peerParameters :: Connection -> IORef Parameters
peerCIDDB :: Connection -> TVar CIDDB
peerInfo :: Connection -> IORef PeerInfo
inputQ :: Connection -> InputQ
cryptoQ :: Connection -> CryptoQ
outputQ :: Connection -> OutputQ
outputQLim :: Connection -> OutputQLim
migrationQ :: Connection -> MigrationQ
shared :: Connection -> Shared
delayedAckCount :: Connection -> IORef Int
delayedAckCancel :: Connection -> IORef (IO ())
peerPacketNumber :: Connection -> IORef Int
streamTable :: Connection -> IORef StreamTable
myStreamId :: Connection -> TVar Concurrency
myUniStreamId :: Connection -> TVar Concurrency
peerStreamId :: Connection -> IORef Concurrency
peerUniStreamId :: Connection -> IORef Concurrency
flowTx :: Connection -> TVar TxFlow
flowRx :: Connection -> IORef RxFlow
migrationState :: Connection -> TVar MigrationState
minIdleTimeout :: Connection -> IORef Microseconds
bytesTx :: Connection -> TVar Int
bytesRx :: Connection -> TVar Int
addressValidated :: Connection -> TVar Bool
pendingQ :: Connection -> Array EncryptionLevel (TVar [ReceivedPacket])
ciphers :: Connection -> IOArray EncryptionLevel Cipher
coders :: Connection -> IOArray EncryptionLevel Coder
coders1RTT :: Connection -> IOArray Bool Coder1RTT
protectors :: Connection -> IOArray EncryptionLevel Protector
currentKeyPhase :: Connection -> IORef (Bool, Int)
negotiated :: Connection -> IORef Negotiated
connMyAuthCIDs :: Connection -> IORef AuthCIDs
connPeerAuthCIDs :: Connection -> IORef AuthCIDs
connResources :: Connection -> IORef (IO ())
encodeBuf :: Connection -> Buffer
encryptRes :: Connection -> SizedBuffer
decryptBuf :: Connection -> Buffer
connLDCC :: Connection -> LDCC
connState :: ConnState
connDebugLog :: DebugLogger
connQLog :: QLogger
connHooks :: Hooks
connSend :: Send
connRecv :: Recv
connRecvQ :: RecvQ
connSocket :: IORef Socket
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
outputQLim :: OutputQLim
migrationQ :: MigrationQ
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
minIdleTimeout :: IORef Microseconds
bytesTx :: TVar Int
bytesRx :: TVar Int
addressValidated :: TVar Bool
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
connResources :: IORef (IO ())
encodeBuf :: Buffer
encryptRes :: SizedBuffer
decryptBuf :: Buffer
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 Int -> (Int -> Int) -> STM ()
forall a. TVar a -> (a -> a) -> STM ()
modifyTVar' TVar Int
bytesTx (Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
n)
getTxBytes :: Connection -> IO Int
getTxBytes :: Connection -> IO Int
getTxBytes Connection{Recv
Buffer
Array EncryptionLevel (TVar [ReceivedPacket])
IOArray Bool Coder1RTT
IOArray EncryptionLevel Cipher
IOArray EncryptionLevel Protector
IOArray EncryptionLevel Coder
ThreadId
TVar Bool
TVar Int
TVar TxFlow
TVar Concurrency
TVar MigrationState
TVar CIDDB
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
OutputQLim
MigrationQ
OutputQ
CryptoQ
InputQ
VersionInfo
RecvQ
SizedBuffer
ConnState
Parameters
LDCC
Hooks
Shared
Send
DebugLogger
QLogger
connState :: Connection -> ConnState
connDebugLog :: Connection -> DebugLogger
connQLog :: Connection -> QLogger
connHooks :: Connection -> Hooks
connSend :: Connection -> Send
connRecv :: Connection -> Recv
connRecvQ :: Connection -> RecvQ
connSocket :: Connection -> IORef Socket
readers :: Connection -> IORef (Map Word64 (Weak ThreadId))
mainThreadId :: Connection -> ThreadId
controlRate :: Connection -> Rate
roleInfo :: Connection -> IORef RoleInfo
quicVersionInfo :: Connection -> IORef VersionInfo
origVersionInfo :: Connection -> VersionInfo
myParameters :: Connection -> Parameters
myCIDDB :: Connection -> IORef CIDDB
peerParameters :: Connection -> IORef Parameters
peerCIDDB :: Connection -> TVar CIDDB
peerInfo :: Connection -> IORef PeerInfo
inputQ :: Connection -> InputQ
cryptoQ :: Connection -> CryptoQ
outputQ :: Connection -> OutputQ
outputQLim :: Connection -> OutputQLim
migrationQ :: Connection -> MigrationQ
shared :: Connection -> Shared
delayedAckCount :: Connection -> IORef Int
delayedAckCancel :: Connection -> IORef (IO ())
peerPacketNumber :: Connection -> IORef Int
streamTable :: Connection -> IORef StreamTable
myStreamId :: Connection -> TVar Concurrency
myUniStreamId :: Connection -> TVar Concurrency
peerStreamId :: Connection -> IORef Concurrency
peerUniStreamId :: Connection -> IORef Concurrency
flowTx :: Connection -> TVar TxFlow
flowRx :: Connection -> IORef RxFlow
migrationState :: Connection -> TVar MigrationState
minIdleTimeout :: Connection -> IORef Microseconds
bytesTx :: Connection -> TVar Int
bytesRx :: Connection -> TVar Int
addressValidated :: Connection -> TVar Bool
pendingQ :: Connection -> Array EncryptionLevel (TVar [ReceivedPacket])
ciphers :: Connection -> IOArray EncryptionLevel Cipher
coders :: Connection -> IOArray EncryptionLevel Coder
coders1RTT :: Connection -> IOArray Bool Coder1RTT
protectors :: Connection -> IOArray EncryptionLevel Protector
currentKeyPhase :: Connection -> IORef (Bool, Int)
negotiated :: Connection -> IORef Negotiated
connMyAuthCIDs :: Connection -> IORef AuthCIDs
connPeerAuthCIDs :: Connection -> IORef AuthCIDs
connResources :: Connection -> IORef (IO ())
encodeBuf :: Connection -> Buffer
encryptRes :: Connection -> SizedBuffer
decryptBuf :: Connection -> Buffer
connLDCC :: Connection -> LDCC
connState :: ConnState
connDebugLog :: DebugLogger
connQLog :: QLogger
connHooks :: Hooks
connSend :: Send
connRecv :: Recv
connRecvQ :: RecvQ
connSocket :: IORef Socket
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
outputQLim :: OutputQLim
migrationQ :: MigrationQ
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
minIdleTimeout :: IORef Microseconds
bytesTx :: TVar Int
bytesRx :: TVar Int
addressValidated :: TVar Bool
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
connResources :: IORef (IO ())
encodeBuf :: Buffer
encryptRes :: SizedBuffer
decryptBuf :: Buffer
connLDCC :: LDCC
..} = TVar Int -> IO Int
forall a. TVar a -> IO a
readTVarIO TVar Int
bytesTx
addRxBytes :: Connection -> Int -> IO ()
addRxBytes :: Connection -> Int -> IO ()
addRxBytes Connection{Recv
Buffer
Array EncryptionLevel (TVar [ReceivedPacket])
IOArray Bool Coder1RTT
IOArray EncryptionLevel Cipher
IOArray EncryptionLevel Protector
IOArray EncryptionLevel Coder
ThreadId
TVar Bool
TVar Int
TVar TxFlow
TVar Concurrency
TVar MigrationState
TVar CIDDB
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
OutputQLim
MigrationQ
OutputQ
CryptoQ
InputQ
VersionInfo
RecvQ
SizedBuffer
ConnState
Parameters
LDCC
Hooks
Shared
Send
DebugLogger
QLogger
connState :: Connection -> ConnState
connDebugLog :: Connection -> DebugLogger
connQLog :: Connection -> QLogger
connHooks :: Connection -> Hooks
connSend :: Connection -> Send
connRecv :: Connection -> Recv
connRecvQ :: Connection -> RecvQ
connSocket :: Connection -> IORef Socket
readers :: Connection -> IORef (Map Word64 (Weak ThreadId))
mainThreadId :: Connection -> ThreadId
controlRate :: Connection -> Rate
roleInfo :: Connection -> IORef RoleInfo
quicVersionInfo :: Connection -> IORef VersionInfo
origVersionInfo :: Connection -> VersionInfo
myParameters :: Connection -> Parameters
myCIDDB :: Connection -> IORef CIDDB
peerParameters :: Connection -> IORef Parameters
peerCIDDB :: Connection -> TVar CIDDB
peerInfo :: Connection -> IORef PeerInfo
inputQ :: Connection -> InputQ
cryptoQ :: Connection -> CryptoQ
outputQ :: Connection -> OutputQ
outputQLim :: Connection -> OutputQLim
migrationQ :: Connection -> MigrationQ
shared :: Connection -> Shared
delayedAckCount :: Connection -> IORef Int
delayedAckCancel :: Connection -> IORef (IO ())
peerPacketNumber :: Connection -> IORef Int
streamTable :: Connection -> IORef StreamTable
myStreamId :: Connection -> TVar Concurrency
myUniStreamId :: Connection -> TVar Concurrency
peerStreamId :: Connection -> IORef Concurrency
peerUniStreamId :: Connection -> IORef Concurrency
flowTx :: Connection -> TVar TxFlow
flowRx :: Connection -> IORef RxFlow
migrationState :: Connection -> TVar MigrationState
minIdleTimeout :: Connection -> IORef Microseconds
bytesTx :: Connection -> TVar Int
bytesRx :: Connection -> TVar Int
addressValidated :: Connection -> TVar Bool
pendingQ :: Connection -> Array EncryptionLevel (TVar [ReceivedPacket])
ciphers :: Connection -> IOArray EncryptionLevel Cipher
coders :: Connection -> IOArray EncryptionLevel Coder
coders1RTT :: Connection -> IOArray Bool Coder1RTT
protectors :: Connection -> IOArray EncryptionLevel Protector
currentKeyPhase :: Connection -> IORef (Bool, Int)
negotiated :: Connection -> IORef Negotiated
connMyAuthCIDs :: Connection -> IORef AuthCIDs
connPeerAuthCIDs :: Connection -> IORef AuthCIDs
connResources :: Connection -> IORef (IO ())
encodeBuf :: Connection -> Buffer
encryptRes :: Connection -> SizedBuffer
decryptBuf :: Connection -> Buffer
connLDCC :: Connection -> LDCC
connState :: ConnState
connDebugLog :: DebugLogger
connQLog :: QLogger
connHooks :: Hooks
connSend :: Send
connRecv :: Recv
connRecvQ :: RecvQ
connSocket :: IORef Socket
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
outputQLim :: OutputQLim
migrationQ :: MigrationQ
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
minIdleTimeout :: IORef Microseconds
bytesTx :: TVar Int
bytesRx :: TVar Int
addressValidated :: TVar Bool
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
connResources :: IORef (IO ())
encodeBuf :: Buffer
encryptRes :: SizedBuffer
decryptBuf :: Buffer
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 Int -> (Int -> Int) -> STM ()
forall a. TVar a -> (a -> a) -> STM ()
modifyTVar' TVar Int
bytesRx (Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
n)
getRxBytes :: Connection -> IO Int
getRxBytes :: Connection -> IO Int
getRxBytes Connection{Recv
Buffer
Array EncryptionLevel (TVar [ReceivedPacket])
IOArray Bool Coder1RTT
IOArray EncryptionLevel Cipher
IOArray EncryptionLevel Protector
IOArray EncryptionLevel Coder
ThreadId
TVar Bool
TVar Int
TVar TxFlow
TVar Concurrency
TVar MigrationState
TVar CIDDB
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
OutputQLim
MigrationQ
OutputQ
CryptoQ
InputQ
VersionInfo
RecvQ
SizedBuffer
ConnState
Parameters
LDCC
Hooks
Shared
Send
DebugLogger
QLogger
connState :: Connection -> ConnState
connDebugLog :: Connection -> DebugLogger
connQLog :: Connection -> QLogger
connHooks :: Connection -> Hooks
connSend :: Connection -> Send
connRecv :: Connection -> Recv
connRecvQ :: Connection -> RecvQ
connSocket :: Connection -> IORef Socket
readers :: Connection -> IORef (Map Word64 (Weak ThreadId))
mainThreadId :: Connection -> ThreadId
controlRate :: Connection -> Rate
roleInfo :: Connection -> IORef RoleInfo
quicVersionInfo :: Connection -> IORef VersionInfo
origVersionInfo :: Connection -> VersionInfo
myParameters :: Connection -> Parameters
myCIDDB :: Connection -> IORef CIDDB
peerParameters :: Connection -> IORef Parameters
peerCIDDB :: Connection -> TVar CIDDB
peerInfo :: Connection -> IORef PeerInfo
inputQ :: Connection -> InputQ
cryptoQ :: Connection -> CryptoQ
outputQ :: Connection -> OutputQ
outputQLim :: Connection -> OutputQLim
migrationQ :: Connection -> MigrationQ
shared :: Connection -> Shared
delayedAckCount :: Connection -> IORef Int
delayedAckCancel :: Connection -> IORef (IO ())
peerPacketNumber :: Connection -> IORef Int
streamTable :: Connection -> IORef StreamTable
myStreamId :: Connection -> TVar Concurrency
myUniStreamId :: Connection -> TVar Concurrency
peerStreamId :: Connection -> IORef Concurrency
peerUniStreamId :: Connection -> IORef Concurrency
flowTx :: Connection -> TVar TxFlow
flowRx :: Connection -> IORef RxFlow
migrationState :: Connection -> TVar MigrationState
minIdleTimeout :: Connection -> IORef Microseconds
bytesTx :: Connection -> TVar Int
bytesRx :: Connection -> TVar Int
addressValidated :: Connection -> TVar Bool
pendingQ :: Connection -> Array EncryptionLevel (TVar [ReceivedPacket])
ciphers :: Connection -> IOArray EncryptionLevel Cipher
coders :: Connection -> IOArray EncryptionLevel Coder
coders1RTT :: Connection -> IOArray Bool Coder1RTT
protectors :: Connection -> IOArray EncryptionLevel Protector
currentKeyPhase :: Connection -> IORef (Bool, Int)
negotiated :: Connection -> IORef Negotiated
connMyAuthCIDs :: Connection -> IORef AuthCIDs
connPeerAuthCIDs :: Connection -> IORef AuthCIDs
connResources :: Connection -> IORef (IO ())
encodeBuf :: Connection -> Buffer
encryptRes :: Connection -> SizedBuffer
decryptBuf :: Connection -> Buffer
connLDCC :: Connection -> LDCC
connState :: ConnState
connDebugLog :: DebugLogger
connQLog :: QLogger
connHooks :: Hooks
connSend :: Send
connRecv :: Recv
connRecvQ :: RecvQ
connSocket :: IORef Socket
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
outputQLim :: OutputQLim
migrationQ :: MigrationQ
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
minIdleTimeout :: IORef Microseconds
bytesTx :: TVar Int
bytesRx :: TVar Int
addressValidated :: TVar Bool
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
connResources :: IORef (IO ())
encodeBuf :: Buffer
encryptRes :: SizedBuffer
decryptBuf :: Buffer
connLDCC :: LDCC
..} = TVar Int -> IO Int
forall a. TVar a -> IO a
readTVarIO TVar Int
bytesRx
setAddressValidated :: Connection -> IO ()
setAddressValidated :: Connection -> IO ()
setAddressValidated Connection{Recv
Buffer
Array EncryptionLevel (TVar [ReceivedPacket])
IOArray Bool Coder1RTT
IOArray EncryptionLevel Cipher
IOArray EncryptionLevel Protector
IOArray EncryptionLevel Coder
ThreadId
TVar Bool
TVar Int
TVar TxFlow
TVar Concurrency
TVar MigrationState
TVar CIDDB
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
OutputQLim
MigrationQ
OutputQ
CryptoQ
InputQ
VersionInfo
RecvQ
SizedBuffer
ConnState
Parameters
LDCC
Hooks
Shared
Send
DebugLogger
QLogger
connState :: Connection -> ConnState
connDebugLog :: Connection -> DebugLogger
connQLog :: Connection -> QLogger
connHooks :: Connection -> Hooks
connSend :: Connection -> Send
connRecv :: Connection -> Recv
connRecvQ :: Connection -> RecvQ
connSocket :: Connection -> IORef Socket
readers :: Connection -> IORef (Map Word64 (Weak ThreadId))
mainThreadId :: Connection -> ThreadId
controlRate :: Connection -> Rate
roleInfo :: Connection -> IORef RoleInfo
quicVersionInfo :: Connection -> IORef VersionInfo
origVersionInfo :: Connection -> VersionInfo
myParameters :: Connection -> Parameters
myCIDDB :: Connection -> IORef CIDDB
peerParameters :: Connection -> IORef Parameters
peerCIDDB :: Connection -> TVar CIDDB
peerInfo :: Connection -> IORef PeerInfo
inputQ :: Connection -> InputQ
cryptoQ :: Connection -> CryptoQ
outputQ :: Connection -> OutputQ
outputQLim :: Connection -> OutputQLim
migrationQ :: Connection -> MigrationQ
shared :: Connection -> Shared
delayedAckCount :: Connection -> IORef Int
delayedAckCancel :: Connection -> IORef (IO ())
peerPacketNumber :: Connection -> IORef Int
streamTable :: Connection -> IORef StreamTable
myStreamId :: Connection -> TVar Concurrency
myUniStreamId :: Connection -> TVar Concurrency
peerStreamId :: Connection -> IORef Concurrency
peerUniStreamId :: Connection -> IORef Concurrency
flowTx :: Connection -> TVar TxFlow
flowRx :: Connection -> IORef RxFlow
migrationState :: Connection -> TVar MigrationState
minIdleTimeout :: Connection -> IORef Microseconds
bytesTx :: Connection -> TVar Int
bytesRx :: Connection -> TVar Int
addressValidated :: Connection -> TVar Bool
pendingQ :: Connection -> Array EncryptionLevel (TVar [ReceivedPacket])
ciphers :: Connection -> IOArray EncryptionLevel Cipher
coders :: Connection -> IOArray EncryptionLevel Coder
coders1RTT :: Connection -> IOArray Bool Coder1RTT
protectors :: Connection -> IOArray EncryptionLevel Protector
currentKeyPhase :: Connection -> IORef (Bool, Int)
negotiated :: Connection -> IORef Negotiated
connMyAuthCIDs :: Connection -> IORef AuthCIDs
connPeerAuthCIDs :: Connection -> IORef AuthCIDs
connResources :: Connection -> IORef (IO ())
encodeBuf :: Connection -> Buffer
encryptRes :: Connection -> SizedBuffer
decryptBuf :: Connection -> Buffer
connLDCC :: Connection -> LDCC
connState :: ConnState
connDebugLog :: DebugLogger
connQLog :: QLogger
connHooks :: Hooks
connSend :: Send
connRecv :: Recv
connRecvQ :: RecvQ
connSocket :: IORef Socket
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
outputQLim :: OutputQLim
migrationQ :: MigrationQ
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
minIdleTimeout :: IORef Microseconds
bytesTx :: TVar Int
bytesRx :: TVar Int
addressValidated :: TVar Bool
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
connResources :: IORef (IO ())
encodeBuf :: Buffer
encryptRes :: SizedBuffer
decryptBuf :: Buffer
connLDCC :: LDCC
..} = STM () -> IO ()
forall a. STM a -> IO a
atomically (STM () -> IO ()) -> STM () -> IO ()
forall a b. (a -> b) -> a -> b
$ TVar Bool -> Bool -> STM ()
forall a. TVar a -> a -> STM ()
writeTVar TVar Bool
addressValidated Bool
True
waitAntiAmplificationFree :: Connection -> Int -> IO ()
waitAntiAmplificationFree :: Connection -> Int -> IO ()
waitAntiAmplificationFree conn :: Connection
conn@Connection{Recv
Buffer
Array EncryptionLevel (TVar [ReceivedPacket])
IOArray Bool Coder1RTT
IOArray EncryptionLevel Cipher
IOArray EncryptionLevel Protector
IOArray EncryptionLevel Coder
ThreadId
TVar Bool
TVar Int
TVar TxFlow
TVar Concurrency
TVar MigrationState
TVar CIDDB
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
OutputQLim
MigrationQ
OutputQ
CryptoQ
InputQ
VersionInfo
RecvQ
SizedBuffer
ConnState
Parameters
LDCC
Hooks
Shared
Send
DebugLogger
QLogger
connState :: Connection -> ConnState
connDebugLog :: Connection -> DebugLogger
connQLog :: Connection -> QLogger
connHooks :: Connection -> Hooks
connSend :: Connection -> Send
connRecv :: Connection -> Recv
connRecvQ :: Connection -> RecvQ
connSocket :: Connection -> IORef Socket
readers :: Connection -> IORef (Map Word64 (Weak ThreadId))
mainThreadId :: Connection -> ThreadId
controlRate :: Connection -> Rate
roleInfo :: Connection -> IORef RoleInfo
quicVersionInfo :: Connection -> IORef VersionInfo
origVersionInfo :: Connection -> VersionInfo
myParameters :: Connection -> Parameters
myCIDDB :: Connection -> IORef CIDDB
peerParameters :: Connection -> IORef Parameters
peerCIDDB :: Connection -> TVar CIDDB
peerInfo :: Connection -> IORef PeerInfo
inputQ :: Connection -> InputQ
cryptoQ :: Connection -> CryptoQ
outputQ :: Connection -> OutputQ
outputQLim :: Connection -> OutputQLim
migrationQ :: Connection -> MigrationQ
shared :: Connection -> Shared
delayedAckCount :: Connection -> IORef Int
delayedAckCancel :: Connection -> IORef (IO ())
peerPacketNumber :: Connection -> IORef Int
streamTable :: Connection -> IORef StreamTable
myStreamId :: Connection -> TVar Concurrency
myUniStreamId :: Connection -> TVar Concurrency
peerStreamId :: Connection -> IORef Concurrency
peerUniStreamId :: Connection -> IORef Concurrency
flowTx :: Connection -> TVar TxFlow
flowRx :: Connection -> IORef RxFlow
migrationState :: Connection -> TVar MigrationState
minIdleTimeout :: Connection -> IORef Microseconds
bytesTx :: Connection -> TVar Int
bytesRx :: Connection -> TVar Int
addressValidated :: Connection -> TVar Bool
pendingQ :: Connection -> Array EncryptionLevel (TVar [ReceivedPacket])
ciphers :: Connection -> IOArray EncryptionLevel Cipher
coders :: Connection -> IOArray EncryptionLevel Coder
coders1RTT :: Connection -> IOArray Bool Coder1RTT
protectors :: Connection -> IOArray EncryptionLevel Protector
currentKeyPhase :: Connection -> IORef (Bool, Int)
negotiated :: Connection -> IORef Negotiated
connMyAuthCIDs :: Connection -> IORef AuthCIDs
connPeerAuthCIDs :: Connection -> IORef AuthCIDs
connResources :: Connection -> IORef (IO ())
encodeBuf :: Connection -> Buffer
encryptRes :: Connection -> SizedBuffer
decryptBuf :: Connection -> Buffer
connLDCC :: Connection -> LDCC
connState :: ConnState
connDebugLog :: DebugLogger
connQLog :: QLogger
connHooks :: Hooks
connSend :: Send
connRecv :: Recv
connRecvQ :: RecvQ
connSocket :: IORef Socket
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
outputQLim :: OutputQLim
migrationQ :: MigrationQ
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
minIdleTimeout :: IORef Microseconds
bytesTx :: TVar Int
bytesRx :: TVar Int
addressValidated :: TVar Bool
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
connResources :: IORef (IO ())
encodeBuf :: Buffer
encryptRes :: SizedBuffer
decryptBuf :: Buffer
connLDCC :: LDCC
..} Int
siz = do
Bool
ok <- Connection -> Int -> IO Bool
checkAntiAmplificationFree Connection
conn Int
siz
Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless Bool
ok (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$ do
LDCC -> IO ()
beforeAntiAmp LDCC
connLDCC
STM () -> IO ()
forall a. STM a -> IO a
atomically (Connection -> Int -> STM Bool
checkAntiAmplificationFreeSTM Connection
conn Int
siz STM Bool -> (Bool -> STM ()) -> STM ()
forall a b. STM a -> (a -> STM b) -> STM b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Bool -> STM ()
check)
checkAntiAmplificationFreeSTM :: Connection -> Int -> STM Bool
checkAntiAmplificationFreeSTM :: Connection -> Int -> STM Bool
checkAntiAmplificationFreeSTM Connection{Recv
Buffer
Array EncryptionLevel (TVar [ReceivedPacket])
IOArray Bool Coder1RTT
IOArray EncryptionLevel Cipher
IOArray EncryptionLevel Protector
IOArray EncryptionLevel Coder
ThreadId
TVar Bool
TVar Int
TVar TxFlow
TVar Concurrency
TVar MigrationState
TVar CIDDB
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
OutputQLim
MigrationQ
OutputQ
CryptoQ
InputQ
VersionInfo
RecvQ
SizedBuffer
ConnState
Parameters
LDCC
Hooks
Shared
Send
DebugLogger
QLogger
connState :: Connection -> ConnState
connDebugLog :: Connection -> DebugLogger
connQLog :: Connection -> QLogger
connHooks :: Connection -> Hooks
connSend :: Connection -> Send
connRecv :: Connection -> Recv
connRecvQ :: Connection -> RecvQ
connSocket :: Connection -> IORef Socket
readers :: Connection -> IORef (Map Word64 (Weak ThreadId))
mainThreadId :: Connection -> ThreadId
controlRate :: Connection -> Rate
roleInfo :: Connection -> IORef RoleInfo
quicVersionInfo :: Connection -> IORef VersionInfo
origVersionInfo :: Connection -> VersionInfo
myParameters :: Connection -> Parameters
myCIDDB :: Connection -> IORef CIDDB
peerParameters :: Connection -> IORef Parameters
peerCIDDB :: Connection -> TVar CIDDB
peerInfo :: Connection -> IORef PeerInfo
inputQ :: Connection -> InputQ
cryptoQ :: Connection -> CryptoQ
outputQ :: Connection -> OutputQ
outputQLim :: Connection -> OutputQLim
migrationQ :: Connection -> MigrationQ
shared :: Connection -> Shared
delayedAckCount :: Connection -> IORef Int
delayedAckCancel :: Connection -> IORef (IO ())
peerPacketNumber :: Connection -> IORef Int
streamTable :: Connection -> IORef StreamTable
myStreamId :: Connection -> TVar Concurrency
myUniStreamId :: Connection -> TVar Concurrency
peerStreamId :: Connection -> IORef Concurrency
peerUniStreamId :: Connection -> IORef Concurrency
flowTx :: Connection -> TVar TxFlow
flowRx :: Connection -> IORef RxFlow
migrationState :: Connection -> TVar MigrationState
minIdleTimeout :: Connection -> IORef Microseconds
bytesTx :: Connection -> TVar Int
bytesRx :: Connection -> TVar Int
addressValidated :: Connection -> TVar Bool
pendingQ :: Connection -> Array EncryptionLevel (TVar [ReceivedPacket])
ciphers :: Connection -> IOArray EncryptionLevel Cipher
coders :: Connection -> IOArray EncryptionLevel Coder
coders1RTT :: Connection -> IOArray Bool Coder1RTT
protectors :: Connection -> IOArray EncryptionLevel Protector
currentKeyPhase :: Connection -> IORef (Bool, Int)
negotiated :: Connection -> IORef Negotiated
connMyAuthCIDs :: Connection -> IORef AuthCIDs
connPeerAuthCIDs :: Connection -> IORef AuthCIDs
connResources :: Connection -> IORef (IO ())
encodeBuf :: Connection -> Buffer
encryptRes :: Connection -> SizedBuffer
decryptBuf :: Connection -> Buffer
connLDCC :: Connection -> LDCC
connState :: ConnState
connDebugLog :: DebugLogger
connQLog :: QLogger
connHooks :: Hooks
connSend :: Send
connRecv :: Recv
connRecvQ :: RecvQ
connSocket :: IORef Socket
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
outputQLim :: OutputQLim
migrationQ :: MigrationQ
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
minIdleTimeout :: IORef Microseconds
bytesTx :: TVar Int
bytesRx :: TVar Int
addressValidated :: TVar Bool
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
connResources :: IORef (IO ())
encodeBuf :: Buffer
encryptRes :: SizedBuffer
decryptBuf :: Buffer
connLDCC :: LDCC
..} Int
siz = do
Bool
validated <- TVar Bool -> STM Bool
forall a. TVar a -> STM a
readTVar TVar Bool
addressValidated
if Bool
validated
then Bool -> STM Bool
forall a. a -> STM a
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
True
else do
Int
tx <- TVar Int -> STM Int
forall a. TVar a -> STM a
readTVar TVar Int
bytesTx
Int
rx <- TVar Int -> STM Int
forall a. TVar a -> STM a
readTVar TVar Int
bytesRx
Bool -> STM Bool
forall a. a -> STM a
forall (m :: * -> *) a. Monad m => a -> m a
return (Int
tx Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
siz Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<= Int
3 Int -> Int -> Int
forall a. Num a => a -> a -> a
* Int
rx)
checkAntiAmplificationFree :: Connection -> Int -> IO Bool
checkAntiAmplificationFree :: Connection -> Int -> IO Bool
checkAntiAmplificationFree Connection
conn Int
siz =
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
$ Connection -> Int -> STM Bool
checkAntiAmplificationFreeSTM Connection
conn Int
siz