{-# LANGUAGE RecordWildCards #-}

module Network.QUIC.Connection.State (
    setConnection0RTTReady
  , isConnection1RTTReady
  , setConnection1RTTReady
  , isConnectionEstablished
  , setConnectionEstablished
  , wait0RTTReady
  , wait1RTTReady
  , waitEstablished
  , readConnectionFlowTx
  , addTxData
  , getTxData
  , setTxMaxData
  , getTxMaxData
  , addRxData
  , getRxData
  , addRxMaxData
  , getRxMaxData
  , getRxDataWindow
  , addTxBytes
  , getTxBytes
  , addRxBytes
  , getRxBytes
  , setAddressValidated
  , waitAntiAmplificationFree
  , checkAntiAmplificationFree
  ) where

import UnliftIO.STM

import Network.QUIC.Connection.Types
import Network.QUIC.Connector
import Network.QUIC.Imports
import Network.QUIC.Recovery
import Network.QUIC.Stream

----------------------------------------------------------------

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 Flow
TVar Concurrency
TVar MigrationState
TVar CIDDB
IORef Int
IORef (IO ())
IORef (Bool, Int)
IORef UDPSocket
IORef Microseconds
IORef VersionInfo
IORef Flow
IORef StreamTable
IORef AuthCIDs
IORef Parameters
IORef Concurrency
IORef Negotiated
IORef CIDDB
IORef RoleInfo
MigrationQ
OutputQ
CryptoQ
InputQ
VersionInfo
RecvQ
SizedBuffer
ConnState
Parameters
LDCC
Hooks
Shared
Send
DebugLogger
QLogger
connLDCC :: Connection -> LDCC
decryptBuf :: Connection -> Buffer
encryptRes :: Connection -> SizedBuffer
encodeBuf :: Connection -> Buffer
connResources :: Connection -> IORef (IO ())
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])
addressValidated :: Connection -> TVar Bool
bytesRx :: Connection -> TVar Int
bytesTx :: Connection -> TVar Int
minIdleTimeout :: Connection -> IORef Microseconds
migrationState :: Connection -> TVar MigrationState
flowRx :: Connection -> IORef Flow
flowTx :: Connection -> TVar Flow
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
migrationQ :: Connection -> MigrationQ
outputQ :: Connection -> OutputQ
cryptoQ :: Connection -> CryptoQ
inputQ :: Connection -> InputQ
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
mainThreadId :: Connection -> ThreadId
readers :: Connection -> IORef (IO ())
udpSocket :: Connection -> IORef UDPSocket
connRecvQ :: Connection -> RecvQ
connRecv :: Connection -> Recv
connSend :: Connection -> Send
connHooks :: Connection -> Hooks
connQLog :: Connection -> QLogger
connDebugLog :: Connection -> DebugLogger
connState :: Connection -> ConnState
connLDCC :: LDCC
decryptBuf :: Buffer
encryptRes :: SizedBuffer
encodeBuf :: Buffer
connResources :: IORef (IO ())
connPeerAuthCIDs :: IORef AuthCIDs
connMyAuthCIDs :: IORef AuthCIDs
negotiated :: IORef Negotiated
currentKeyPhase :: IORef (Bool, Int)
protectors :: IOArray EncryptionLevel Protector
coders1RTT :: IOArray Bool Coder1RTT
coders :: IOArray EncryptionLevel Coder
ciphers :: IOArray EncryptionLevel Cipher
pendingQ :: Array EncryptionLevel (TVar [ReceivedPacket])
addressValidated :: TVar Bool
bytesRx :: TVar Int
bytesTx :: TVar Int
minIdleTimeout :: IORef Microseconds
migrationState :: TVar MigrationState
flowRx :: IORef Flow
flowTx :: TVar Flow
peerStreamId :: IORef Concurrency
myUniStreamId :: TVar Concurrency
myStreamId :: TVar Concurrency
streamTable :: IORef StreamTable
peerPacketNumber :: IORef Int
delayedAckCancel :: IORef (IO ())
delayedAckCount :: IORef Int
shared :: Shared
migrationQ :: MigrationQ
outputQ :: OutputQ
cryptoQ :: CryptoQ
inputQ :: InputQ
peerCIDDB :: TVar CIDDB
peerParameters :: IORef Parameters
myCIDDB :: IORef CIDDB
myParameters :: Parameters
origVersionInfo :: VersionInfo
quicVersionInfo :: IORef VersionInfo
roleInfo :: IORef RoleInfo
mainThreadId :: ThreadId
readers :: IORef (IO ())
udpSocket :: IORef UDPSocket
connRecvQ :: RecvQ
connRecv :: Recv
connSend :: Send
connHooks :: Hooks
connQLog :: QLogger
connDebugLog :: DebugLogger
connState :: ConnState
..} ConnectionState
st =
    forall (m :: * -> *) a. MonadIO m => STM a -> m a
atomically forall a b. (a -> b) -> a -> b
$ 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
    forall a. IORef a -> a -> IO ()
writeIORef (Shared -> IORef Bool
shared1RTTReady 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 Flow
TVar Concurrency
TVar MigrationState
TVar CIDDB
IORef Int
IORef (IO ())
IORef (Bool, Int)
IORef UDPSocket
IORef Microseconds
IORef VersionInfo
IORef Flow
IORef StreamTable
IORef AuthCIDs
IORef Parameters
IORef Concurrency
IORef Negotiated
IORef CIDDB
IORef RoleInfo
MigrationQ
OutputQ
CryptoQ
InputQ
VersionInfo
RecvQ
SizedBuffer
ConnState
Parameters
LDCC
Hooks
Shared
Send
DebugLogger
QLogger
connLDCC :: LDCC
decryptBuf :: Buffer
encryptRes :: SizedBuffer
encodeBuf :: Buffer
connResources :: IORef (IO ())
connPeerAuthCIDs :: IORef AuthCIDs
connMyAuthCIDs :: IORef AuthCIDs
negotiated :: IORef Negotiated
currentKeyPhase :: IORef (Bool, Int)
protectors :: IOArray EncryptionLevel Protector
coders1RTT :: IOArray Bool Coder1RTT
coders :: IOArray EncryptionLevel Coder
ciphers :: IOArray EncryptionLevel Cipher
pendingQ :: Array EncryptionLevel (TVar [ReceivedPacket])
addressValidated :: TVar Bool
bytesRx :: TVar Int
bytesTx :: TVar Int
minIdleTimeout :: IORef Microseconds
migrationState :: TVar MigrationState
flowRx :: IORef Flow
flowTx :: TVar Flow
peerStreamId :: IORef Concurrency
myUniStreamId :: TVar Concurrency
myStreamId :: TVar Concurrency
streamTable :: IORef StreamTable
peerPacketNumber :: IORef Int
delayedAckCancel :: IORef (IO ())
delayedAckCount :: IORef Int
shared :: Shared
migrationQ :: MigrationQ
outputQ :: OutputQ
cryptoQ :: CryptoQ
inputQ :: InputQ
peerCIDDB :: TVar CIDDB
peerParameters :: IORef Parameters
myCIDDB :: IORef CIDDB
myParameters :: Parameters
origVersionInfo :: VersionInfo
quicVersionInfo :: IORef VersionInfo
roleInfo :: IORef RoleInfo
mainThreadId :: ThreadId
readers :: IORef (IO ())
udpSocket :: IORef UDPSocket
connRecvQ :: RecvQ
connRecv :: Recv
connSend :: Send
connHooks :: Hooks
connQLog :: QLogger
connDebugLog :: DebugLogger
connState :: ConnState
connLDCC :: Connection -> LDCC
decryptBuf :: Connection -> Buffer
encryptRes :: Connection -> SizedBuffer
encodeBuf :: Connection -> Buffer
connResources :: Connection -> IORef (IO ())
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])
addressValidated :: Connection -> TVar Bool
bytesRx :: Connection -> TVar Int
bytesTx :: Connection -> TVar Int
minIdleTimeout :: Connection -> IORef Microseconds
migrationState :: Connection -> TVar MigrationState
flowRx :: Connection -> IORef Flow
flowTx :: Connection -> TVar Flow
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
migrationQ :: Connection -> MigrationQ
outputQ :: Connection -> OutputQ
cryptoQ :: Connection -> CryptoQ
inputQ :: Connection -> InputQ
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
mainThreadId :: Connection -> ThreadId
readers :: Connection -> IORef (IO ())
udpSocket :: Connection -> IORef UDPSocket
connRecvQ :: Connection -> RecvQ
connRecv :: Connection -> Recv
connSend :: Connection -> Send
connHooks :: Connection -> Hooks
connQLog :: Connection -> QLogger
connDebugLog :: Connection -> DebugLogger
connState :: Connection -> ConnState
..} = forall (m :: * -> *) a. MonadIO m => STM a -> m a
atomically forall a b. (a -> b) -> a -> b
$ do
    ConnectionState
st <- forall a. TVar a -> STM a
readTVar forall a b. (a -> b) -> a -> b
$ ConnState -> TVar ConnectionState
connectionState ConnState
connState
    forall (m :: * -> *) a. Monad m => a -> m a
return (ConnectionState
st forall a. Ord a => a -> a -> Bool
>= ConnectionState
ReadyFor1RTT)

----------------------------------------------------------------

-- | Waiting until 0-RTT data can be sent.
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 Flow
TVar Concurrency
TVar MigrationState
TVar CIDDB
IORef Int
IORef (IO ())
IORef (Bool, Int)
IORef UDPSocket
IORef Microseconds
IORef VersionInfo
IORef Flow
IORef StreamTable
IORef AuthCIDs
IORef Parameters
IORef Concurrency
IORef Negotiated
IORef CIDDB
IORef RoleInfo
MigrationQ
OutputQ
CryptoQ
InputQ
VersionInfo
RecvQ
SizedBuffer
ConnState
Parameters
LDCC
Hooks
Shared
Send
DebugLogger
QLogger
connLDCC :: LDCC
decryptBuf :: Buffer
encryptRes :: SizedBuffer
encodeBuf :: Buffer
connResources :: IORef (IO ())
connPeerAuthCIDs :: IORef AuthCIDs
connMyAuthCIDs :: IORef AuthCIDs
negotiated :: IORef Negotiated
currentKeyPhase :: IORef (Bool, Int)
protectors :: IOArray EncryptionLevel Protector
coders1RTT :: IOArray Bool Coder1RTT
coders :: IOArray EncryptionLevel Coder
ciphers :: IOArray EncryptionLevel Cipher
pendingQ :: Array EncryptionLevel (TVar [ReceivedPacket])
addressValidated :: TVar Bool
bytesRx :: TVar Int
bytesTx :: TVar Int
minIdleTimeout :: IORef Microseconds
migrationState :: TVar MigrationState
flowRx :: IORef Flow
flowTx :: TVar Flow
peerStreamId :: IORef Concurrency
myUniStreamId :: TVar Concurrency
myStreamId :: TVar Concurrency
streamTable :: IORef StreamTable
peerPacketNumber :: IORef Int
delayedAckCancel :: IORef (IO ())
delayedAckCount :: IORef Int
shared :: Shared
migrationQ :: MigrationQ
outputQ :: OutputQ
cryptoQ :: CryptoQ
inputQ :: InputQ
peerCIDDB :: TVar CIDDB
peerParameters :: IORef Parameters
myCIDDB :: IORef CIDDB
myParameters :: Parameters
origVersionInfo :: VersionInfo
quicVersionInfo :: IORef VersionInfo
roleInfo :: IORef RoleInfo
mainThreadId :: ThreadId
readers :: IORef (IO ())
udpSocket :: IORef UDPSocket
connRecvQ :: RecvQ
connRecv :: Recv
connSend :: Send
connHooks :: Hooks
connQLog :: QLogger
connDebugLog :: DebugLogger
connState :: ConnState
connLDCC :: Connection -> LDCC
decryptBuf :: Connection -> Buffer
encryptRes :: Connection -> SizedBuffer
encodeBuf :: Connection -> Buffer
connResources :: Connection -> IORef (IO ())
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])
addressValidated :: Connection -> TVar Bool
bytesRx :: Connection -> TVar Int
bytesTx :: Connection -> TVar Int
minIdleTimeout :: Connection -> IORef Microseconds
migrationState :: Connection -> TVar MigrationState
flowRx :: Connection -> IORef Flow
flowTx :: Connection -> TVar Flow
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
migrationQ :: Connection -> MigrationQ
outputQ :: Connection -> OutputQ
cryptoQ :: Connection -> CryptoQ
inputQ :: Connection -> InputQ
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
mainThreadId :: Connection -> ThreadId
readers :: Connection -> IORef (IO ())
udpSocket :: Connection -> IORef UDPSocket
connRecvQ :: Connection -> RecvQ
connRecv :: Connection -> Recv
connSend :: Connection -> Send
connHooks :: Connection -> Hooks
connQLog :: Connection -> QLogger
connDebugLog :: Connection -> DebugLogger
connState :: Connection -> ConnState
..} = forall (m :: * -> *) a. MonadIO m => STM a -> m a
atomically forall a b. (a -> b) -> a -> b
$ do
    ConnectionState
