{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE TupleSections #-}

module Network.QUIC.Connection.Misc (
    setVersionInfo,
    getVersionInfo,
    setVersion,
    getVersion,
    getOriginalVersion,
    getSocket,
    setSocket,
    clearSocket,
    getPeerAuthCIDs,
    setPeerAuthCIDs,
    getClientDstCID,
    getMyParameters,
    getPeerParameters,
    setPeerParameters,
    delayedAck,
    resetDealyedAck,
    setMaxPacketSize,
    addReader,
    killReaders,
    addResource,
    freeResources,
    readMinIdleTimeout,
    setMinIdleTimeout,
    sendFrames,
    sendFramesLim,
    closeConnection,
    abortConnection,
) where

import Network.UDP
import System.Mem.Weak
import UnliftIO.Concurrent
import qualified UnliftIO.Exception as E

import Network.QUIC.Connection.Queue
import Network.QUIC.Connection.Timeout
import Network.QUIC.Connection.Types
import Network.QUIC.Connector
import Network.QUIC.Imports
import Network.QUIC.Parameters
import Network.QUIC.Types

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

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

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

setVersion :: Connection -> Version -> IO ()
setVersion :: Connection -> Version -> IO ()
setVersion Connection{Recv
Buffer
Array EncryptionLevel (TVar [ReceivedPacket])
IOArray Bool Coder1RTT
IOArray EncryptionLevel Cipher
IOArray EncryptionLevel Protector
IOArray EncryptionLevel Coder
ThreadId
TVar Bool
TVar Int
TVar TxFlow
TVar Concurrency
TVar MigrationState
TVar CIDDB
IORef Int
IORef (IO ())
IORef (Bool, Int)
IORef RxFlow
IORef UDPSocket
IORef Microseconds
IORef VersionInfo
IORef AuthCIDs
IORef Parameters
IORef StreamTable
IORef Concurrency
IORef Negotiated
IORef CIDDB
IORef RoleInfo
Rate
OutputQLim
MigrationQ
OutputQ
CryptoQ
InputQ
VersionInfo
RecvQ
SizedBuffer
ConnState
Parameters
LDCC
Hooks
Shared
Send
DebugLogger
QLogger
connState :: Connection -> ConnState
connDebugLog :: Connection -> DebugLogger
connQLog :: Connection -> QLogger
connHooks :: Connection -> Hooks
connSend :: Connection -> Send
connRecv :: Connection -> Recv
connRecvQ :: Connection -> RecvQ
udpSocket :: Connection -> IORef UDPSocket
readers :: Connection -> IORef (IO ())
mainThreadId :: Connection -> ThreadId
controlRate :: Connection -> Rate
roleInfo :: Connection -> IORef RoleInfo
quicVersionInfo :: Connection -> IORef VersionInfo
origVersionInfo :: Connection -> VersionInfo
myParameters :: Connection -> Parameters
myCIDDB :: Connection -> IORef CIDDB
peerParameters :: Connection -> IORef Parameters
peerCIDDB :: Connection -> TVar CIDDB
inputQ :: Connection -> InputQ
cryptoQ :: Connection -> CryptoQ
outputQ :: Connection -> OutputQ
outputQLim :: Connection -> OutputQLim
migrationQ :: Connection -> MigrationQ
shared :: Connection -> Shared
delayedAckCount :: Connection -> IORef Int
delayedAckCancel :: Connection -> IORef (IO ())
peerPacketNumber :: Connection -> IORef Int
streamTable :: Connection -> IORef StreamTable
myStreamId :: Connection -> TVar Concurrency
myUniStreamId :: Connection -> TVar Concurrency
peerStreamId :: Connection -> IORef Concurrency
peerUniStreamId :: Connection -> IORef Concurrency
flowTx :: Connection -> TVar TxFlow
flowRx :: Connection -> IORef RxFlow
migrationState :: Connection -> TVar MigrationState
minIdleTimeout :: Connection -> IORef Microseconds
bytesTx :: Connection -> TVar Int
bytesRx :: Connection -> TVar Int
addressValidated :: Connection -> TVar Bool
pendingQ :: Connection -> Array EncryptionLevel (TVar [ReceivedPacket])
ciphers :: Connection -> IOArray EncryptionLevel Cipher
coders :: Connection -> IOArray EncryptionLevel Coder
coders1RTT :: Connection -> IOArray Bool Coder1RTT
protectors :: Connection -> IOArray EncryptionLevel Protector
currentKeyPhase :: Connection -> IORef (Bool, Int)
negotiated :: Connection -> IORef Negotiated
connMyAuthCIDs :: Connection -> IORef AuthCIDs
connPeerAuthCIDs :: Connection -> IORef AuthCIDs
connResources :: Connection -> IORef (IO ())
encodeBuf :: Connection -> Buffer
encryptRes :: Connection -> SizedBuffer
decryptBuf :: Connection -> Buffer
connLDCC :: Connection -> LDCC
connState :: ConnState
connDebugLog :: DebugLogger
connQLog :: QLogger
connHooks :: Hooks
connSend :: Send
connRecv :: Recv
connRecvQ :: RecvQ
udpSocket :: IORef UDPSocket
readers :: IORef (IO ())
mainThreadId :: ThreadId
controlRate :: Rate
roleInfo :: IORef RoleInfo
quicVersionInfo :: IORef VersionInfo
origVersionInfo :: VersionInfo
myParameters :: Parameters
myCIDDB :: IORef CIDDB
peerParameters :: IORef Parameters
peerCIDDB :: TVar CIDDB
inputQ :: InputQ
cryptoQ :: CryptoQ
outputQ :: OutputQ
outputQLim :: OutputQLim
migrationQ :: MigrationQ
shared :: Shared
delayedAckCount :: IORef Int
delayedAckCancel :: IORef (IO ())
peerPacketNumber :: IORef Int
streamTable :: IORef StreamTable
myStreamId :: TVar Concurrency
myUniStreamId :: TVar Concurrency
peerStreamId :: IORef Concurrency
peerUniStreamId :: IORef Concurrency
flowTx :: TVar TxFlow
flowRx :: IORef RxFlow
migrationState :: TVar MigrationState
minIdleTimeout :: IORef Microseconds
bytesTx :: TVar Int
bytesRx :: TVar Int
addressValidated :: TVar Bool
pendingQ :: Array EncryptionLevel (TVar [ReceivedPacket])
ciphers :: IOArray EncryptionLevel Cipher
coders :: IOArray EncryptionLevel Coder
coders1RTT :: IOArray Bool Coder1RTT
protectors :: IOArray EncryptionLevel Protector
currentKeyPhase :: IORef (Bool, Int)
negotiated :: IORef Negotiated
connMyAuthCIDs :: IORef AuthCIDs
connPeerAuthCIDs :: IORef AuthCIDs
connResources :: IORef (IO ())
encodeBuf :: Buffer
encryptRes :: SizedBuffer
decryptBuf :: Buffer
connLDCC :: LDCC
..} Version
ver = IORef VersionInfo -> (VersionInfo -> VersionInfo) -> IO ()
forall a. IORef a -> (a -> a) -> IO ()
atomicModifyIORef'' IORef VersionInfo
quicVersionInfo ((VersionInfo -> VersionInfo) -> IO ())
-> (VersionInfo -> VersionInfo) -> IO ()
forall a b. (a -> b) -> a -> b
$ \VersionInfo
vi ->
    VersionInfo
vi{chosenVersion = ver}

getVersion :: Connection -> IO Version
getVersion :: Connection -> IO Version
getVersion Connection
conn = VersionInfo -> Version
chosenVersion (VersionInfo -> Version) -> IO VersionInfo -> IO Version
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Connection -> IO VersionInfo
getVersionInfo Connection
conn

getOriginalVersion :: Connection -> Version
getOriginalVersion :: Connection -> Version
getOriginalVersion = VersionInfo -> Version
chosenVersion (VersionInfo -> Version)
-> (Connection -> VersionInfo) -> Connection -> Version
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Connection -> VersionInfo
origVersionInfo

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

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

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

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

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

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

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

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

getClientDstCID :: Connection -> IO CID
getClientDstCID :: Connection -> IO CID
getClientDstCID Connection
conn = do
    AuthCIDs
cids <-
        if Connection -> Bool
forall a. Connector a => a -> Bool
isClient Connection
conn
            then Connection -> IO AuthCIDs
getPeerAuthCIDs Connection
conn
            else Connection -> IO AuthCIDs
getMyAuthCIDs Connection
conn
    CID -> IO CID
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (CID -> IO CID) -> CID -> IO CID
forall a b. (a -> b) -> a -> b
$ case AuthCIDs -> Maybe CID
retrySrcCID AuthCIDs
cids of
        Maybe CID
Nothing -> Maybe CID -> CID
forall a. HasCallStack => Maybe a -> a
fromJust (Maybe CID -> CID) -> Maybe CID -> CID
forall a b. (a -> b) -> a -> b
$ AuthCIDs -> Maybe CID
origDstCID AuthCIDs
cids
        Just CID
dcid -> CID
dcid

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

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

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

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

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

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

delayedAck :: Connection -> IO ()
delayedAck :: Connection -> IO ()
delayedAck conn :: Connection
conn@Connection{Recv
Buffer
Array EncryptionLevel (TVar [ReceivedPacket])
IOArray Bool Coder1RTT
IOArray EncryptionLevel Cipher
IOArray EncryptionLevel Protector
IOArray EncryptionLevel Coder
ThreadId
TVar Bool
TVar Int
TVar TxFlow
TVar Concurrency
TVar MigrationState
TVar CIDDB
IORef Int
IORef (IO ())
IORef (Bool, Int)
IORef RxFlow
IORef UDPSocket
IORef Microseconds
IORef VersionInfo
IORef AuthCIDs
IORef Parameters
IORef StreamTable
IORef Concurrency
IORef Negotiated
IORef CIDDB
IORef RoleInfo
Rate
OutputQLim
MigrationQ
OutputQ
CryptoQ
InputQ
VersionInfo
RecvQ
SizedBuffer
ConnState
Parameters
LDCC
Hooks
Shared
Send
DebugLogger
QLogger
connState :: Connection -> ConnState
connDebugLog :: Connection -> DebugLogger
connQLog :: Connection -> QLogger
connHooks :: Connection -> Hooks
connSend :: Connection -> Send
connRecv :: Connection -> Recv
connRecvQ :: Connection -> RecvQ
udpSocket :: Connection -> IORef UDPSocket
readers :: Connection -> IORef (IO ())
mainThreadId :: Connection -> ThreadId
controlRate :: Connection -> Rate
roleInfo :: Connection -> IORef RoleInfo
quicVersionInfo :: Connection -> IORef VersionInfo
origVersionInfo :: Connection -> VersionInfo
myParameters :: Connection -> Parameters
myCIDDB :: Connection -> IORef CIDDB
peerParameters :: Connection -> IORef Parameters
peerCIDDB :: Connection -> TVar CIDDB
inputQ :: Connection -> InputQ
cryptoQ :: Connection -> CryptoQ
outputQ :: Connection -> OutputQ
outputQLim :: Connection -> OutputQLim
migrationQ :: Connection -> MigrationQ
shared :: Connection -> Shared
delayedAckCount :: Connection -> IORef Int
delayedAckCancel :: Connection -> IORef (IO ())
peerPacketNumber :: Connection -> IORef Int
streamTable :: Connection -> IORef StreamTable
myStreamId :: Connection -> TVar Concurrency
myUniStreamId :: Connection -> TVar Concurrency
peerStreamId :: Connection -> IORef Concurrency
peerUniStreamId :: Connection -> IORef Concurrency
flowTx :: Connection -> TVar TxFlow
flowRx :: Connection -> IORef RxFlow
migrationState :: Connection -> TVar MigrationState
minIdleTimeout :: Connection -> IORef Microseconds
bytesTx :: Connection -> TVar Int
bytesRx :: Connection -> TVar Int
addressValidated :: Connection -> TVar Bool
pendingQ :: Connection -> Array EncryptionLevel (TVar [ReceivedPacket])
ciphers :: Connection -> IOArray EncryptionLevel Cipher
coders :: Connection -> IOArray EncryptionLevel Coder
coders1RTT :: Connection -> IOArray Bool Coder1RTT
protectors :: Connection -> IOArray EncryptionLevel Protector
currentKeyPhase :: Connection -> IORef (Bool, Int)
negotiated :: Connection -> IORef Negotiated
connMyAuthCIDs :: Connection -> IORef AuthCIDs
connPeerAuthCIDs :: Connection -> IORef AuthCIDs
connResources :: Connection -> IORef (IO ())
encodeBuf :: Connection -> Buffer
encryptRes :: Connection -> SizedBuffer
decryptBuf :: Connection -> Buffer
connLDCC :: Connection -> LDCC
connState :: ConnState
connDebugLog :: DebugLogger
connQLog :: QLogger
connHooks :: Hooks
connSend :: Send
connRecv :: Recv
connRecvQ :: RecvQ
udpSocket :: IORef UDPSocket
readers :: IORef (IO ())
mainThreadId :: ThreadId
controlRate :: Rate
roleInfo :: IORef RoleInfo
quicVersionInfo :: IORef VersionInfo
origVersionInfo :: VersionInfo
myParameters :: Parameters
myCIDDB :: IORef CIDDB
peerParameters :: IORef Parameters
peerCIDDB :: TVar CIDDB
inputQ :: InputQ
cryptoQ :: CryptoQ
outputQ :: OutputQ
outputQLim :: OutputQLim
migrationQ :: MigrationQ
shared :: Shared
delayedAckCount :: IORef Int
delayedAckCancel :: IORef (IO ())
peerPacketNumber :: IORef Int
streamTable :: IORef StreamTable
myStreamId :: TVar Concurrency
myUniStreamId :: TVar Concurrency
peerStreamId :: IORef Concurrency
peerUniStreamId :: IORef Concurrency
flowTx :: TVar TxFlow
flowRx :: IORef RxFlow
migrationState :: TVar MigrationState
minIdleTimeout :: IORef Microseconds
bytesTx :: TVar Int
bytesRx :: TVar Int
addressValidated :: TVar Bool
pendingQ :: Array EncryptionLevel (TVar [ReceivedPacket])
ciphers :: IOArray EncryptionLevel Cipher
coders :: IOArray EncryptionLevel Coder
coders1RTT :: IOArray Bool Coder1RTT
protectors :: IOArray EncryptionLevel Protector
currentKeyPhase :: IORef (Bool, Int)
negotiated :: IORef Negotiated
connMyAuthCIDs :: IORef AuthCIDs
connPeerAuthCIDs :: IORef AuthCIDs
connResources :: IORef (IO ())
encodeBuf :: Buffer
encryptRes :: SizedBuffer
decryptBuf :: Buffer
connLDCC :: LDCC
..} = do
    (Int
oldcnt, Bool
send_) <- IORef Int -> (Int -> (Int, (Int, Bool))) -> IO (Int, Bool)
forall a b. IORef a -> (a -> (a, b)) -> IO b
atomicModifyIORef' IORef Int
delayedAckCount Int -> (Int, (Int, Bool))
forall {a}. (Eq a, Num a) => a -> (a, (a, Bool))
check
    Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Int
oldcnt Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
0) (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$ do
        IO ()
new <- Connection -> Microseconds -> IO () -> IO (IO ())
cfire Connection
conn (Int -> Microseconds
Microseconds Int
20000) IO ()
sendAck
        IO (IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => m (m a) -> m a
join (IO (IO ()) -> IO ()) -> IO (IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ IORef (IO ()) -> (IO () -> (IO (), IO ())) -> IO (IO ())
forall a b. IORef a -> (a -> (a, b)) -> IO b
atomicModifyIORef' IORef (IO ())
delayedAckCancel (IO ()
new,)
    Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when Bool
send_ (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$ do
        let new :: IO ()
new = () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
        IO (IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => m (m a) -> m a
join (IO (IO ()) -> IO ()) -> IO (IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ IORef (IO ()) -> (IO () -> (IO (), IO ())) -> IO (IO ())
forall a b. IORef a -> (a -> (a, b)) -> IO b
atomicModifyIORef' IORef (IO ())
delayedAckCancel (IO ()
new,)
        IO ()
sendAck
  where
    sendAck :: IO ()
sendAck = Connection -> Output -> IO ()
putOutput Connection
conn (Output -> IO ()) -> Output -> IO ()
forall a b. (a -> b) -> a -> b
$ EncryptionLevel -> [Frame] -> IO () -> Output
OutControl EncryptionLevel
RTT1Level [] (IO () -> Output) -> IO () -> Output
forall a b. (a -> b) -> a -> b
$ () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
    check :: a -> (a, (a, Bool))
check a
1 = (a
0, (a
1, Bool
True))
    check a
n = (a
n a -> a -> a
forall a. Num a => a -> a -> a
+ a
1, (a
n, Bool
False))

resetDealyedAck :: Connection -> IO ()
resetDealyedAck :: Connection -> IO ()
resetDealyedAck Connection{Recv
Buffer
Array EncryptionLevel (TVar [ReceivedPacket])
IOArray Bool Coder1RTT
IOArray EncryptionLevel Cipher
IOArray EncryptionLevel Protector
IOArray EncryptionLevel Coder
ThreadId
TVar Bool
TVar Int
TVar TxFlow
TVar Concurrency
TVar MigrationState
TVar CIDDB
IORef Int
IORef (IO ())
IORef (Bool, Int)
IORef RxFlow
IORef UDPSocket
IORef Microseconds
IORef VersionInfo
IORef AuthCIDs
IORef Parameters
IORef StreamTable
IORef Concurrency
IORef Negotiated
IORef CIDDB
IORef RoleInfo
Rate
OutputQLim
MigrationQ
OutputQ
CryptoQ
InputQ
VersionInfo
RecvQ
SizedBuffer
ConnState
Parameters
LDCC
Hooks
Shared
Send
DebugLogger
QLogger
connState :: Connection -> ConnState
connDebugLog :: Connection -> DebugLogger
connQLog :: Connection -> QLogger
connHooks :: Connection -> Hooks
connSend :: Connection -> Send
connRecv :: Connection -> Recv
connRecvQ :: Connection -> RecvQ
udpSocket :: Connection -> IORef UDPSocket
readers :: Connection -> IORef (IO ())
mainThreadId :: Connection -> ThreadId
controlRate :: Connection -> Rate
roleInfo :: Connection -> IORef RoleInfo
quicVersionInfo :: Connection -> IORef VersionInfo
origVersionInfo :: Connection -> VersionInfo
myParameters :: Connection -> Parameters
myCIDDB :: Connection -> IORef CIDDB
peerParameters :: Connection -> IORef Parameters
peerCIDDB :: Connection -> TVar CIDDB
inputQ :: Connection -> InputQ
cryptoQ :: Connection -> CryptoQ
outputQ :: Connection -> OutputQ
outputQLim :: Connection -> OutputQLim
migrationQ :: Connection -> MigrationQ
shared :: Connection -> Shared
delayedAckCount :: Connection -> IORef Int
delayedAckCancel :: Connection -> IORef (IO ())
peerPacketNumber :: Connection -> IORef Int
streamTable :: Connection -> IORef StreamTable
myStreamId :: Connection -> TVar Concurrency
myUniStreamId :: Connection -> TVar Concurrency
peerStreamId :: Connection -> IORef Concurrency
peerUniStreamId :: Connection -> IORef Concurrency
flowTx :: Connection -> TVar TxFlow
flowRx :: Connection -> IORef RxFlow
migrationState :: Connection -> TVar MigrationState
minIdleTimeout :: Connection -> IORef Microseconds
bytesTx :: Connection -> TVar Int
bytesRx :: Connection -> TVar Int
addressValidated :: Connection -> TVar Bool
pendingQ :: Connection -> Array EncryptionLevel (TVar [ReceivedPacket])
ciphers :: Connection -> IOArray EncryptionLevel Cipher
coders :: Connection -> IOArray EncryptionLevel Coder
coders1RTT :: Connection -> IOArray Bool Coder1RTT
protectors :: Connection -> IOArray EncryptionLevel Protector
currentKeyPhase :: Connection -> IORef (Bool, Int)
negotiated :: Connection -> IORef Negotiated
connMyAuthCIDs :: Connection -> IORef AuthCIDs
connPeerAuthCIDs :: Connection -> IORef AuthCIDs
connResources :: Connection -> IORef (IO ())
encodeBuf :: Connection -> Buffer
encryptRes :: Connection -> SizedBuffer
decryptBuf :: Connection -> Buffer
connLDCC :: Connection -> LDCC
connState :: ConnState
connDebugLog :: DebugLogger
connQLog :: QLogger
connHooks :: Hooks
connSend :: Send
connRecv :: Recv
connRecvQ :: RecvQ
udpSocket :: IORef UDPSocket
readers :: IORef (IO ())
mainThreadId :: ThreadId
controlRate :: Rate
roleInfo :: IORef RoleInfo
quicVersionInfo :: IORef VersionInfo
origVersionInfo :: VersionInfo
myParameters :: Parameters
myCIDDB :: IORef CIDDB
peerParameters :: IORef Parameters
peerCIDDB :: TVar CIDDB
inputQ :: InputQ
cryptoQ :: CryptoQ
outputQ :: OutputQ
outputQLim :: OutputQLim
migrationQ :: MigrationQ
shared :: Shared
delayedAckCount :: IORef Int
delayedAckCancel :: IORef (IO ())
peerPacketNumber :: IORef Int
streamTable :: IORef StreamTable
myStreamId :: TVar Concurrency
myUniStreamId :: TVar Concurrency
peerStreamId :: IORef Concurrency
peerUniStreamId :: IORef Concurrency
flowTx :: TVar TxFlow
flowRx :: IORef RxFlow
migrationState :: TVar MigrationState
minIdleTimeout :: IORef Microseconds
bytesTx :: TVar Int
bytesRx :: TVar Int
addressValidated :: TVar Bool
pendingQ :: Array EncryptionLevel (TVar [ReceivedPacket])
ciphers :: IOArray EncryptionLevel Cipher
coders :: IOArray EncryptionLevel Coder
coders1RTT :: IOArray Bool Coder1RTT
protectors :: IOArray EncryptionLevel Protector
currentKeyPhase :: IORef (Bool, Int)
negotiated :: IORef Negotiated
connMyAuthCIDs :: IORef AuthCIDs
connPeerAuthCIDs :: IORef AuthCIDs
connResources :: IORef (IO ())
encodeBuf :: Buffer
encryptRes :: SizedBuffer
decryptBuf :: Buffer
connLDCC :: LDCC
..} = do
    IORef Int -> Int -> IO ()
forall a. IORef a -> a -> IO ()
writeIORef IORef Int
delayedAckCount Int
0
    let new :: IO ()
new = () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
    IO (IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => m (m a) -> m a
join (IO (IO ()) -> IO ()) -> IO (IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ IORef (IO ()) -> (IO () -> (IO (), IO ())) -> IO (IO ())
forall a b. IORef a -> (a -> (a, b)) -> IO b
atomicModifyIORef' IORef (IO ())
delayedAckCancel (IO ()
new,)

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

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

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

addResource :: Connection -> IO () -> IO ()
addResource :: Connection -> IO () -> IO ()
addResource Connection{Recv
Buffer
Array EncryptionLevel (TVar [ReceivedPacket])
IOArray Bool Coder1RTT
IOArray EncryptionLevel Cipher
IOArray EncryptionLevel Protector
IOArray EncryptionLevel Coder
ThreadId
TVar Bool
TVar Int
TVar TxFlow
TVar Concurrency
TVar MigrationState
TVar CIDDB
IORef Int
IORef (IO ())
IORef (Bool, Int)
IORef RxFlow
IORef UDPSocket
IORef Microseconds
IORef VersionInfo
IORef AuthCIDs
IORef Parameters
IORef StreamTable
IORef Concurrency
IORef Negotiated
IORef CIDDB
IORef RoleInfo
Rate
OutputQLim
MigrationQ
OutputQ
CryptoQ
InputQ
VersionInfo
RecvQ
SizedBuffer
ConnState
Parameters
LDCC
Hooks
Shared
Send
DebugLogger
QLogger
connState :: Connection -> ConnState
connDebugLog :: Connection -> DebugLogger
connQLog :: Connection -> QLogger
connHooks :: Connection -> Hooks
connSend :: Connection -> Send
connRecv :: Connection -> Recv
connRecvQ :: Connection -> RecvQ
udpSocket :: Connection -> IORef UDPSocket
readers :: Connection -> IORef (IO ())
mainThreadId :: Connection -> ThreadId
controlRate :: Connection -> Rate
roleInfo :: Connection -> IORef RoleInfo
quicVersionInfo :: Connection -> IORef VersionInfo
origVersionInfo :: Connection -> VersionInfo
myParameters :: Connection -> Parameters
myCIDDB :: Connection -> IORef CIDDB
peerParameters :: Connection -> IORef Parameters
peerCIDDB :: Connection -> TVar CIDDB
inputQ :: Connection -> InputQ
cryptoQ :: Connection -> CryptoQ
outputQ :: Connection -> OutputQ
outputQLim :: Connection -> OutputQLim
migrationQ :: Connection -> MigrationQ
shared :: Connection -> Shared
delayedAckCount :: Connection -> IORef Int
delayedAckCancel :: Connection -> IORef (IO ())
peerPacketNumber :: Connection -> IORef Int
streamTable :: Connection -> IORef StreamTable
myStreamId :: Connection -> TVar Concurrency
myUniStreamId :: Connection -> TVar Concurrency
peerStreamId :: Connection -> IORef Concurrency
peerUniStreamId :: Connection -> IORef Concurrency
flowTx :: Connection -> TVar TxFlow
flowRx :: Connection -> IORef RxFlow
migrationState :: Connection -> TVar MigrationState
minIdleTimeout :: Connection -> IORef Microseconds
bytesTx :: Connection -> TVar Int
bytesRx :: Connection -> TVar Int
addressValidated :: Connection -> TVar Bool
pendingQ :: Connection -> Array EncryptionLevel (TVar [ReceivedPacket])
ciphers :: Connection -> IOArray EncryptionLevel Cipher
coders :: Connection -> IOArray EncryptionLevel Coder
coders1RTT :: Connection -> IOArray Bool Coder1RTT
protectors :: Connection -> IOArray EncryptionLevel Protector
currentKeyPhase :: Connection -> IORef (Bool, Int)
negotiated :: Connection -> IORef Negotiated
connMyAuthCIDs :: Connection -> IORef AuthCIDs
connPeerAuthCIDs :: Connection -> IORef AuthCIDs
connResources :: Connection -> IORef (IO ())
encodeBuf :: Connection -> Buffer
encryptRes :: Connection -> SizedBuffer
decryptBuf :: Connection -> Buffer
connLDCC :: Connection -> LDCC
connState :: ConnState
connDebugLog :: DebugLogger
connQLog :: QLogger
connHooks :: Hooks
connSend :: Send
connRecv :: Recv
connRecvQ :: RecvQ
udpSocket :: IORef UDPSocket
readers :: IORef (IO ())
mainThreadId :: ThreadId
controlRate :: Rate
roleInfo :: IORef RoleInfo
quicVersionInfo :: IORef VersionInfo
origVersionInfo :: VersionInfo
myParameters :: Parameters
myCIDDB :: IORef CIDDB
peerParameters :: IORef Parameters
peerCIDDB :: TVar CIDDB
inputQ :: InputQ
cryptoQ :: CryptoQ
outputQ :: OutputQ
outputQLim :: OutputQLim
migrationQ :: MigrationQ
shared :: Shared
delayedAckCount :: IORef Int
delayedAckCancel :: IORef (IO ())
peerPacketNumber :: IORef Int
streamTable :: IORef StreamTable
myStreamId :: TVar Concurrency
myUniStreamId :: TVar Concurrency
peerStreamId :: IORef Concurrency
peerUniStreamId :: IORef Concurrency
flowTx :: TVar TxFlow
flowRx :: IORef RxFlow
migrationState :: TVar MigrationState
minIdleTimeout :: IORef Microseconds
bytesTx :: TVar Int
bytesRx :: TVar Int
addressValidated :: TVar Bool
pendingQ :: Array EncryptionLevel (TVar [ReceivedPacket])
ciphers :: IOArray EncryptionLevel Cipher
coders :: IOArray EncryptionLevel Coder
coders1RTT :: IOArray Bool Coder1RTT
protectors :: IOArray EncryptionLevel Protector
currentKeyPhase :: IORef (Bool, Int)
negotiated :: IORef Negotiated
connMyAuthCIDs :: IORef AuthCIDs
connPeerAuthCIDs :: IORef AuthCIDs
connResources :: IORef (IO ())
encodeBuf :: Buffer
encryptRes :: SizedBuffer
decryptBuf :: Buffer
connLDCC :: LDCC
..} IO ()
f = IORef (IO ()) -> (IO () -> IO ()) -> IO ()
forall a. IORef a -> (a -> a) -> IO ()
atomicModifyIORef'' IORef (IO ())
connResources ((IO () -> IO ()) -> IO ()) -> (IO () -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \IO ()
fs -> IO ()
f' IO () -> IO () -> IO ()
forall a b. IO a -> IO b -> IO b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> IO ()
fs
  where
    f' :: IO ()
f' = IO ()
f IO () -> (SomeException -> IO ()) -> IO ()
forall (m :: * -> *) e a.
(MonadUnliftIO m, Exception e) =>
m a -> (e -> m a) -> m a
`E.catch` (\(E.SomeException e
_) -> () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ())

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

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

addReader :: Connection -> ThreadId -> IO ()
addReader :: Connection -> ThreadId -> IO ()
addReader Connection{Recv
Buffer
Array EncryptionLevel (TVar [ReceivedPacket])
IOArray Bool Coder1RTT
IOArray EncryptionLevel Cipher
IOArray EncryptionLevel Protector
IOArray EncryptionLevel Coder
ThreadId
TVar Bool
TVar Int
TVar TxFlow
TVar Concurrency
TVar MigrationState
TVar CIDDB
IORef Int
IORef (IO ())
IORef (Bool, Int)
IORef RxFlow
IORef UDPSocket
IORef Microseconds
IORef VersionInfo
IORef AuthCIDs
IORef Parameters
IORef StreamTable
IORef Concurrency
IORef Negotiated
IORef CIDDB
IORef RoleInfo
Rate
OutputQLim
MigrationQ
OutputQ
CryptoQ
InputQ
VersionInfo
RecvQ
SizedBuffer
ConnState
Parameters
LDCC
Hooks
Shared
Send
DebugLogger
QLogger
connState :: Connection -> ConnState
connDebugLog :: Connection -> DebugLogger
connQLog :: Connection -> QLogger
connHooks :: Connection -> Hooks
connSend :: Connection -> Send
connRecv :: Connection -> Recv
connRecvQ :: Connection -> RecvQ
udpSocket :: Connection -> IORef UDPSocket
readers :: Connection -> IORef (IO ())
mainThreadId :: Connection -> ThreadId
controlRate :: Connection -> Rate
roleInfo :: Connection -> IORef RoleInfo
quicVersionInfo :: Connection -> IORef VersionInfo
origVersionInfo :: Connection -> VersionInfo
myParameters :: Connection -> Parameters
myCIDDB :: Connection -> IORef CIDDB
peerParameters :: Connection -> IORef Parameters
peerCIDDB :: Connection -> TVar CIDDB
inputQ :: Connection -> InputQ
cryptoQ :: Connection -> CryptoQ
outputQ :: Connection -> OutputQ
outputQLim :: Connection -> OutputQLim
migrationQ :: Connection -> MigrationQ
shared :: Connection -> Shared
delayedAckCount :: Connection -> IORef Int
delayedAckCancel :: Connection -> IORef (IO ())
peerPacketNumber :: Connection -> IORef Int
streamTable :: Connection -> IORef StreamTable
myStreamId :: Connection -> TVar Concurrency
myUniStreamId :: Connection -> TVar Concurrency
peerStreamId :: Connection -> IORef Concurrency
peerUniStreamId :: Connection -> IORef Concurrency
flowTx :: Connection -> TVar TxFlow
flowRx :: Connection -> IORef RxFlow
migrationState :: Connection -> TVar MigrationState
minIdleTimeout :: Connection -> IORef Microseconds
bytesTx :: Connection -> TVar Int
bytesRx :: Connection -> TVar Int
addressValidated :: Connection -> TVar Bool
pendingQ :: Connection -> Array EncryptionLevel (TVar [ReceivedPacket])
ciphers :: Connection -> IOArray EncryptionLevel Cipher
coders :: Connection -> IOArray EncryptionLevel Coder
coders1RTT :: Connection -> IOArray Bool Coder1RTT
protectors :: Connection -> IOArray EncryptionLevel Protector
currentKeyPhase :: Connection -> IORef (Bool, Int)
negotiated :: Connection -> IORef Negotiated
connMyAuthCIDs :: Connection -> IORef AuthCIDs
connPeerAuthCIDs :: Connection -> IORef AuthCIDs
connResources :: Connection -> IORef (IO ())
encodeBuf :: Connection -> Buffer
encryptRes :: Connection -> SizedBuffer
decryptBuf :: Connection -> Buffer
connLDCC :: Connection -> LDCC
connState :: ConnState
connDebugLog :: DebugLogger
connQLog :: QLogger
connHooks :: Hooks
connSend :: Send
connRecv :: Recv
connRecvQ :: RecvQ
udpSocket :: IORef UDPSocket
readers :: IORef (IO ())
mainThreadId :: ThreadId
controlRate :: Rate
roleInfo :: IORef RoleInfo
quicVersionInfo :: IORef VersionInfo
origVersionInfo :: VersionInfo
myParameters :: Parameters
myCIDDB :: IORef CIDDB
peerParameters :: IORef Parameters
peerCIDDB :: TVar CIDDB
inputQ :: InputQ
cryptoQ :: CryptoQ
outputQ :: OutputQ
outputQLim :: OutputQLim
migrationQ :: MigrationQ
shared :: Shared
delayedAckCount :: IORef Int
delayedAckCancel :: IORef (IO ())
peerPacketNumber :: IORef Int
streamTable :: IORef StreamTable
myStreamId :: TVar Concurrency
myUniStreamId :: TVar Concurrency
peerStreamId :: IORef Concurrency
peerUniStreamId :: IORef Concurrency
flowTx :: TVar TxFlow
flowRx :: IORef RxFlow
migrationState :: TVar MigrationState
minIdleTimeout :: IORef Microseconds
bytesTx :: TVar Int
bytesRx :: TVar Int
addressValidated :: TVar Bool
pendingQ :: Array EncryptionLevel (TVar [ReceivedPacket])
ciphers :: IOArray EncryptionLevel Cipher
coders :: IOArray EncryptionLevel Coder
coders1RTT :: IOArray Bool Coder1RTT
protectors :: IOArray EncryptionLevel Protector
currentKeyPhase :: IORef (Bool, Int)
negotiated :: IORef Negotiated
connMyAuthCIDs :: IORef AuthCIDs
connPeerAuthCIDs :: IORef AuthCIDs
connResources :: IORef (IO ())
encodeBuf :: Buffer
encryptRes :: SizedBuffer
decryptBuf :: Buffer
connLDCC :: LDCC
..} ThreadId
tid = do
    Weak ThreadId
wtid <- ThreadId -> IO (Weak ThreadId)
forall (m :: * -> *). MonadIO m => ThreadId -> m (Weak ThreadId)
mkWeakThreadId ThreadId
tid
    IORef (IO ()) -> (IO () -> IO ()) -> IO ()
forall a. IORef a -> (a -> a) -> IO ()
atomicModifyIORef'' IORef (IO ())
readers ((IO () -> IO ()) -> IO ()) -> (IO () -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \IO ()
m -> do
        IO ()
m
        Weak ThreadId -> IO (Maybe ThreadId)
forall v. Weak v -> IO (Maybe v)
deRefWeak Weak ThreadId
wtid IO (Maybe ThreadId) -> (Maybe ThreadId -> IO ()) -> IO ()
forall a b. IO a -> (a -> IO b) -> IO b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= (ThreadId -> IO ()) -> Maybe ThreadId -> IO ()
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
mapM_ ThreadId -> IO ()
forall (m :: * -> *). MonadIO m => ThreadId -> m ()
killThread

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

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

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

setMinIdleTimeout :: Connection -> Microseconds -> IO ()
setMinIdleTimeout :: Connection -> Microseconds -> IO ()
setMinIdleTimeout Connection{Recv
Buffer
Array EncryptionLevel (TVar [ReceivedPacket])
IOArray Bool Coder1RTT
IOArray EncryptionLevel Cipher
IOArray EncryptionLevel Protector
IOArray EncryptionLevel Coder
ThreadId
TVar Bool
TVar Int
TVar TxFlow
TVar Concurrency
TVar MigrationState
TVar CIDDB
IORef Int
IORef (IO ())
IORef (Bool, Int)
IORef RxFlow
IORef UDPSocket
IORef Microseconds
IORef VersionInfo
IORef AuthCIDs
IORef Parameters
IORef StreamTable
IORef Concurrency
IORef Negotiated
IORef CIDDB
IORef RoleInfo
Rate
OutputQLim
MigrationQ
OutputQ
CryptoQ
InputQ
VersionInfo
RecvQ
SizedBuffer
ConnState
Parameters
LDCC
Hooks
Shared
Send
DebugLogger
QLogger
connState :: Connection -> ConnState
connDebugLog :: Connection -> DebugLogger
connQLog :: Connection -> QLogger
connHooks :: Connection -> Hooks
connSend :: Connection -> Send
connRecv :: Connection -> Recv
connRecvQ :: Connection -> RecvQ
udpSocket :: Connection -> IORef UDPSocket
readers :: Connection -> IORef (IO ())
mainThreadId :: Connection -> ThreadId
controlRate :: Connection -> Rate
roleInfo :: Connection -> IORef RoleInfo
quicVersionInfo :: Connection -> IORef VersionInfo
origVersionInfo :: Connection -> VersionInfo
myParameters :: Connection -> Parameters
myCIDDB :: Connection -> IORef CIDDB
peerParameters :: Connection -> IORef Parameters
peerCIDDB :: Connection -> TVar CIDDB
inputQ :: Connection -> InputQ
cryptoQ :: Connection -> CryptoQ
outputQ :: Connection -> OutputQ
outputQLim :: Connection -> OutputQLim
migrationQ :: Connection -> MigrationQ
shared :: Connection -> Shared
delayedAckCount :: Connection -> IORef Int
delayedAckCancel :: Connection -> IORef (IO ())
peerPacketNumber :: Connection -> IORef Int
streamTable :: Connection -> IORef StreamTable
myStreamId :: Connection -> TVar Concurrency
myUniStreamId :: Connection -> TVar Concurrency
peerStreamId :: Connection -> IORef Concurrency
peerUniStreamId :: Connection -> IORef Concurrency
flowTx :: Connection -> TVar TxFlow
flowRx :: Connection -> IORef RxFlow
migrationState :: Connection -> TVar MigrationState
minIdleTimeout :: Connection -> IORef Microseconds
bytesTx :: Connection -> TVar Int
bytesRx :: Connection -> TVar Int
addressValidated :: Connection -> TVar Bool
pendingQ :: Connection -> Array EncryptionLevel (TVar [ReceivedPacket])
ciphers :: Connection -> IOArray EncryptionLevel Cipher
coders :: Connection -> IOArray EncryptionLevel Coder
coders1RTT :: Connection -> IOArray Bool Coder1RTT
protectors :: Connection -> IOArray EncryptionLevel Protector
currentKeyPhase :: Connection -> IORef (Bool, Int)
negotiated :: Connection -> IORef Negotiated
connMyAuthCIDs :: Connection -> IORef AuthCIDs
connPeerAuthCIDs :: Connection -> IORef AuthCIDs
connResources :: Connection -> IORef (IO ())
encodeBuf :: Connection -> Buffer
encryptRes :: Connection -> SizedBuffer
decryptBuf :: Connection -> Buffer
connLDCC :: Connection -> LDCC
connState :: ConnState
connDebugLog :: DebugLogger
connQLog :: QLogger
connHooks :: Hooks
connSend :: Send
connRecv :: Recv
connRecvQ :: RecvQ
udpSocket :: IORef UDPSocket
readers :: IORef (IO ())
mainThreadId :: ThreadId
controlRate :: Rate
roleInfo :: IORef RoleInfo
quicVersionInfo :: IORef VersionInfo
origVersionInfo :: VersionInfo
myParameters :: Parameters
myCIDDB :: IORef CIDDB
peerParameters :: IORef Parameters
peerCIDDB :: TVar CIDDB
inputQ :: InputQ
cryptoQ :: CryptoQ
outputQ :: OutputQ
outputQLim :: OutputQLim
migrationQ :: MigrationQ
shared :: Shared
delayedAckCount :: IORef Int
delayedAckCancel :: IORef (IO ())
peerPacketNumber :: IORef Int
streamTable :: IORef StreamTable
myStreamId :: TVar Concurrency
myUniStreamId :: TVar Concurrency
peerStreamId :: IORef Concurrency
peerUniStreamId :: IORef Concurrency
flowTx :: TVar TxFlow
flowRx :: IORef RxFlow
migrationState :: TVar MigrationState
minIdleTimeout :: IORef Microseconds
bytesTx :: TVar Int
bytesRx :: TVar Int
addressValidated :: TVar Bool
pendingQ :: Array EncryptionLevel (TVar [ReceivedPacket])
ciphers :: IOArray EncryptionLevel Cipher
coders :: IOArray EncryptionLevel Coder
coders1RTT :: IOArray Bool Coder1RTT
protectors :: IOArray EncryptionLevel Protector
currentKeyPhase :: IORef (Bool, Int)
negotiated :: IORef Negotiated
connMyAuthCIDs :: IORef AuthCIDs
connPeerAuthCIDs :: IORef AuthCIDs
connResources :: IORef (IO ())
encodeBuf :: Buffer
encryptRes :: SizedBuffer
decryptBuf :: Buffer
connLDCC :: LDCC
..} Microseconds
us
    | Microseconds
us Microseconds -> Microseconds -> Bool
forall a. Eq a => a -> a -> Bool
== Int -> Microseconds
Microseconds Int
0 = () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
    | Bool
otherwise = IORef Microseconds -> (Microseconds -> Microseconds) -> IO ()
forall a. IORef a -> (a -> a) -> IO ()
atomicModifyIORef'' IORef Microseconds
minIdleTimeout Microseconds -> Microseconds
modify
  where
    modify :: Microseconds -> Microseconds
modify Microseconds
us0 = Microseconds -> Microseconds -> Microseconds
forall a. Ord a => a -> a -> a
min Microseconds
us Microseconds
us0

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

sendFrames :: Connection -> EncryptionLevel -> [Frame] -> IO ()
sendFrames :: Connection -> EncryptionLevel -> [Frame] -> IO ()
sendFrames Connection
conn EncryptionLevel
lvl [Frame]
frames = Connection -> Output -> IO ()
putOutput Connection
conn (Output -> IO ()) -> Output -> IO ()
forall a b. (a -> b) -> a -> b
$ EncryptionLevel -> [Frame] -> IO () -> Output
OutControl EncryptionLevel
lvl [Frame]
frames (IO () -> Output) -> IO () -> Output
forall a b. (a -> b) -> a -> b
$ () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

sendFramesLim :: Connection -> EncryptionLevel -> [Frame] -> IO ()
sendFramesLim :: Connection -> EncryptionLevel -> [Frame] -> IO ()
sendFramesLim Connection
conn EncryptionLevel
lvl [Frame]
frames = Connection -> Output -> IO ()
putOutputLim Connection
conn (Output -> IO ()) -> Output -> IO ()
forall a b. (a -> b) -> a -> b
$ EncryptionLevel -> [Frame] -> IO () -> Output
OutControl EncryptionLevel
lvl [Frame]
frames (IO () -> Output) -> IO () -> Output
forall a b. (a -> b) -> a -> b
$ () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

-- | Closing a connection with/without a transport error.
--   Internal threads should use this.
closeConnection :: TransportError -> ReasonPhrase -> IO ()
closeConnection :: TransportError -> ReasonPhrase -> IO ()
closeConnection TransportError
err ReasonPhrase
desc = QUICException -> IO ()
forall (m :: * -> *) e a. (MonadIO m, Exception e) => e -> m a
E.throwIO QUICException
quicexc
  where
    quicexc :: QUICException
quicexc = TransportError -> ReasonPhrase -> QUICException
TransportErrorIsSent TransportError
err ReasonPhrase
desc

-- | Closing a connection with an application protocol error.
abortConnection
    :: Connection -> ApplicationProtocolError -> ReasonPhrase -> IO ()
abortConnection :: Connection -> ApplicationProtocolError -> ReasonPhrase -> IO ()
abortConnection Connection
conn ApplicationProtocolError
err ReasonPhrase
desc = ThreadId -> Abort -> IO ()
forall e (m :: * -> *).
(Exception e, MonadIO m) =>
ThreadId -> e -> m ()
E.throwTo (Connection -> ThreadId
mainThreadId Connection
conn) (Abort -> IO ()) -> Abort -> IO ()
forall a b. (a -> b) -> a -> b
$ ApplicationProtocolError -> ReasonPhrase -> Abort
Abort ApplicationProtocolError
err ReasonPhrase
desc