cs <- forall a. TVar a -> STM a
readTVar forall a b. (a -> b) -> a -> b
$ ConnState -> TVar ConnectionState
connectionState ConnState
connState
    Bool -> STM ()
checkSTM (ConnectionState
cs forall a. Ord a => a -> a -> Bool
>= ConnectionState
ReadyFor0RTT)

-- | Waiting until 1-RTT data can be sent.
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 Flow
TVar Concurrency
TVar MigrationState
TVar CIDDB
IORef Int
IORef (IO ())
IORef (Bool, Int)
IORef UDPSocket
IORef Microseconds
IORef VersionInfo
IORef Flow
IORef StreamTable
IORef AuthCIDs
IORef Parameters
IORef Concurrency
IORef Negotiated
IORef CIDDB
IORef RoleInfo
MigrationQ
OutputQ
CryptoQ
InputQ
VersionInfo
RecvQ
SizedBuffer
ConnState
Parameters
LDCC
Hooks
Shared
Send
DebugLogger
QLogger
connLDCC :: LDCC
decryptBuf :: Buffer
encryptRes :: SizedBuffer
encodeBuf :: Buffer
connResources :: IORef (IO ())
connPeerAuthCIDs :: IORef AuthCIDs
connMyAuthCIDs :: IORef AuthCIDs
negotiated :: IORef Negotiated
currentKeyPhase :: IORef (Bool, Int)
protectors :: IOArray EncryptionLevel Protector
coders1RTT :: IOArray Bool Coder1RTT
coders :: IOArray EncryptionLevel Coder
ciphers :: IOArray EncryptionLevel Cipher
pendingQ :: Array EncryptionLevel (TVar [ReceivedPacket])
addressValidated :: TVar Bool
bytesRx :: TVar Int
bytesTx :: TVar Int
minIdleTimeout :: IORef Microseconds
migrationState :: TVar MigrationState
flowRx :: IORef Flow
flowTx :: TVar Flow
peerStreamId :: IORef Concurrency
myUniStreamId :: TVar Concurrency
myStreamId :: TVar Concurrency
streamTable :: IORef StreamTable
peerPacketNumber :: IORef Int
delayedAckCancel :: IORef (IO ())
delayedAckCount :: IORef Int
shared :: Shared
migrationQ :: MigrationQ
outputQ :: OutputQ
cryptoQ :: CryptoQ
inputQ :: InputQ
peerCIDDB :: TVar CIDDB
peerParameters :: IORef Parameters
myCIDDB :: IORef CIDDB
myParameters :: Parameters
origVersionInfo :: VersionInfo
quicVersionInfo :: IORef VersionInfo
roleInfo :: IORef RoleInfo
mainThreadId :: ThreadId
readers :: IORef (IO ())
udpSocket :: IORef UDPSocket
connRecvQ :: RecvQ
connRecv :: Recv
connSend :: Send
connHooks :: Hooks
connQLog :: QLogger
connDebugLog :: DebugLogger
connState :: ConnState
connLDCC :: Connection -> LDCC
decryptBuf :: Connection -> Buffer
encryptRes :: Connection -> SizedBuffer
encodeBuf :: Connection -> Buffer
connResources :: Connection -> IORef (IO ())
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])
addressValidated :: Connection -> TVar Bool
bytesRx :: Connection -> TVar Int
bytesTx :: Connection -> TVar Int
minIdleTimeout :: Connection -> IORef Microseconds
migrationState :: Connection -> TVar MigrationState
flowRx :: Connection -> IORef Flow
flowTx :: Connection -> TVar Flow
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
migrationQ :: Connection -> MigrationQ
outputQ :: Connection -> OutputQ
cryptoQ :: Connection -> CryptoQ
inputQ :: Connection -> InputQ
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
mainThreadId :: Connection -> ThreadId
readers :: Connection -> IORef (IO ())
udpSocket :: Connection -> IORef UDPSocket
connRecvQ :: Connection -> RecvQ
connRecv :: Connection -> Recv
connSend :: Connection -> Send
connHooks :: Connection -> Hooks
connQLog :: Connection -> QLogger
connDebugLog :: Connection -> DebugLogger
connState :: Connection -> ConnState
..} = forall (m :: * -> *) a. MonadIO m => STM a -> m a
atomically forall a b. (a -> b) -> a -> b
$ do
    ConnectionState
cs <- forall a. TVar a -> STM a
readTVar forall a b. (a -> b) -> a -> b
$ ConnState -> TVar ConnectionState
connectionState ConnState
connState
    Bool -> STM ()
checkSTM (ConnectionState
cs forall a. Ord a => a -> a -> Bool
>= ConnectionState
ReadyFor1RTT)

-- | For clients, waiting until HANDSHAKE_DONE is received.
--   For servers, waiting until a TLS stack reports that the handshake is complete.
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 Flow
TVar Concurrency
TVar MigrationState
TVar CIDDB
IORef Int
IORef (IO ())
IORef (Bool, Int)
IORef UDPSocket
IORef Microseconds
IORef VersionInfo
IORef Flow
IORef StreamTable
IORef AuthCIDs
IORef Parameters
IORef Concurrency
IORef Negotiated
IORef CIDDB
IORef RoleInfo
MigrationQ
OutputQ
CryptoQ
InputQ
VersionInfo
RecvQ
SizedBuffer
ConnState
Parameters
LDCC
Hooks
Shared
Send
DebugLogger
QLogger
connLDCC :: LDCC
decryptBuf :: Buffer
encryptRes :: SizedBuffer
encodeBuf :: Buffer
connResources :: IORef (IO ())
connPeerAuthCIDs :: IORef AuthCIDs
connMyAuthCIDs :: IORef AuthCIDs
negotiated :: IORef Negotiated
currentKeyPhase :: IORef (Bool, Int)
protectors :: IOArray EncryptionLevel Protector
coders1RTT :: IOArray Bool Coder1RTT
coders :: IOArray EncryptionLevel Coder
ciphers :: IOArray EncryptionLevel Cipher
pendingQ :: Array EncryptionLevel (TVar [ReceivedPacket])
addressValidated :: TVar Bool
bytesRx :: TVar Int
bytesTx :: TVar Int
minIdleTimeout :: IORef Microseconds
migrationState :: TVar MigrationState
flowRx :: IORef Flow
flowTx :: TVar Flow
peerStreamId :: IORef Concurrency
myUniStreamId :: TVar Concurrency
myStreamId :: TVar Concurrency
streamTable :: IORef StreamTable
peerPacketNumber :: IORef Int
delayedAckCancel :: IORef (IO ())
delayedAckCount :: IORef Int
shared :: Shared
migrationQ :: MigrationQ
outputQ :: OutputQ
cryptoQ :: CryptoQ
inputQ :: InputQ
peerCIDDB :: TVar CIDDB
peerParameters :: IORef Parameters
myCIDDB :: IORef CIDDB
myParameters :: Parameters
origVersionInfo :: VersionInfo
quicVersionInfo :: IORef VersionInfo
roleInfo :: IORef RoleInfo
mainThreadId :: ThreadId
readers :: IORef (IO ())
udpSocket :: IORef UDPSocket
connRecvQ :: RecvQ
connRecv :: Recv
connSend :: Send
connHooks :: Hooks
connQLog :: QLogger
connDebugLog :: DebugLogger
connState :: ConnState
connLDCC :: Connection -> LDCC
decryptBuf :: Connection -> Buffer
encryptRes :: Connection -> SizedBuffer
encodeBuf :: Connection -> Buffer
connResources :: Connection -> IORef (IO ())
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])
addressValidated :: Connection -> TVar Bool
bytesRx :: Connection -> TVar Int
bytesTx :: Connection -> TVar Int
minIdleTimeout :: Connection -> IORef Microseconds
migrationState :: Connection -> TVar MigrationState
flowRx :: Connection -> IORef Flow
flowTx :: Connection -> TVar Flow
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
migrationQ :: Connection -> MigrationQ
outputQ :: Connection -> OutputQ
cryptoQ :: Connection -> CryptoQ
inputQ :: Connection -> InputQ
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
mainThreadId :: Connection -> ThreadId
readers :: Connection -> IORef (IO ())
udpSocket :: Connection -> IORef UDPSocket
connRecvQ :: Connection -> RecvQ
connRecv :: Connection -> Recv
connSend :: Connection -> Send
connHooks :: Connection -> Hooks
connQLog :: Connection -> QLogger
connDebugLog :: Connection -> DebugLogger
connState :: Connection -> ConnState
..} = forall (m :: * -> *) a. MonadIO m => STM a -> m a
atomically forall a b. (a -> b) -> a -> b
$ do
    ConnectionState
cs <- forall a. TVar a -> STM a
readTVar forall a b. (a -> b) -> a -> b
$ ConnState -> TVar ConnectionState
connectionState ConnState
connState
    Bool -> STM ()
checkSTM (ConnectionState
cs forall a. Ord a => a -> a -> Bool
>= ConnectionState
Established)

----------------------------------------------------------------

readConnectionFlowTx :: Connection -> STM Flow
readConnectionFlowTx :: Connection -> STM Flow
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 Flow
TVar Concurrency
TVar MigrationState
TVar CIDDB
IORef Int
IORef (IO ())
IORef (Bool, Int)
IORef UDPSocket
IORef Microseconds
IORef VersionInfo
IORef Flow
IORef StreamTable
IORef AuthCIDs
IORef Parameters
IORef Concurrency
IORef Negotiated
IORef CIDDB
IORef RoleInfo
MigrationQ
OutputQ
CryptoQ
InputQ
VersionInfo
RecvQ
SizedBuffer
ConnState
Parameters
LDCC
Hooks
Shared
Send
DebugLogger
QLogger
connLDCC :: LDCC
decryptBuf :: Buffer
encryptRes :: SizedBuffer
encodeBuf :: Buffer
connResources :: IORef (IO ())
connPeerAuthCIDs :: IORef AuthCIDs
connMyAuthCIDs :: IORef AuthCIDs
negotiated :: IORef Negotiated
currentKeyPhase :: IORef (Bool, Int)
protectors :: IOArray EncryptionLevel Protector
coders1RTT :: IOArray Bool Coder1RTT
coders :: IOArray EncryptionLevel Coder
ciphers :: IOArray EncryptionLevel Cipher
pendingQ :: Array EncryptionLevel (TVar [ReceivedPacket])
addressValidated :: TVar Bool
bytesRx :: TVar Int
bytesTx :: TVar Int
minIdleTimeout :: IORef Microseconds
migrationState :: TVar MigrationState
flowRx :: IORef Flow
flowTx :: TVar Flow
peerStreamId :: IORef Concurrency
myUniStreamId :: TVar Concurrency
myStreamId :: TVar Concurrency
streamTable :: IORef StreamTable
peerPacketNumber :: IORef Int
delayedAckCancel :: IORef (IO ())
delayedAckCount :: IORef Int
shared :: Shared
migrationQ :: MigrationQ
outputQ :: OutputQ
cryptoQ :: CryptoQ
inputQ :: InputQ
peerCIDDB :: TVar CIDDB
peerParameters :: IORef Parameters
myCIDDB :: IORef CIDDB
myParameters :: Parameters
origVersionInfo :: VersionInfo
quicVersionInfo :: IORef VersionInfo
roleInfo :: IORef RoleInfo
mainThreadId :: ThreadId
readers :: IORef (IO ())
udpSocket :: IORef UDPSocket
connRecvQ :: RecvQ
connRecv :: Recv
connSend :: Send
connHooks :: Hooks
connQLog :: QLogger
connDebugLog :: DebugLogger
connState :: ConnState
connLDCC :: Connection -> LDCC
decryptBuf :: Connection -> Buffer
encryptRes :: Connection -> SizedBuffer
encodeBuf :: Connection -> Buffer
connResources :: Connection -> IORef (IO ())
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])
addressValidated :: Connection -> TVar Bool
bytesRx :: Connection -> TVar Int
bytesTx :: Connection -> TVar Int
minIdleTimeout :: Connection -> IORef Microseconds
migrationState :: Connection -> TVar MigrationState
flowRx :: Connection -> IORef Flow
flowTx :: Connection -> TVar Flow
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
migrationQ :: Connection -> MigrationQ
outputQ :: Connection -> OutputQ
cryptoQ :: Connection -> CryptoQ
inputQ :: Connection -> InputQ
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
mainThreadId :: Connection -> ThreadId
readers :: Connection -> IORef (IO ())
udpSocket :: Connection -> IORef UDPSocket
connRecvQ :: Connection -> RecvQ
connRecv :: Connection -> Recv
connSend :: Connection -> Send
connHooks :: Connection -> Hooks
connQLog :: Connection -> QLogger
connDebugLog :: Connection -> DebugLogger
connState :: Connection -> ConnState
..} = forall a. TVar a -> STM a
readTVar TVar Flow
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 Flow
TVar Concurrency
TVar MigrationState
TVar CIDDB
IORef Int
IORef (IO ())
IORef (Bool, Int)
IORef UDPSocket
IORef Microseconds
IORef VersionInfo
IORef Flow
IORef StreamTable
IORef AuthCIDs
IORef Parameters
IORef Concurrency
IORef Negotiated
IORef CIDDB
IORef RoleInfo
MigrationQ
OutputQ
CryptoQ
InputQ
VersionInfo
RecvQ
SizedBuffer
ConnState
Parameters
LDCC
Hooks
Shared
Send
DebugLogger
QLogger
connLDCC :: LDCC
decryptBuf :: Buffer
encryptRes :: SizedBuffer
encodeBuf :: Buffer
connResources :: IORef (IO ())
connPeerAuthCIDs :: IORef AuthCIDs
connMyAuthCIDs :: IORef AuthCIDs
negotiated :: IORef Negotiated
currentKeyPhase :: IORef (Bool, Int)
protectors :: IOArray EncryptionLevel Protector
coders1RTT :: IOArray Bool Coder1RTT
coders :: IOArray EncryptionLevel Coder
ciphers :: IOArray EncryptionLevel Cipher
pendingQ :: Array EncryptionLevel (TVar [ReceivedPacket])
addressValidated :: TVar Bool
bytesRx :: TVar Int
bytesTx :: TVar Int
minIdleTimeout :: IORef Microseconds
migrationState :: TVar MigrationState
flowRx :: IORef Flow
flowTx :: TVar Flow
peerStreamId :: IORef Concurrency
myUniStreamId :: TVar Concurrency
myStreamId :: TVar Concurrency
streamTable :: IORef StreamTable
peerPacketNumber :: IORef Int
delayedAckCancel :: IORef (IO ())
delayedAckCount :: IORef Int
shared :: Shared
migrationQ :: MigrationQ
outputQ :: OutputQ
cryptoQ :: CryptoQ
inputQ :: InputQ
peerCIDDB :: TVar CIDDB
peerParameters :: IORef Parameters
myCIDDB :: IORef CIDDB
myParameters :: Parameters
origVersionInfo :: VersionInfo
quicVersionInfo :: IORef VersionInfo
roleInfo :: IORef RoleInfo
mainThreadId :: ThreadId
readers :: IORef (IO ())
udpSocket :: IORef UDPSocket
connRecvQ :: RecvQ
connRecv :: Recv
connSend :: Send
connHooks :: Hooks
connQLog :: QLogger
connDebugLog :: DebugLogger
connState :: ConnState
connLDCC :: Connection -> LDCC
decryptBuf :: Connection -> Buffer
encryptRes :: Connection -> SizedBuffer
encodeBuf :: Connection -> Buffer
connResources :: Connection -> IORef (IO ())
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])
addressValidated :: Connection -> TVar Bool
bytesRx :: Connection -> TVar Int
bytesTx :: Connection -> TVar Int
minIdleTimeout :: Connection -> IORef Microseconds
migrationState :: Connection -> TVar MigrationState
flowRx :: Connection -> IORef Flow
flowTx :: Connection -> TVar Flow
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
migrationQ :: Connection -> MigrationQ
outputQ :: Connection -> OutputQ
cryptoQ :: Connection -> CryptoQ
inputQ :: Connection -> InputQ
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
mainThreadId :: Connection -> ThreadId
readers :: Connection -> IORef (IO ())
udpSocket :: Connection -> IORef UDPSocket
connRecvQ :: Connection -> RecvQ
connRecv :: Connection -> Recv
connSend :: Connection -> Send
connHooks :: Connection -> Hooks
connQLog :: Connection -> QLogger
connDebugLog :: Connection -> DebugLogger
connState :: Connection -> ConnState
..} Int
n = forall a. TVar a -> (a -> a) -> STM ()
modifyTVar' TVar Flow
flowTx Flow -> Flow
add
  where
    add :: Flow -> Flow
add Flow
flow = Flow
flow { flowData :: Int
flowData = Flow -> Int
flowData Flow
flow forall a. Num a => a -> a -> a
+ Int
n }

getTxData :: Connection -> IO Int
getTxData :: Connection -> IO Int
getTxData 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 Flow
TVar Concurrency
TVar MigrationState
TVar CIDDB
IORef Int
IORef (IO ())
IORef (Bool, Int)
IORef UDPSocket
IORef Microseconds
IORef VersionInfo
IORef Flow
IORef StreamTable
IORef AuthCIDs
IORef Parameters
IORef Concurrency
IORef Negotiated
IORef CIDDB
IORef RoleInfo
MigrationQ
OutputQ
CryptoQ
InputQ
VersionInfo
RecvQ
SizedBuffer
ConnState
Parameters
LDCC
Hooks
Shared
Send
DebugLogger
QLogger
connLDCC :: LDCC
decryptBuf :: Buffer
encryptRes :: SizedBuffer
encodeBuf :: Buffer
connResources :: IORef (IO ())
connPeerAuthCIDs :: IORef AuthCIDs
connMyAuthCIDs :: IORef AuthCIDs
negotiated :: IORef Negotiated
currentKeyPhase :: IORef (Bool, Int)
protectors :: IOArray EncryptionLevel Protector
coders1RTT :: IOArray Bool Coder1RTT
coders :: IOArray EncryptionLevel Coder
ciphers :: IOArray EncryptionLevel Cipher
pendingQ :: Array EncryptionLevel (TVar [ReceivedPacket])
addressValidated :: TVar Bool
bytesRx :: TVar Int
bytesTx :: TVar Int
minIdleTimeout :: IORef Microseconds
migrationState :: TVar MigrationState
flowRx :: IORef Flow
flowTx :: TVar Flow
peerStreamId :: IORef Concurrency
myUniStreamId :: TVar Concurrency
myStreamId :: TVar Concurrency
streamTable :: IORef StreamTable
peerPacketNumber :: IORef Int
delayedAckCancel :: IORef (IO ())
delayedAckCount :: IORef Int
shared :: Shared
migrationQ :: MigrationQ
outputQ :: OutputQ
cryptoQ :: CryptoQ
inputQ :: InputQ
peerCIDDB :: TVar CIDDB
peerParameters :: IORef Parameters
myCIDDB :: IORef CIDDB
myParameters :: Parameters
origVersionInfo :: VersionInfo
quicVersionInfo :: IORef VersionInfo
roleInfo :: IORef RoleInfo
mainThreadId :: ThreadId
readers :: IORef (IO ())
udpSocket :: IORef UDPSocket
connRecvQ :: RecvQ
connRecv :: Recv
connSend :: Send
connHooks :: Hooks
connQLog :: QLogger
connDebugLog :: DebugLogger
connState :: ConnState
connLDCC :: Connection -> LDCC
decryptBuf :: Connection -> Buffer
encryptRes :: Connection -> SizedBuffer
encodeBuf :: Connection -> Buffer
connResources :: Connection -> IORef (IO ())
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])
addressValidated :: Connection -> TVar Bool
bytesRx :: Connection -> TVar Int
bytesTx :: Connection -> TVar Int
minIdleTimeout :: Connection -> IORef Microseconds
migrationState :: Connection -> TVar MigrationState
flowRx :: Connection -> IORef Flow
flowTx :: Connection -> TVar Flow
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
migrationQ :: Connection -> MigrationQ
outputQ :: Connection -> OutputQ
cryptoQ :: Connection -> CryptoQ
inputQ :: Connection -> InputQ
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
mainThreadId :: Connection -> ThreadId
readers :: Connection -> IORef (IO ())
udpSocket :: Connection -> IORef UDPSocket
connRecvQ :: Connection -> RecvQ
connRecv :: Connection -> Recv
connSend :: Connection -> Send
connHooks :: Connection -> Hooks
connQLog :: Connection -> QLogger
connDebugLog :: Connection -> DebugLogger
connState :: Connection -> ConnState
..} = forall (m :: * -> *) a. MonadIO m => STM a -> m a
atomically forall a b. (a -> b) -> a -> b
$ Flow -> Int
flowData forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a. TVar a -> STM a
readTVar TVar Flow
flowTx

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 Flow
TVar Concurrency
TVar MigrationState
TVar CIDDB
IORef Int
IORef (IO ())
IORef (Bool, Int)
IORef UDPSocket
IORef Microseconds
IORef VersionInfo
IORef Flow
IORef StreamTable
IORef AuthCIDs
IORef Parameters
IORef Concurrency
IORef Negotiated
IORef CIDDB
IORef RoleInfo
MigrationQ
OutputQ
CryptoQ
InputQ
VersionInfo
RecvQ
SizedBuffer
ConnState
Parameters
LDCC
Hooks
Shared
Send
DebugLogger
QLogger
connLDCC :: LDCC
decryptBuf :: Buffer
encryptRes :: SizedBuffer
encodeBuf :: Buffer
connResources :: IORef (IO ())
connPeerAuthCIDs :: IORef AuthCIDs
connMyAuthCIDs :: IORef AuthCIDs
negotiated :: IORef Negotiated
currentKeyPhase :: IORef (Bool, Int)
protectors :: IOArray EncryptionLevel Protector
coders1RTT :: IOArray Bool Coder1RTT
coders :: IOArray EncryptionLevel Coder
ciphers :: IOArray EncryptionLevel Cipher
pendingQ :: Array EncryptionLevel (TVar [ReceivedPacket])
addressValidated :: TVar Bool
bytesRx :: TVar Int
bytesTx :: TVar Int
minIdleTimeout :: IORef Microseconds
migrationState :: TVar MigrationState
flowRx :: IORef Flow
flowTx :: TVar Flow
peerStreamId :: IORef Concurrency
myUniStreamId :: TVar Concurrency
myStreamId :: TVar Concurrency
streamTable :: IORef StreamTable
peerPacketNumber :: IORef Int
delayedAckCancel :: IORef (IO ())
delayedAckCount :: IORef Int
shared :: Shared
migrationQ :: MigrationQ
outputQ :: OutputQ
cryptoQ :: CryptoQ
inputQ :: InputQ
peerCIDDB :: TVar CIDDB
peerParameters :: IORef Parameters
myCIDDB :: IORef CIDDB
myParameters :: Parameters
origVersionInfo :: VersionInfo
quicVersionInfo :: IORef VersionInfo
roleInfo :: IORef RoleInfo
mainThreadId :: ThreadId
readers :: IORef (IO ())
udpSocket :: IORef UDPSocket
connRecvQ :: RecvQ
connRecv :: Recv
connSend :: Send
connHooks :: Hooks
connQLog :: QLogger
connDebugLog :: DebugLogger
connState :: ConnState
connLDCC :: Connection -> LDCC
decryptBuf :: Connection -> Buffer
encryptRes :: Connection -> SizedBuffer
encodeBuf :: Connection -> Buffer
connResources :: Connection -> IORef (IO ())
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])
addressValidated :: Connection -> TVar Bool
bytesRx :: Connection -> TVar Int
bytesTx :: Connection -> TVar Int
minIdleTimeout :: Connection -> IORef Microseconds
migrationState :: Connection -> TVar MigrationState
flowRx :: Connection -> IORef Flow
flowTx :: Connection -> TVar Flow
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
migrationQ :: Connection -> MigrationQ
outputQ :: Connection -> OutputQ
cryptoQ :: Connection -> CryptoQ
inputQ :: Connection -> InputQ
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
mainThreadId :: Connection -> ThreadId
readers :: Connection -> IORef (IO ())
udpSocket :: Connection -> IORef UDPSocket
connRecvQ :: Connection -> RecvQ
connRecv :: Connection -> Recv
connSend :: Connection -> Send
connHooks :: Connection -> Hooks
connQLog :: Connection -> QLogger
connDebugLog :: Connection -> DebugLogger
connState :: Connection -> ConnState
..} Int
n = forall (m :: * -> *) a. MonadIO m => STM a -> m a
atomically forall a b. (a -> b) -> a -> b
$ forall a. TVar a -> (a -> a) -> STM ()
modifyTVar' TVar Flow
flowTx Flow -> Flow
set
  where
    set :: Flow -> Flow
set Flow
flow
      | Flow -> Int
flowMaxData Flow
flow forall a. Ord a => a -> a -> Bool
< Int
n = Flow
flow { flowMaxData :: Int
flowMaxData = Int
n }
      | Bool
otherwise            = Flow
flow

getTxMaxData :: Connection -> STM Int
getTxMaxData :: Connection -> STM Int
getTxMaxData 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 Flow
TVar Concurrency
TVar MigrationState
TVar CIDDB
IORef Int
IORef (IO ())
IORef (Bool, Int)
IORef UDPSocket
IORef Microseconds
IORef VersionInfo
IORef Flow
IORef StreamTable
IORef AuthCIDs
IORef Parameters
IORef Concurrency
IORef Negotiated
IORef CIDDB
IORef RoleInfo
MigrationQ
OutputQ
CryptoQ
InputQ
VersionInfo
RecvQ
SizedBuffer
ConnState
Parameters
LDCC
Hooks
Shared
Send
DebugLogger
QLogger
connLDCC :: LDCC
decryptBuf :: Buffer
encryptRes :: SizedBuffer
encodeBuf :: Buffer
connResources :: IORef (IO ())
connPeerAuthCIDs :: IORef AuthCIDs
connMyAuthCIDs :: IORef AuthCIDs
negotiated :: IORef Negotiated
currentKeyPhase :: IORef (Bool, Int)
protectors :: IOArray EncryptionLevel Protector
coders1RTT :: IOArray Bool Coder1RTT
coders :: IOArray EncryptionLevel Coder
ciphers :: IOArray EncryptionLevel Cipher
pendingQ :: Array EncryptionLevel (TVar [ReceivedPacket])
addressValidated :: TVar Bool
bytesRx :: TVar Int
bytesTx :: TVar Int
minIdleTimeout :: IORef Microseconds
migrationState :: TVar MigrationState
flowRx :: IORef Flow
flowTx :: TVar Flow
peerStreamId :: IORef Concurrency
myUniStreamId :: TVar Concurrency
myStreamId :: TVar Concurrency
streamTable :: IORef StreamTable
peerPacketNumber :: IORef Int
delayedAckCancel :: IORef (IO ())
delayedAckCount :: IORef Int
shared :: Shared
migrationQ :: MigrationQ
outputQ :: OutputQ
cryptoQ :: CryptoQ
inputQ :: InputQ
peerCIDDB :: TVar CIDDB
peerParameters :: IORef Parameters
myCIDDB :: IORef CIDDB
myParameters :: Parameters
origVersionInfo :: VersionInfo
quicVersionInfo :: IORef VersionInfo
roleInfo :: IORef RoleInfo
mainThreadId :: ThreadId
readers :: IORef (IO ())
udpSocket :: IORef UDPSocket
connRecvQ :: RecvQ
connRecv :: Recv
connSend :: Send
connHooks :: Hooks
connQLog :: QLogger
connDebugLog :: DebugLogger
connState :: ConnState
connLDCC :: Connection -> LDCC
decryptBuf :: Connection -> Buffer
encryptRes :: Connection -> SizedBuffer
encodeBuf :: Connection -> Buffer
connResources :: Connection -> IORef (IO ())
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])
addressValidated :: Connection -> TVar Bool
bytesRx :: Connection -> TVar Int
bytesTx :: Connection -> TVar Int
minIdleTimeout :: Connection -> IORef Microseconds
migrationState :: Connection -> TVar MigrationState
flowRx :: Connection -> IORef Flow
flowTx :: Connection -> TVar Flow
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
migrationQ :: Connection -> MigrationQ
outputQ :: Connection -> OutputQ
cryptoQ :: Connection -> CryptoQ
inputQ :: Connection -> InputQ
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
mainThreadId :: Connection -> ThreadId
readers :: Connection -> IORef (IO ())
udpSocket :: Connection -> IORef UDPSocket
connRecvQ :: Connection -> RecvQ
connRecv :: Connection -> Recv
connSend :: Connection -> Send
connHooks :: Connection -> Hooks
connQLog :: Connection -> QLogger
connDebugLog :: Connection -> DebugLogger
connState :: Connection -> ConnState
..} = Flow -> Int
flowMaxData forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a. TVar a -> STM a
readTVar TVar Flow
flowTx

----------------------------------------------------------------

addRxData :: Connection -> Int -> IO ()
addRxData :: Connection -> Int -> IO ()
addRxData 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 Flow
TVar Concurrency
TVar MigrationState
TVar CIDDB
IORef Int
IORef (IO ())
IORef (Bool, Int)
IORef UDPSocket
IORef Microseconds
IORef VersionInfo
IORef Flow
IORef StreamTable
IORef AuthCIDs
IORef Parameters
IORef Concurrency
IORef Negotiated
IORef CIDDB
IORef RoleInfo
MigrationQ
OutputQ
CryptoQ
InputQ
VersionInfo
RecvQ
SizedBuffer
ConnState
Parameters
LDCC
Hooks
Shared
Send
DebugLogger
QLogger
connLDCC :: LDCC
decryptBuf :: Buffer
encryptRes :: SizedBuffer
encodeBuf :: Buffer
connResources :: IORef (IO ())
connPeerAuthCIDs :: IORef AuthCIDs
connMyAuthCIDs :: IORef AuthCIDs
negotiated :: IORef Negotiated
currentKeyPhase :: IORef (Bool, Int)
protectors :: IOArray EncryptionLevel Protector
coders1RTT :: IOArray Bool Coder1RTT
coders :: IOArray EncryptionLevel Coder
ciphers :: IOArray EncryptionLevel Cipher
pendingQ :: Array EncryptionLevel (TVar [ReceivedPacket])
addressValidated :: TVar Bool
bytesRx :: TVar Int
bytesTx :: TVar Int
minIdleTimeout :: IORef Microseconds
migrationState :: TVar MigrationState
flowRx :: IORef Flow
flowTx :: TVar Flow
peerStreamId :: IORef Concurrency
myUniStreamId :: TVar Concurrency
myStreamId :: TVar Concurrency
streamTable :: IORef StreamTable
peerPacketNumber :: IORef Int
delayedAckCancel :: IORef (IO ())
delayedAckCount :: IORef Int
shared :: Shared
migrationQ :: MigrationQ
outputQ :: OutputQ
cryptoQ :: CryptoQ
inputQ :: InputQ
peerCIDDB :: TVar CIDDB
peerParameters :: IORef Parameters
myCIDDB :: IORef CIDDB
myParameters :: Parameters
origVersionInfo :: VersionInfo
quicVersionInfo :: IORef VersionInfo
roleInfo :: IORef RoleInfo
mainThreadId :: ThreadId
readers :: IORef (IO ())
udpSocket :: IORef UDPSocket
connRecvQ :: RecvQ
connRecv :: Recv
connSend :: Send
connHooks :: Hooks
connQLog :: QLogger
connDebugLog :: DebugLogger
connState :: ConnState
connLDCC :: Connection -> LDCC
decryptBuf :: Connection -> Buffer
encryptRes :: Connection -> SizedBuffer
encodeBuf :: Connection -> Buffer
connResources :: Connection -> IORef (IO ())
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])
addressValidated :: Connection -> TVar Bool
bytesRx :: Connection -> TVar Int
bytesTx :: Connection -> TVar Int
minIdleTimeout :: Connection -> IORef Microseconds
migrationState :: Connection -> TVar MigrationState
flowRx :: Connection -> IORef Flow
flowTx :: Connection -> TVar Flow
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
migrationQ :: Connection -> MigrationQ
outputQ :: Connection -> OutputQ
cryptoQ :: Connection -> CryptoQ
inputQ :: Connection -> InputQ
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
mainThreadId :: Connection -> ThreadId
readers :: Connection -> IORef (IO ())
udpSocket :: Connection -> IORef UDPSocket
connRecvQ :: Connection -> RecvQ
connRecv :: Connection -> Recv
connSend :: Connection -> Send
connHooks :: Connection -> Hooks
connQLog :: Connection -> QLogger
connDebugLog :: Connection -> DebugLogger
connState :: Connection -> ConnState
..} Int
n = forall a. IORef a -> (a -> a) -> IO ()
atomicModifyIORef'' IORef Flow
flowRx Flow -> Flow
add
  where
    add :: Flow -> Flow
add Flow
flow = Flow
flow { flowData :: Int
flowData = Flow -> Int
flowData Flow
flow forall a. Num a => a -> a -> a
+ Int
n }

getRxData :: Connection -> IO Int
getRxData :: Connection -> IO Int
getRxData 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 Flow
TVar Concurrency
TVar MigrationState
TVar CIDDB
IORef Int
IORef (IO ())
IORef (Bool, Int)
IORef UDPSocket
IORef Microseconds
IORef VersionInfo
IORef Flow
IORef StreamTable
IORef AuthCIDs
IORef Parameters
IORef Concurrency
IORef Negotiated
IORef CIDDB
IORef RoleInfo
MigrationQ
OutputQ
CryptoQ
InputQ
VersionInfo
RecvQ
SizedBuffer
ConnState
Parameters
LDCC
Hooks
Shared
Send
DebugLogger
QLogger
connLDCC :: LDCC
decryptBuf :: Buffer
encryptRes :: SizedBuffer
encodeBuf :: Buffer
connResources :: IORef (IO ())
connPeerAuthCIDs :: IORef AuthCIDs
connMyAuthCIDs :: IORef AuthCIDs
negotiated :: IORef Negotiated
currentKeyPhase :: IORef (Bool, Int)
protectors :: IOArray EncryptionLevel Protector
coders1RTT :: IOArray Bool Coder1RTT
coders :: IOArray EncryptionLevel Coder
ciphers :: IOArray EncryptionLevel Cipher
pendingQ :: Array EncryptionLevel (TVar [ReceivedPacket])
addressValidated :: TVar Bool
bytesRx :: TVar Int
bytesTx :: TVar Int
minIdleTimeout :: IORef Microseconds
migrationState :: TVar MigrationState
flowRx :: IORef Flow
flowTx :: TVar Flow
peerStreamId :: IORef Concurrency
myUniStreamId :: TVar Concurrency
myStreamId :: TVar Concurrency
streamTable :: IORef StreamTable
peerPacketNumber :: IORef Int
delayedAckCancel :: IORef (IO ())
delayedAckCount :: IORef Int
shared :: Shared
migrationQ :: MigrationQ
outputQ :: OutputQ
cryptoQ :: CryptoQ
inputQ :: InputQ
peerCIDDB :: TVar CIDDB
peerParameters :: IORef Parameters
myCIDDB :: IORef CIDDB
myParameters :: Parameters
origVersionInfo :: VersionInfo
quicVersionInfo :: IORef VersionInfo
roleInfo :: IORef RoleInfo
mainThreadId :: ThreadId
readers :: IORef (IO ())
udpSocket :: IORef UDPSocket
connRecvQ :: RecvQ
connRecv :: Recv
connSend :: Send
connHooks :: Hooks
connQLog :: QLogger
connDebugLog :: DebugLogger
connState :: ConnState
connLDCC :: Connection -> LDCC
decryptBuf :: Connection -> Buffer
encryptRes :: Connection -> SizedBuffer
encodeBuf :: Connection -> Buffer
connResources :: Connection -> IORef (IO ())
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])
addressValidated :: Connection -> TVar Bool
bytesRx :: Connection -> TVar Int
bytesTx :: Connection -> TVar Int
minIdleTimeout :: Connection -> IORef Microseconds
migrationState :: Connection -> TVar MigrationState
flowRx :: Connection -> IORef Flow
flowTx :: Connection -> TVar Flow
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
migrationQ :: Connection -> MigrationQ
outputQ :: Connection -> OutputQ
cryptoQ :: Connection -> CryptoQ
inputQ :: Connection -> InputQ
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
mainThreadId :: Connection -> ThreadId
readers :: Connection -> IORef (IO ())
udpSocket :: Connection -> IORef UDPSocket
connRecvQ :: Connection -> RecvQ
connRecv :: Connection -> Recv
connSend :: Connection -> Send
connHooks :: Connection -> Hooks
connQLog :: Connection -> QLogger
connDebugLog :: Connection -> DebugLogger
connState :: Connection -> ConnState
..} = Flow -> Int
flowData forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a. IORef a -> IO a
readIORef IORef Flow
flowRx

addRxMaxData :: Connection -> Int -> IO Int
addRxMaxData :: Connection -> Int -> IO Int
addRxMaxData 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 Flow
TVar Concurrency
TVar MigrationState
TVar CIDDB
IORef Int
IORef (IO ())
IORef (Bool, Int)
IORef UDPSocket
IORef Microseconds
IORef VersionInfo
IORef Flow
IORef StreamTable
IORef AuthCIDs
IORef Parameters
IORef Concurrency
IORef Negotiated
IORef CIDDB
IORef RoleInfo
MigrationQ
OutputQ
CryptoQ
InputQ
VersionInfo
RecvQ
SizedBuffer
ConnState
Parameters
LDCC
Hooks
Shared
Send
DebugLogger
QLogger
connLDCC :: LDCC
decryptBuf :: Buffer
encryptRes :: SizedBuffer
encodeBuf :: Buffer
connResources :: IORef (IO ())
connPeerAuthCIDs :: IORef AuthCIDs
connMyAuthCIDs :: IORef AuthCIDs
negotiated :: IORef Negotiated
currentKeyPhase :: IORef (Bool, Int)
protectors :: IOArray EncryptionLevel Protector
coders1RTT :: IOArray Bool Coder1RTT
coders :: IOArray EncryptionLevel Coder
ciphers :: IOArray EncryptionLevel Cipher
pendingQ :: Array EncryptionLevel (TVar [ReceivedPacket])
addressValidated :: TVar Bool
bytesRx :: TVar Int
bytesTx :: TVar Int
minIdleTimeout :: IORef Microseconds
migrationState :: TVar MigrationState
flowRx :: IORef Flow
flowTx :: TVar Flow
peerStreamId :: IORef Concurrency
myUniStreamId :: TVar Concurrency
myStreamId :: TVar Concurrency
streamTable :: IORef StreamTable
peerPacketNumber :: IORef Int
delayedAckCancel :: IORef (IO ())
delayedAckCount :: IORef Int
shared :: Shared
migrationQ :: MigrationQ
outputQ :: OutputQ
cryptoQ :: CryptoQ
inputQ :: InputQ
peerCIDDB :: TVar CIDDB
peerParameters :: IORef Parameters
myCIDDB :: IORef CIDDB
myParameters :: Parameters
origVersionInfo :: VersionInfo
quicVersionInfo :: IORef VersionInfo
roleInfo :: IORef RoleInfo
mainThreadId :: ThreadId
readers :: IORef (IO ())
udpSocket :: IORef UDPSocket
connRecvQ :: RecvQ
connRecv :: Recv
connSend :: Send
connHooks :: Hooks
connQLog :: QLogger
connDebugLog :: DebugLogger
connState :: ConnState
connLDCC :: Connection -> LDCC
decryptBuf :: Connection -> Buffer
encryptRes :: Connection -> SizedBuffer
encodeBuf :: Connection -> Buffer
connResources :: Connection -> IORef (IO ())
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])
addressValidated :: Connection -> TVar Bool
bytesRx :: Connection -> TVar Int
bytesTx :: Connection -> TVar Int
minIdleTimeout :: Connection -> IORef Microseconds
migrationState :: Connection -> TVar MigrationState
flowRx :: Connection -> IORef Flow
flowTx :: Connection -> TVar Flow
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
migrationQ :: Connection -> MigrationQ
outputQ :: Connection -> OutputQ
cryptoQ :: Connection -> CryptoQ
inputQ :: Connection -> InputQ
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
mainThreadId :: Connection -> ThreadId
readers :: Connection -> IORef (IO ())
udpSocket :: Connection -> IORef UDPSocket
connRecvQ :: Connection -> RecvQ
connRecv :: Connection -> Recv
connSend :: Connection -> Send
connHooks :: Connection -> Hooks
connQLog :: Connection -> QLogger
connDebugLog :: Connection -> DebugLogger
connState :: Connection -> ConnState
..} Int
n = forall a b. IORef a -> (a -> (a, b)) -> IO b
atomicModifyIORef' IORef Flow
flowRx Flow -> (Flow, Int)
add
  where
    add :: Flow -> (Flow, Int)
add Flow
flow = (Flow
flow { flowMaxData :: Int
flowMaxData = Int
m }, Int
m)
      where
        m :: Int
m = Flow -> Int
flowMaxData Flow
flow forall a. Num a => a -> a -> a
+ Int
n

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 Flow
TVar Concurrency
TVar MigrationState
TVar CIDDB
IORef Int
IORef (IO ())
IORef (Bool, Int)
IORef UDPSocket
IORef Microseconds
IORef VersionInfo
IORef Flow
IORef StreamTable
IORef AuthCIDs
IORef Parameters
IORef Concurrency
IORef Negotiated
IORef CIDDB
IORef RoleInfo
MigrationQ
OutputQ
CryptoQ
InputQ
VersionInfo
RecvQ
SizedBuffer
ConnState
Parameters
LDCC
Hooks
Shared
Send
DebugLogger
QLogger
connLDCC :: LDCC
decryptBuf :: Buffer
encryptRes :: SizedBuffer
encodeBuf :: Buffer
connResources :: IORef (IO ())
connPeerAuthCIDs :: IORef AuthCIDs
connMyAuthCIDs :: IORef AuthCIDs
negotiated :: IORef Negotiated
currentKeyPhase :: IORef (Bool, Int)
protectors :: IOArray EncryptionLevel Protector
coders1RTT :: IOArray Bool Coder1RTT
coders :: IOArray EncryptionLevel Coder
ciphers :: IOArray EncryptionLevel Cipher
pendingQ :: Array EncryptionLevel (TVar [ReceivedPacket])
addressValidated :: TVar Bool
bytesRx :: TVar Int
bytesTx :: TVar Int
minIdleTimeout :: IORef Microseconds
migrationState :: TVar MigrationState
flowRx :: IORef Flow
flowTx :: TVar Flow
peerStreamId :: IORef Concurrency
myUniStreamId :: TVar Concurrency
myStreamId :: TVar Concurrency
streamTable :: IORef StreamTable
peerPacketNumber :: IORef Int
delayedAckCancel :: IORef (IO ())
delayedAckCount :: IORef Int
shared :: Shared
migrationQ :: MigrationQ
outputQ :: OutputQ
cryptoQ :: CryptoQ
inputQ :: InputQ
peerCIDDB :: TVar CIDDB
peerParameters :: IORef Parameters
myCIDDB :: IORef CIDDB
myParameters :: Parameters
origVersionInfo :: VersionInfo
quicVersionInfo :: IORef VersionInfo
roleInfo :: IORef RoleInfo
mainThreadId :: ThreadId
readers :: IORef (IO ())
udpSocket :: IORef UDPSocket
connRecvQ :: RecvQ
connRecv :: Recv
connSend :: Send
connHooks :: Hooks
connQLog :: QLogger
connDebugLog :: DebugLogger
connState :: ConnState
connLDCC :: Connection -> LDCC
decryptBuf :: Connection -> Buffer
encryptRes :: Connection -> SizedBuffer
encodeBuf :: Connection -> Buffer
connResources :: Connection -> IORef (IO ())
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])
addressValidated :: Connection -> TVar Bool
bytesRx :: Connection -> TVar Int
bytesTx :: Connection -> TVar Int
minIdleTimeout :: Connection -> IORef Microseconds
migrationState :: Connection -> TVar MigrationState
flowRx :: Connection -> IORef Flow
flowTx :: Connection -> TVar Flow
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
migrationQ :: Connection -> MigrationQ
outputQ :: Connection -> OutputQ
cryptoQ :: Connection -> CryptoQ
inputQ :: Connection -> InputQ
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
mainThreadId :: Connection -> ThreadId
readers :: Connection -> IORef (IO ())
udpSocket :: Connection -> IORef UDPSocket
connRecvQ :: Connection -> RecvQ
connRecv :: Connection -> Recv
connSend :: Connection -> Send
connHooks :: Connection -> Hooks
connQLog :: Connection -> QLogger
connDebugLog :: Connection -> DebugLogger
connState :: Connection -> ConnState
..} = Flow -> Int
flowMaxData forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a. IORef a -> IO a
readIORef IORef Flow
flowRx

getRxDataWindow :: Connection -> IO Int
getRxDataWindow :: Connection -> IO Int
getRxDataWindow 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 Flow
TVar Concurrency
TVar MigrationState
TVar CIDDB
IORef Int
IORef (IO ())
IORef (Bool, Int)
IORef UDPSocket
IORef Microseconds
IORef VersionInfo
IORef Flow
IORef StreamTable
IORef AuthCIDs
IORef Parameters
IORef Concurrency
IORef Negotiated
IORef CIDDB
IORef RoleInfo
MigrationQ
OutputQ
CryptoQ
InputQ
VersionInfo
RecvQ
SizedBuffer
ConnState
Parameters
LDCC
Hooks
Shared
Send
DebugLogger
QLogger
connLDCC :: LDCC
decryptBuf :: Buffer
encryptRes :: SizedBuffer
encodeBuf :: Buffer
connResources :: IORef (IO ())
connPeerAuthCIDs :: IORef AuthCIDs
connMyAuthCIDs :: IORef AuthCIDs
negotiated :: IORef Negotiated
currentKeyPhase :: IORef (Bool, Int)
protectors :: IOArray EncryptionLevel Protector
coders1RTT :: IOArray Bool Coder1RTT
coders :: IOArray EncryptionLevel Coder
ciphers :: IOArray EncryptionLevel Cipher
pendingQ :: Array EncryptionLevel (TVar [ReceivedPacket])
addressValidated :: TVar Bool
bytesRx :: TVar Int
bytesTx :: TVar Int
minIdleTimeout :: IORef Microseconds
migrationState :: TVar MigrationState
flowRx :: IORef Flow
flowTx :: TVar Flow
peerStreamId :: IORef Concurrency
myUniStreamId :: TVar Concurrency
myStreamId :: TVar Concurrency
streamTable :: IORef StreamTable
peerPacketNumber :: IORef Int
delayedAckCancel :: IORef (IO ())
delayedAckCount :: IORef Int
shared :: Shared
migrationQ :: MigrationQ
outputQ :: OutputQ
cryptoQ :: CryptoQ
inputQ :: InputQ
peerCIDDB :: TVar CIDDB
peerParameters :: IORef Parameters
myCIDDB :: IORef CIDDB
myParameters :: Parameters
origVersionInfo :: VersionInfo
quicVersionInfo :: IORef VersionInfo
roleInfo :: IORef RoleInfo
mainThreadId :: ThreadId
readers :: IORef (IO ())
udpSocket :: IORef UDPSocket
connRecvQ :: RecvQ
connRecv :: Recv
connSend :: Send
connHooks :: Hooks
connQLog :: QLogger
connDebugLog :: DebugLogger
connState :: ConnState
connLDCC :: Connection -> LDCC
decryptBuf :: Connection -> Buffer
encryptRes :: Connection -> SizedBuffer
encodeBuf :: Connection -> Buffer
connResources :: Connection -> IORef (IO ())
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])
addressValidated :: Connection -> TVar Bool
bytesRx :: Connection -> TVar Int
bytesTx :: Connection -> TVar Int
minIdleTimeout :: Connection -> IORef Microseconds
migrationState :: Connection -> TVar MigrationState
flowRx :: Connection -> IORef Flow
flowTx :: Connection -> TVar Flow
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
migrationQ :: Connection -> MigrationQ
outputQ :: Connection -> OutputQ
cryptoQ :: Connection -> CryptoQ
inputQ :: Connection -> InputQ
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
mainThreadId :: Connection -> ThreadId
readers :: Connection -> IORef (IO ())
udpSocket :: Connection -> IORef UDPSocket
connRecvQ :: Connection -> RecvQ
connRecv :: Connection -> Recv
connSend :: Connection -> Send
connHooks :: Connection -> Hooks
connQLog :: Connection -> QLogger
connDebugLog :: Connection -> DebugLogger
connState :: Connection -> ConnState
..} = Flow -> Int
flowWindow forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a. IORef a -> IO a
readIORef IORef Flow
flowRx

----------------------------------------------------------------

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 Flow
TVar Concurrency
TVar MigrationState
TVar CIDDB
IORef Int
IORef (IO ())
IORef (Bool, Int)
IORef UDPSocket
IORef Microseconds
IORef VersionInfo
IORef Flow
IORef StreamTable
IORef AuthCIDs
IORef Parameters
IORef Concurrency
IORef Negotiated
IORef CIDDB
IORef RoleInfo
MigrationQ
OutputQ
CryptoQ
InputQ
VersionInfo
RecvQ
SizedBuffer
ConnState
Parameters
LDCC
Hooks
Shared
Send
DebugLogger
QLogger
connLDCC :: LDCC
decryptBuf :: Buffer
encryptRes :: SizedBuffer
encodeBuf :: Buffer
connResources :: IORef (IO ())
connPeerAuthCIDs :: IORef AuthCIDs
connMyAuthCIDs :: IORef AuthCIDs
negotiated :: IORef Negotiated
currentKeyPhase :: IORef (Bool, Int)
protectors :: IOArray EncryptionLevel Protector
coders1RTT :: IOArray Bool Coder1RTT
coders :: IOArray EncryptionLevel Coder
ciphers :: IOArray EncryptionLevel Cipher
pendingQ :: Array EncryptionLevel (TVar [ReceivedPacket])
addressValidated :: TVar Bool
bytesRx :: TVar Int
bytesTx :: TVar Int
minIdleTimeout :: IORef Microseconds
migrationState :: TVar MigrationState
flowRx :: IORef Flow
flowTx :: TVar Flow
peerStreamId :: IORef Concurrency
myUniStreamId :: TVar Concurrency
myStreamId :: TVar Concurrency
streamTable :: IORef StreamTable
peerPacketNumber :: IORef Int
delayedAckCancel :: IORef (IO ())
delayedAckCount :: IORef Int
shared :: Shared
migrationQ :: MigrationQ
outputQ :: OutputQ
cryptoQ :: CryptoQ
inputQ :: InputQ
peerCIDDB :: TVar CIDDB
peerParameters :: IORef Parameters
myCIDDB :: IORef CIDDB
myParameters :: Parameters
origVersionInfo :: VersionInfo
quicVersionInfo :: IORef VersionInfo
roleInfo :: IORef RoleInfo
mainThreadId :: ThreadId
readers :: IORef (IO ())
udpSocket :: IORef UDPSocket
connRecvQ :: RecvQ
connRecv :: Recv
connSend :: Send
connHooks :: Hooks
connQLog :: QLogger
connDebugLog :: DebugLogger
connState :: ConnState
connLDCC :: Connection -> LDCC
decryptBuf :: Connection -> Buffer
encryptRes :: Connection -> SizedBuffer
encodeBuf :: Connection -> Buffer
connResources :: Connection -> IORef (IO ())
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])
addressValidated :: Connection -> TVar Bool
bytesRx :: Connection -> TVar Int
bytesTx :: Connection -> TVar Int
minIdleTimeout :: Connection -> IORef Microseconds
migrationState :: Connection -> TVar MigrationState
flowRx :: Connection -> IORef Flow
flowTx :: Connection -> TVar Flow
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
migrationQ :: Connection -> MigrationQ
outputQ :: Connection -> OutputQ
cryptoQ :: Connection -> CryptoQ
inputQ :: Connection -> InputQ
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
mainThreadId :: Connection -> ThreadId
readers :: Connection -> IORef (IO ())
udpSocket :: Connection -> IORef UDPSocket
connRecvQ :: Connection -> RecvQ
connRecv :: Connection -> Recv
connSend :: Connection -> Send
connHooks :: Connection -> Hooks
connQLog :: Connection -> QLogger
connDebugLog :: Connection -> DebugLogger
connState :: Connection -> ConnState
..} Int
n = forall (m :: * -> *) a. MonadIO m => STM a -> m a
atomically forall a b. (a -> b) -> a -> b
$ forall a. TVar a -> (a -> a) -> STM ()
modifyTVar' TVar Int
bytesTx (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 Flow
TVar Concurrency
TVar MigrationState
TVar CIDDB
IORef Int
IORef (IO ())
IORef (Bool, Int)
IORef UDPSocket
IORef Microseconds
IORef VersionInfo
IORef Flow
IORef StreamTable
IORef AuthCIDs
IORef Parameters
IORef Concurrency
IORef Negotiated
IORef CIDDB
IORef RoleInfo
MigrationQ
OutputQ
CryptoQ
InputQ
VersionInfo
RecvQ
SizedBuffer
ConnState
Parameters
LDCC
Hooks
Shared
Send
DebugLogger
QLogger
connLDCC :: LDCC
decryptBuf :: Buffer
encryptRes :: SizedBuffer
encodeBuf :: Buffer
connResources :: IORef (IO ())
connPeerAuthCIDs :: IORef AuthCIDs
connMyAuthCIDs :: IORef AuthCIDs
negotiated :: IORef Negotiated
currentKeyPhase :: IORef (Bool, Int)
protectors :: IOArray EncryptionLevel Protector
coders1RTT :: IOArray Bool Coder1RTT
coders :: IOArray EncryptionLevel Coder
ciphers :: IOArray EncryptionLevel Cipher
pendingQ :: Array EncryptionLevel (TVar [ReceivedPacket])
addressValidated :: TVar Bool
bytesRx :: TVar Int
bytesTx :: TVar Int
minIdleTimeout :: IORef Microseconds
migrationState :: TVar MigrationState
flowRx :: IORef Flow
flowTx :: TVar Flow
peerStreamId :: IORef Concurrency
myUniStreamId :: TVar Concurrency
myStreamId :: TVar Concurrency
streamTable :: IORef StreamTable
peerPacketNumber :: IORef Int
delayedAckCancel :: IORef (IO ())
delayedAckCount :: IORef Int
shared :: Shared
migrationQ :: MigrationQ
outputQ :: OutputQ
cryptoQ :: CryptoQ
inputQ :: InputQ
peerCIDDB :: TVar CIDDB
peerParameters :: IORef Parameters
myCIDDB :: IORef CIDDB
myParameters :: Parameters
origVersionInfo :: VersionInfo
quicVersionInfo :: IORef VersionInfo
roleInfo :: IORef RoleInfo
mainThreadId :: ThreadId
readers :: IORef (IO ())
udpSocket :: IORef UDPSocket
connRecvQ :: RecvQ
connRecv :: Recv
connSend :: Send
connHooks :: Hooks
connQLog :: QLogger
connDebugLog :: DebugLogger
connState :: ConnState
connLDCC :: Connection -> LDCC
decryptBuf :: Connection -> Buffer
encryptRes :: Connection -> SizedBuffer
encodeBuf :: Connection -> Buffer
connResources :: Connection -> IORef (IO ())
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])
addressValidated :: Connection -> TVar Bool
bytesRx :: Connection -> TVar Int
bytesTx :: Connection -> TVar Int
minIdleTimeout :: Connection -> IORef Microseconds
migrationState :: Connection -> TVar MigrationState
flowRx :: Connection -> IORef Flow
flowTx :: Connection -> TVar Flow
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
migrationQ :: Connection -> MigrationQ
outputQ :: Connection -> OutputQ
cryptoQ :: Connection -> CryptoQ
inputQ :: Connection -> InputQ
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
mainThreadId :: Connection -> ThreadId
readers :: Connection -> IORef (IO ())
udpSocket :: Connection -> IORef UDPSocket
connRecvQ :: Connection -> RecvQ
connRecv :: Connection -> Recv
connSend :: Connection -> Send
connHooks :: Connection -> Hooks
connQLog :: Connection -> QLogger
connDebugLog :: Connection -> DebugLogger
connState :: Connection -> ConnState
..} = forall (m :: * -> *) a. MonadIO m => TVar a -> m 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 Flow
TVar Concurrency
TVar MigrationState
TVar CIDDB
IORef Int
IORef (IO ())
IORef (Bool, Int)
IORef UDPSocket
IORef Microseconds
IORef VersionInfo
IORef Flow
IORef StreamTable
IORef AuthCIDs
IORef Parameters
IORef Concurrency
IORef Negotiated
IORef CIDDB
IORef RoleInfo
MigrationQ
OutputQ
CryptoQ
InputQ
VersionInfo
RecvQ
SizedBuffer
ConnState
Parameters
LDCC
Hooks
Shared
Send
DebugLogger
QLogger
connLDCC :: LDCC
decryptBuf :: Buffer
encryptRes :: SizedBuffer
encodeBuf :: Buffer
connResources :: IORef (IO ())
connPeerAuthCIDs :: IORef AuthCIDs
connMyAuthCIDs :: IORef AuthCIDs
negotiated :: IORef Negotiated
currentKeyPhase :: IORef (Bool, Int)
protectors :: IOArray EncryptionLevel Protector
coders1RTT :: IOArray Bool Coder1RTT
coders :: IOArray EncryptionLevel Coder
ciphers :: IOArray EncryptionLevel Cipher
pendingQ :: Array EncryptionLevel (TVar [ReceivedPacket])
addressValidated :: TVar Bool
bytesRx :: TVar Int
bytesTx :: TVar Int
minIdleTimeout :: IORef Microseconds
migrationState :: TVar MigrationState
flowRx :: IORef Flow
flowTx :: TVar Flow
peerStreamId :: IORef Concurrency
myUniStreamId :: TVar Concurrency
myStreamId :: TVar Concurrency
streamTable :: IORef StreamTable
peerPacketNumber :: IORef Int
delayedAckCancel :: IORef (IO ())
delayedAckCount :: IORef Int
shared :: Shared
migrationQ :: MigrationQ
outputQ :: OutputQ
cryptoQ :: CryptoQ
inputQ :: InputQ
peerCIDDB :: TVar CIDDB
peerParameters :: IORef Parameters
myCIDDB :: IORef CIDDB
myParameters :: Parameters
origVersionInfo :: VersionInfo
quicVersionInfo :: IORef VersionInfo
roleInfo :: IORef RoleInfo
mainThreadId :: ThreadId
readers :: IORef (IO ())
udpSocket :: IORef UDPSocket
connRecvQ :: RecvQ
connRecv :: Recv
connSend :: Send
connHooks :: Hooks
connQLog :: QLogger
connDebugLog :: DebugLogger
connState :: ConnState
connLDCC :: Connection -> LDCC
decryptBuf :: Connection -> Buffer
encryptRes :: Connection -> SizedBuffer
encodeBuf :: Connection -> Buffer
connResources :: Connection -> IORef (IO ())
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])
addressValidated :: Connection -> TVar Bool
bytesRx :: Connection -> TVar Int
bytesTx :: Connection -> TVar Int
minIdleTimeout :: Connection -> IORef Microseconds
migrationState :: Connection -> TVar MigrationState
flowRx :: Connection -> IORef Flow
flowTx :: Connection -> TVar Flow
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
migrationQ :: Connection -> MigrationQ
outputQ :: Connection -> OutputQ
cryptoQ :: Connection -> CryptoQ
inputQ :: Connection -> InputQ
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
mainThreadId :: Connection -> ThreadId
readers :: Connection -> IORef (IO ())
udpSocket :: Connection -> IORef UDPSocket
connRecvQ :: Connection -> RecvQ
connRecv :: Connection -> Recv
connSend :: Connection -> Send
connHooks :: Connection -> Hooks
connQLog :: Connection -> QLogger
connDebugLog :: Connection -> DebugLogger
connState :: Connection -> ConnState
..} Int
n = forall (m :: * -> *) a. MonadIO m => STM a -> m a
atomically forall a b. (a -> b) -> a -> b
$ forall a. TVar a -> (a -> a) -> STM ()
modifyTVar' TVar Int
bytesRx (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 Flow
TVar Concurrency
TVar MigrationState
TVar CIDDB
IORef Int
IORef (IO ())
IORef (Bool, Int)
IORef UDPSocket
IORef Microseconds
IORef VersionInfo
IORef Flow
IORef StreamTable
IORef AuthCIDs
IORef Parameters
IORef Concurrency
IORef Negotiated
IORef CIDDB
IORef RoleInfo
MigrationQ
OutputQ
CryptoQ
InputQ
VersionInfo
RecvQ
SizedBuffer
ConnState
Parameters
LDCC
Hooks
Shared
Send
DebugLogger
QLogger
connLDCC :: LDCC
decryptBuf :: Buffer
encryptRes :: SizedBuffer
encodeBuf :: Buffer
connResources :: IORef (IO ())
connPeerAuthCIDs :: IORef AuthCIDs
connMyAuthCIDs :: IORef AuthCIDs
negotiated :: IORef Negotiated
currentKeyPhase :: IORef (Bool, Int)
protectors :: IOArray EncryptionLevel Protector
coders1RTT :: IOArray Bool Coder1RTT
coders :: IOArray EncryptionLevel Coder
ciphers :: IOArray EncryptionLevel Cipher
pendingQ :: Array EncryptionLevel (TVar [ReceivedPacket])
addressValidated :: TVar Bool
bytesRx :: TVar Int
bytesTx :: TVar Int
minIdleTimeout :: IORef Microseconds
migrationState :: TVar MigrationState
flowRx :: IORef Flow
flowTx :: TVar Flow
peerStreamId :: IORef Concurrency
myUniStreamId :: TVar Concurrency
myStreamId :: TVar Concurrency
streamTable :: IORef StreamTable
peerPacketNumber :: IORef Int
delayedAckCancel :: IORef (IO ())
delayedAckCount :: IORef Int
shared :: Shared
migrationQ :: MigrationQ
outputQ :: OutputQ
cryptoQ :: CryptoQ
inputQ :: InputQ
peerCIDDB :: TVar CIDDB
peerParameters :: IORef Parameters
myCIDDB :: IORef CIDDB
myParameters :: Parameters
origVersionInfo :: VersionInfo
quicVersionInfo :: IORef VersionInfo
roleInfo :: IORef RoleInfo
mainThreadId :: ThreadId
readers :: IORef (IO ())
udpSocket :: IORef UDPSocket
connRecvQ :: RecvQ
connRecv :: Recv
connSend :: Send
connHooks :: Hooks
connQLog :: QLogger
connDebugLog :: DebugLogger
connState :: ConnState
connLDCC :: Connection -> LDCC
decryptBuf :: Connection -> Buffer
encryptRes :: Connection -> SizedBuffer
encodeBuf :: Connection -> Buffer
connResources :: Connection -> IORef (IO ())
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])
addressValidated :: Connection -> TVar Bool
bytesRx :: Connection -> TVar Int
bytesTx :: Connection -> TVar Int
minIdleTimeout :: Connection -> IORef Microseconds
migrationState :: Connection -> TVar MigrationState
flowRx :: Connection -> IORef Flow
flowTx :: Connection -> TVar Flow
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
migrationQ :: Connection -> MigrationQ
outputQ :: Connection -> OutputQ
cryptoQ :: Connection -> CryptoQ
inputQ :: Connection -> InputQ
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
mainThreadId :: Connection -> ThreadId
readers :: Connection -> IORef (IO ())
udpSocket :: Connection -> IORef UDPSocket
connRecvQ :: Connection -> RecvQ
connRecv :: Connection -> Recv
connSend :: Connection -> Send
connHooks :: Connection -> Hooks
connQLog :: Connection -> QLogger
connDebugLog :: Connection -> DebugLogger
connState :: Connection -> ConnState
..} = forall (m :: * -> *) a. MonadIO m => TVar a -> m 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 Flow
TVar Concurrency
TVar MigrationState
TVar CIDDB
IORef Int
IORef (IO ())
IORef (Bool, Int)
IORef UDPSocket
IORef Microseconds
IORef VersionInfo
IORef Flow
IORef StreamTable
IORef AuthCIDs
IORef Parameters
IORef Concurrency
IORef Negotiated
IORef CIDDB
IORef RoleInfo
MigrationQ
OutputQ
CryptoQ
InputQ
VersionInfo
RecvQ
SizedBuffer
ConnState
Parameters
LDCC
Hooks
Shared
Send
DebugLogger
QLogger
connLDCC :: LDCC
decryptBuf :: Buffer
encryptRes :: SizedBuffer
encodeBuf :: Buffer
connResources :: IORef (IO ())
connPeerAuthCIDs :: IORef AuthCIDs
connMyAuthCIDs :: IORef AuthCIDs
negotiated :: IORef Negotiated
currentKeyPhase :: IORef (Bool, Int)
protectors :: IOArray EncryptionLevel Protector
coders1RTT :: IOArray Bool Coder1RTT
coders :: IOArray EncryptionLevel Coder
ciphers :: IOArray EncryptionLevel Cipher
pendingQ :: Array EncryptionLevel (TVar [ReceivedPacket])
addressValidated :: TVar Bool
bytesRx :: TVar Int
bytesTx :: TVar Int
minIdleTimeout :: IORef Microseconds
migrationState :: TVar MigrationState
flowRx :: IORef Flow
flowTx :: TVar Flow
peerStreamId :: IORef Concurrency
myUniStreamId :: TVar Concurrency
myStreamId :: TVar Concurrency
streamTable :: IORef StreamTable
peerPacketNumber :: IORef Int
delayedAckCancel :: IORef (IO ())
delayedAckCount :: IORef Int
shared :: Shared
migrationQ :: MigrationQ
outputQ :: OutputQ
cryptoQ :: CryptoQ
inputQ :: InputQ
peerCIDDB :: TVar CIDDB
peerParameters :: IORef Parameters
myCIDDB :: IORef CIDDB
myParameters :: Parameters
origVersionInfo :: VersionInfo
quicVersionInfo :: IORef VersionInfo
roleInfo :: IORef RoleInfo
mainThreadId :: ThreadId
readers :: IORef (IO ())
udpSocket :: IORef UDPSocket
connRecvQ :: RecvQ
connRecv :: Recv
connSend :: Send
connHooks :: Hooks
connQLog :: QLogger
connDebugLog :: DebugLogger
connState :: ConnState
connLDCC :: Connection -> LDCC
decryptBuf :: Connection -> Buffer
encryptRes :: Connection -> SizedBuffer
encodeBuf :: Connection -> Buffer
connResources :: Connection -> IORef (IO ())
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])
addressValidated :: Connection -> TVar Bool
bytesRx :: Connection -> TVar Int
bytesTx :: Connection -> TVar Int
minIdleTimeout :: Connection -> IORef Microseconds
migrationState :: Connection -> TVar MigrationState
flowRx :: Connection -> IORef Flow
flowTx :: Connection -> TVar Flow
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
migrationQ :: Connection -> MigrationQ
outputQ :: Connection -> OutputQ
cryptoQ :: Connection -> CryptoQ
inputQ :: Connection -> InputQ
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
mainThreadId :: Connection -> ThreadId
readers :: Connection -> IORef (IO ())
udpSocket :: Connection -> IORef UDPSocket
connRecvQ :: Connection -> RecvQ
connRecv :: Connection -> Recv
connSend :: Connection -> Send
connHooks :: Connection -> Hooks
connQLog :: Connection -> QLogger
connDebugLog :: Connection -> DebugLogger
connState :: Connection -> ConnState
..} = forall (m :: * -> *) a. MonadIO m => STM a -> m a
atomically forall a b. (a -> b) -> a -> b
$ forall a. TVar a -> a -> STM ()
writeTVar TVar Bool
addressValidated Bool
True

-- Three times rule for anti amplification
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 Flow
TVar Concurrency
TVar MigrationState
TVar CIDDB
IORef Int
IORef (IO ())
IORef (Bool, Int)
IORef UDPSocket
IORef Microseconds
IORef VersionInfo
IORef Flow
IORef StreamTable
IORef AuthCIDs
IORef Parameters
IORef Concurrency
IORef Negotiated
IORef CIDDB
IORef RoleInfo
MigrationQ
OutputQ
CryptoQ
InputQ
VersionInfo
RecvQ
SizedBuffer
ConnState
Parameters
LDCC
Hooks
Shared
Send
DebugLogger
QLogger
connLDCC :: LDCC
decryptBuf :: Buffer
encryptRes :: SizedBuffer
encodeBuf :: Buffer
connResources :: IORef (IO ())
connPeerAuthCIDs :: IORef AuthCIDs
connMyAuthCIDs :: IORef AuthCIDs
negotiated :: IORef Negotiated
currentKeyPhase :: IORef (Bool, Int)
protectors :: IOArray EncryptionLevel Protector
coders1RTT :: IOArray Bool Coder1RTT
coders :: IOArray EncryptionLevel Coder
ciphers :: IOArray EncryptionLevel Cipher
pendingQ :: Array EncryptionLevel (TVar [ReceivedPacket])
addressValidated :: TVar Bool
bytesRx :: TVar Int
bytesTx :: TVar Int
minIdleTimeout :: IORef Microseconds
migrationState :: TVar MigrationState
flowRx :: IORef Flow
flowTx :: TVar Flow
peerStreamId :: IORef Concurrency
myUniStreamId :: TVar Concurrency
myStreamId :: TVar Concurrency
streamTable :: IORef StreamTable
peerPacketNumber :: IORef Int
delayedAckCancel :: IORef (IO ())
delayedAckCount :: IORef Int
shared :: Shared
migrationQ :: MigrationQ
outputQ :: OutputQ
cryptoQ :: CryptoQ
inputQ :: InputQ
peerCIDDB :: TVar CIDDB
peerParameters :: IORef Parameters
myCIDDB :: IORef CIDDB
myParameters :: Parameters
origVersionInfo :: VersionInfo
quicVersionInfo :: IORef VersionInfo
roleInfo :: IORef RoleInfo
mainThreadId :: ThreadId
readers :: IORef (IO ())
udpSocket :: IORef UDPSocket
connRecvQ :: RecvQ
connRecv :: Recv
connSend :: Send
connHooks :: Hooks
connQLog :: QLogger
connDebugLog :: DebugLogger
connState :: ConnState
connLDCC :: Connection -> LDCC
decryptBuf :: Connection -> Buffer
encryptRes :: Connection -> SizedBuffer
encodeBuf :: Connection -> Buffer
connResources :: Connection -> IORef (IO ())
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])
addressValidated :: Connection -> TVar Bool
bytesRx :: Connection -> TVar Int
bytesTx :: Connection -> TVar Int
minIdleTimeout :: Connection -> IORef Microseconds
migrationState :: Connection -> TVar MigrationState
flowRx :: Connection -> IORef Flow
flowTx :: Connection -> TVar Flow
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
migrationQ :: Connection -> MigrationQ
outputQ :: Connection -> OutputQ
cryptoQ :: Connection -> CryptoQ
inputQ :: Connection -> InputQ
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
mainThreadId :: Connection -> ThreadId
readers :: Connection -> IORef (IO ())
udpSocket :: Connection -> IORef UDPSocket
connRecvQ :: Connection -> RecvQ
connRecv :: Connection -> Recv
connSend :: Connection -> Send
connHooks :: Connection -> Hooks
connQLog :: Connection -> QLogger
connDebugLog :: Connection -> DebugLogger
connState :: Connection -> ConnState
..} Int
siz = do
    Bool
ok <- Connection -> Int -> IO Bool
checkAntiAmplificationFree Connection
conn Int
siz
    forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless Bool
ok forall a b. (a -> b) -> a -> b
$ do
        LDCC -> IO ()
beforeAntiAmp LDCC
connLDCC
        forall (m :: * -> *) a. MonadIO m => STM a -> m a
atomically (Connection -> Int -> STM Bool
checkAntiAmplificationFreeSTM Connection
conn Int
siz forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Bool -> STM ()
checkSTM)
        -- setLossDetectionTimer is called eventually.

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 Flow
TVar Concurrency
TVar MigrationState
TVar CIDDB
IORef Int
IORef (IO ())
IORef (Bool, Int)
IORef UDPSocket
IORef Microseconds
IORef VersionInfo
IORef Flow
IORef StreamTable
IORef AuthCIDs
IORef Parameters
IORef Concurrency
IORef Negotiated
IORef CIDDB
IORef RoleInfo
MigrationQ
OutputQ
CryptoQ
InputQ
VersionInfo
RecvQ
SizedBuffer
ConnState
Parameters
LDCC
Hooks
Shared
Send
DebugLogger
QLogger
connLDCC :: LDCC
decryptBuf :: Buffer
encryptRes :: SizedBuffer
encodeBuf :: Buffer
connResources :: IORef (IO ())
connPeerAuthCIDs :: IORef AuthCIDs
connMyAuthCIDs :: IORef AuthCIDs
negotiated :: IORef Negotiated
currentKeyPhase :: IORef (Bool, Int)
protectors :: IOArray EncryptionLevel Protector
coders1RTT :: IOArray Bool Coder1RTT
coders :: IOArray EncryptionLevel Coder
ciphers :: IOArray EncryptionLevel Cipher
pendingQ :: Array EncryptionLevel (TVar [ReceivedPacket])
addressValidated :: TVar Bool
bytesRx :: TVar Int
bytesTx :: TVar Int
minIdleTimeout :: IORef Microseconds
migrationState :: TVar MigrationState
flowRx :: IORef Flow
flowTx :: TVar Flow
peerStreamId :: IORef Concurrency
myUniStreamId :: TVar Concurrency
myStreamId :: TVar Concurrency
streamTable :: IORef StreamTable
peerPacketNumber :: IORef Int
delayedAckCancel :: IORef (IO ())
delayedAckCount :: IORef Int
shared :: Shared
migrationQ :: MigrationQ
outputQ :: OutputQ
cryptoQ :: CryptoQ
inputQ :: InputQ
peerCIDDB :: TVar CIDDB
peerParameters :: IORef Parameters
myCIDDB :: IORef CIDDB
myParameters :: Parameters
origVersionInfo :: VersionInfo
quicVersionInfo :: IORef VersionInfo
roleInfo :: IORef RoleInfo
mainThreadId :: ThreadId
readers :: IORef (IO ())
udpSocket :: IORef UDPSocket
connRecvQ :: RecvQ
connRecv :: Recv
connSend :: Send
connHooks :: Hooks
connQLog :: QLogger
connDebugLog :: DebugLogger
connState :: ConnState
connLDCC :: Connection -> LDCC
decryptBuf :: Connection -> Buffer
encryptRes :: Connection -> SizedBuffer
encodeBuf :: Connection -> Buffer
connResources :: Connection -> IORef (IO ())
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])
addressValidated :: Connection -> TVar Bool
bytesRx :: Connection -> TVar Int
bytesTx :: Connection -> TVar Int
minIdleTimeout :: Connection -> IORef Microseconds
migrationState :: Connection -> TVar MigrationState
flowRx :: Connection -> IORef Flow
flowTx :: Connection -> TVar Flow
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
migrationQ :: Connection -> MigrationQ
outputQ :: Connection -> OutputQ
cryptoQ :: Connection -> CryptoQ
inputQ :: Connection -> InputQ
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
mainThreadId :: Connection -> ThreadId
readers :: Connection -> IORef (IO ())
udpSocket :: Connection -> IORef UDPSocket
connRecvQ :: Connection -> RecvQ
connRecv :: Connection -> Recv
connSend :: Connection -> Send
connHooks :: Connection -> Hooks
connQLog :: Connection -> QLogger
connDebugLog :: Connection -> DebugLogger
connState :: Connection -> ConnState
..} Int
siz = do
    Bool
validated <- forall a. TVar a -> STM a
readTVar TVar Bool
addressValidated
    if Bool
validated then
        forall (m :: * -> *) a. Monad m => a -> m a
return Bool
True
      else do
        Int
tx <- forall a. TVar a -> STM a
readTVar TVar Int
bytesTx
        Int
rx <- forall a. TVar a -> STM a
readTVar TVar Int
bytesRx
        forall (m :: * -> *) a. Monad m => a -> m a
return (Int
tx forall a. Num a => a -> a -> a
+ Int
siz forall a. Ord a => a -> a -> Bool
<= Int
3 forall a. Num a => a -> a -> a
* Int
rx)

checkAntiAmplificationFree :: Connection -> Int -> IO Bool
checkAntiAmplificationFree :: Connection -> Int -> IO Bool
checkAntiAmplificationFree Connection
conn Int
siz =
    forall (m :: * -> *) a. MonadIO m => STM a -> m a
atomically forall a b. (a -> b) -> a -> b
$ Connection -> Int -> STM Bool
checkAntiAmplificationFreeSTM Connection
conn Int
siz