{-# LANGUAGE RecordWildCards #-}

module Network.QUIC.Connection.StreamTable (
    createStream
  , findStream
  , addStream
  , delStream
  , initialRxMaxStreamData
  , setupCryptoStreams
  , clearCryptoStream
  , getCryptoStream
  ) where

import Network.QUIC.Connection.Misc
import Network.QUIC.Connection.Queue
import Network.QUIC.Connection.Types
import Network.QUIC.Connector
import Network.QUIC.Imports
import Network.QUIC.Parameters
import Network.QUIC.Stream
import Network.QUIC.Types

createStream :: Connection -> StreamId -> IO Stream
createStream :: Connection -> StreamId -> IO Stream
createStream Connection
conn StreamId
sid = do
      Stream
strm <- Connection -> StreamId -> IO Stream
addStream Connection
conn StreamId
sid
      Connection -> Input -> IO ()
putInput Connection
conn (Input -> IO ()) -> Input -> IO ()
forall a b. (a -> b) -> a -> b
$ Stream -> Input
InpStream Stream
strm
      Stream -> IO Stream
forall (m :: * -> *) a. Monad m => a -> m a
return Stream
strm

findStream :: Connection -> StreamId -> IO (Maybe Stream)
findStream :: Connection -> StreamId -> IO (Maybe Stream)
findStream Connection{Array EncryptionLevel (TVar [ReceivedPacket])
IOArray Bool Coder1RTT
IOArray EncryptionLevel Cipher
IOArray EncryptionLevel Protector
IOArray EncryptionLevel Coder
ThreadId
TVar Bool
TVar StreamId
TVar Flow
TVar Concurrency
TVar MigrationState
TVar CIDDB
IORef StreamId
IORef [Socket]
IORef (IO ())
IORef (Bool, StreamId)
IORef Microseconds
IORef Version
IORef Flow
IORef StreamTable
IORef AuthCIDs
IORef Parameters
IORef Concurrency
IORef Negotiated
IORef CIDDB
IORef RoleInfo
MigrationQ
OutputQ
CryptoQ
InputQ
RecvQ
ConnState
Parameters
LDCC
Hooks
Shared
DebugLogger
QLogger
connLDCC :: Connection -> LDCC
connResources :: Connection -> IORef (IO ())
handshakeCIDs :: Connection -> IORef AuthCIDs
negotiated :: Connection -> IORef Negotiated
currentKeyPhase :: Connection -> IORef (Bool, StreamId)
protectors :: Connection -> IOArray EncryptionLevel Protector
coders1RTT :: Connection -> IOArray Bool Coder1RTT
coders :: Connection -> IOArray EncryptionLevel Coder
ciphers :: Connection -> IOArray EncryptionLevel Cipher
pendingQ :: Connection -> Array EncryptionLevel (TVar [ReceivedPacket])
addressValidated :: Connection -> TVar Bool
bytesRx :: Connection -> TVar StreamId
bytesTx :: Connection -> TVar StreamId
minIdleTimeout :: Connection -> IORef Microseconds
migrationState :: Connection -> TVar MigrationState
flowRx :: Connection -> IORef Flow
flowTx :: Connection -> TVar Flow
peerStreamId :: Connection -> IORef Concurrency
myUniStreamId :: Connection -> TVar Concurrency
myStreamId :: Connection -> TVar Concurrency
streamTable :: Connection -> IORef StreamTable
peerPacketNumber :: Connection -> IORef StreamId
delayedAckCancel :: Connection -> IORef (IO ())
delayedAckCount :: Connection -> IORef StreamId
shared :: Connection -> Shared
migrationQ :: Connection -> MigrationQ
outputQ :: Connection -> OutputQ
cryptoQ :: Connection -> CryptoQ
inputQ :: Connection -> InputQ
peerCIDDB :: Connection -> TVar CIDDB
peerParameters :: Connection -> IORef Parameters
myCIDDB :: Connection -> IORef CIDDB
myParameters :: Connection -> Parameters
quicVersion :: Connection -> IORef Version
roleInfo :: Connection -> IORef RoleInfo
mainThreadId :: Connection -> ThreadId
tmouter :: Connection -> IORef (IO ())
readers :: Connection -> IORef (IO ())
sockets :: Connection -> IORef [Socket]
connRecvQ :: Connection -> RecvQ
connHooks :: Connection -> Hooks
connQLog :: Connection -> QLogger
connDebugLog :: Connection -> DebugLogger
connState :: Connection -> ConnState
connLDCC :: LDCC
connResources :: IORef (IO ())
handshakeCIDs :: IORef AuthCIDs
negotiated :: IORef Negotiated
currentKeyPhase :: IORef (Bool, StreamId)
protectors :: IOArray EncryptionLevel Protector
coders1RTT :: IOArray Bool Coder1RTT
coders :: IOArray EncryptionLevel Coder
ciphers :: IOArray EncryptionLevel Cipher
pendingQ :: Array EncryptionLevel (TVar [ReceivedPacket])
addressValidated :: TVar Bool
bytesRx :: TVar StreamId
bytesTx :: TVar StreamId
minIdleTimeout :: IORef Microseconds
migrationState :: TVar MigrationState
flowRx :: IORef Flow
flowTx :: TVar Flow
peerStreamId :: IORef Concurrency
myUniStreamId :: TVar Concurrency
myStreamId :: TVar Concurrency
streamTable :: IORef StreamTable
peerPacketNumber :: IORef StreamId
delayedAckCancel :: IORef (IO ())
delayedAckCount :: IORef StreamId
shared :: Shared
migrationQ :: MigrationQ
outputQ :: OutputQ
cryptoQ :: CryptoQ
inputQ :: InputQ
peerCIDDB :: TVar CIDDB
peerParameters :: IORef Parameters
myCIDDB :: IORef CIDDB
myParameters :: Parameters
quicVersion :: IORef Version
roleInfo :: IORef RoleInfo
mainThreadId :: ThreadId
tmouter :: IORef (IO ())
readers :: IORef (IO ())
sockets :: IORef [Socket]
connRecvQ :: RecvQ
connHooks :: Hooks
connQLog :: QLogger
connDebugLog :: DebugLogger
connState :: ConnState
..} StreamId
sid = StreamId -> StreamTable -> Maybe Stream
lookupStream StreamId
sid (StreamTable -> Maybe Stream)
-> IO StreamTable -> IO (Maybe Stream)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> IORef StreamTable -> IO StreamTable
forall a. IORef a -> IO a
readIORef IORef StreamTable
streamTable

addStream :: Connection -> StreamId -> IO Stream
addStream :: Connection -> StreamId -> IO Stream
addStream conn :: Connection
conn@Connection{Array EncryptionLevel (TVar [ReceivedPacket])
IOArray Bool Coder1RTT
IOArray EncryptionLevel Cipher
IOArray EncryptionLevel Protector
IOArray EncryptionLevel Coder
ThreadId
TVar Bool
TVar StreamId
TVar Flow
TVar Concurrency
TVar MigrationState
TVar CIDDB
IORef StreamId
IORef [Socket]
IORef (IO ())
IORef (Bool, StreamId)
IORef Microseconds
IORef Version
IORef Flow
IORef StreamTable
IORef AuthCIDs
IORef Parameters
IORef Concurrency
IORef Negotiated
IORef CIDDB
IORef RoleInfo
MigrationQ
OutputQ
CryptoQ
InputQ
RecvQ
ConnState
Parameters
LDCC
Hooks
Shared
DebugLogger
QLogger
connLDCC :: LDCC
connResources :: IORef (IO ())
handshakeCIDs :: IORef AuthCIDs
negotiated :: IORef Negotiated
currentKeyPhase :: IORef (Bool, StreamId)
protectors :: IOArray EncryptionLevel Protector
coders1RTT :: IOArray Bool Coder1RTT
coders :: IOArray EncryptionLevel Coder
ciphers :: IOArray EncryptionLevel Cipher
pendingQ :: Array EncryptionLevel (TVar [ReceivedPacket])
addressValidated :: TVar Bool
bytesRx :: TVar StreamId
bytesTx :: TVar StreamId
minIdleTimeout :: IORef Microseconds
migrationState :: TVar MigrationState
flowRx :: IORef Flow
flowTx :: TVar Flow
peerStreamId :: IORef Concurrency
myUniStreamId :: TVar Concurrency
myStreamId :: TVar Concurrency
streamTable :: IORef StreamTable
peerPacketNumber :: IORef StreamId
delayedAckCancel :: IORef (IO ())
delayedAckCount :: IORef StreamId
shared :: Shared
migrationQ :: MigrationQ
outputQ :: OutputQ
cryptoQ :: CryptoQ
inputQ :: InputQ
peerCIDDB :: TVar CIDDB
peerParameters :: IORef Parameters
myCIDDB :: IORef CIDDB
myParameters :: Parameters
quicVersion :: IORef Version
roleInfo :: IORef RoleInfo
mainThreadId :: ThreadId
tmouter :: IORef (IO ())
readers :: IORef (IO ())
sockets :: IORef [Socket]
connRecvQ :: RecvQ
connHooks :: Hooks
connQLog :: QLogger
connDebugLog :: DebugLogger
connState :: ConnState
connLDCC :: Connection -> LDCC
connResources :: Connection -> IORef (IO ())
handshakeCIDs :: Connection -> IORef AuthCIDs
negotiated :: Connection -> IORef Negotiated
currentKeyPhase :: Connection -> IORef (Bool, StreamId)
protectors :: Connection -> IOArray EncryptionLevel Protector
coders1RTT :: Connection -> IOArray Bool Coder1RTT
coders :: Connection -> IOArray EncryptionLevel Coder
ciphers :: Connection -> IOArray EncryptionLevel Cipher
pendingQ :: Connection -> Array EncryptionLevel (TVar [ReceivedPacket])
addressValidated :: Connection -> TVar Bool
bytesRx :: Connection -> TVar StreamId
bytesTx :: Connection -> TVar StreamId
minIdleTimeout :: Connection -> IORef Microseconds
migrationState :: Connection -> TVar MigrationState
flowRx :: Connection -> IORef Flow
flowTx :: Connection -> TVar Flow
peerStreamId :: Connection -> IORef Concurrency
myUniStreamId :: Connection -> TVar Concurrency
myStreamId :: Connection -> TVar Concurrency
streamTable :: Connection -> IORef StreamTable
peerPacketNumber :: Connection -> IORef StreamId
delayedAckCancel :: Connection -> IORef (IO ())
delayedAckCount :: Connection -> IORef StreamId
shared :: Connection -> Shared
migrationQ :: Connection -> MigrationQ
outputQ :: Connection -> OutputQ
cryptoQ :: Connection -> CryptoQ
inputQ :: Connection -> InputQ
peerCIDDB :: Connection -> TVar CIDDB
peerParameters :: Connection -> IORef Parameters
myCIDDB :: Connection -> IORef CIDDB
myParameters :: Connection -> Parameters
quicVersion :: Connection -> IORef Version
roleInfo :: Connection -> IORef RoleInfo
mainThreadId :: Connection -> ThreadId
tmouter :: Connection -> IORef (IO ())
readers :: Connection -> IORef (IO ())
sockets :: Connection -> IORef [Socket]
connRecvQ :: Connection -> RecvQ
connHooks :: Connection -> Hooks
connQLog :: Connection -> QLogger
connDebugLog :: Connection -> DebugLogger
connState :: Connection -> ConnState
..} StreamId
sid = do
    Stream
strm <- Connection -> StreamId -> IO Stream
newStream Connection
conn StreamId
sid
    Parameters
peerParams <- Connection -> IO Parameters
getPeerParameters Connection
conn
    let txMaxStreamData :: StreamId
txMaxStreamData | Connection -> Bool
forall a. Connector a => a -> Bool
isClient Connection
conn = StreamId -> Parameters -> StreamId
clientInitial StreamId
sid Parameters
peerParams
                        | Bool
otherwise     = StreamId -> Parameters -> StreamId
serverInitial StreamId
sid Parameters
peerParams
    Stream -> StreamId -> IO ()
setTxMaxStreamData Stream
strm StreamId
txMaxStreamData
    let rxMaxStreamData :: StreamId
rxMaxStreamData = Connection -> StreamId -> StreamId
initialRxMaxStreamData Connection
conn StreamId
sid
    Stream -> StreamId -> IO ()
setRxMaxStreamData Stream
strm StreamId
rxMaxStreamData
    IORef StreamTable -> (StreamTable -> StreamTable) -> IO ()
forall a. IORef a -> (a -> a) -> IO ()
atomicModifyIORef'' IORef StreamTable
streamTable ((StreamTable -> StreamTable) -> IO ())
-> (StreamTable -> StreamTable) -> IO ()
forall a b. (a -> b) -> a -> b
$ StreamId -> Stream -> StreamTable -> StreamTable
insertStream StreamId
sid Stream
strm
    Stream -> IO Stream
forall (m :: * -> *) a. Monad m => a -> m a
return Stream
strm

delStream :: Connection -> Stream -> IO ()
delStream :: Connection -> Stream -> IO ()
delStream Connection{Array EncryptionLevel (TVar [ReceivedPacket])
IOArray Bool Coder1RTT
IOArray EncryptionLevel Cipher
IOArray EncryptionLevel Protector
IOArray EncryptionLevel Coder
ThreadId
TVar Bool
TVar StreamId
TVar Flow
TVar Concurrency
TVar MigrationState
TVar CIDDB
IORef StreamId
IORef [Socket]
IORef (IO ())
IORef (Bool, StreamId)
IORef Microseconds
IORef Version
IORef Flow
IORef StreamTable
IORef AuthCIDs
IORef Parameters
IORef Concurrency
IORef Negotiated
IORef CIDDB
IORef RoleInfo
MigrationQ
OutputQ
CryptoQ
InputQ
RecvQ
ConnState
Parameters
LDCC
Hooks
Shared
DebugLogger
QLogger
connLDCC :: LDCC
connResources :: IORef (IO ())
handshakeCIDs :: IORef AuthCIDs
negotiated :: IORef Negotiated
currentKeyPhase :: IORef (Bool, StreamId)
protectors :: IOArray EncryptionLevel Protector
coders1RTT :: IOArray Bool Coder1RTT
coders :: IOArray EncryptionLevel Coder
ciphers :: IOArray EncryptionLevel Cipher
pendingQ :: Array EncryptionLevel (TVar [ReceivedPacket])
addressValidated :: TVar Bool
bytesRx :: TVar StreamId
bytesTx :: TVar StreamId
minIdleTimeout :: IORef Microseconds
migrationState :: TVar MigrationState
flowRx :: IORef Flow
flowTx :: TVar Flow
peerStreamId :: IORef Concurrency
myUniStreamId :: TVar Concurrency
myStreamId :: TVar Concurrency
streamTable :: IORef StreamTable
peerPacketNumber :: IORef StreamId
delayedAckCancel :: IORef (IO ())
delayedAckCount :: IORef StreamId
shared :: Shared
migrationQ :: MigrationQ
outputQ :: OutputQ
cryptoQ :: CryptoQ
inputQ :: InputQ
peerCIDDB :: TVar CIDDB
peerParameters :: IORef Parameters
myCIDDB :: IORef CIDDB
myParameters :: Parameters
quicVersion :: IORef Version
roleInfo :: IORef RoleInfo
mainThreadId :: ThreadId
tmouter :: IORef (IO ())
readers :: IORef (IO ())
sockets :: IORef [Socket]
connRecvQ :: RecvQ
connHooks :: Hooks
connQLog :: QLogger
connDebugLog :: DebugLogger
connState :: ConnState
connLDCC :: Connection -> LDCC
connResources :: Connection -> IORef (IO ())
handshakeCIDs :: Connection -> IORef AuthCIDs
negotiated :: Connection -> IORef Negotiated
currentKeyPhase :: Connection -> IORef (Bool, StreamId)
protectors :: Connection -> IOArray EncryptionLevel Protector
coders1RTT :: Connection -> IOArray Bool Coder1RTT
coders :: Connection -> IOArray EncryptionLevel Coder
ciphers :: Connection -> IOArray EncryptionLevel Cipher
pendingQ :: Connection -> Array EncryptionLevel (TVar [ReceivedPacket])
addressValidated :: Connection -> TVar Bool
bytesRx :: Connection -> TVar StreamId
bytesTx :: Connection -> TVar StreamId
minIdleTimeout :: Connection -> IORef Microseconds
migrationState :: Connection -> TVar MigrationState
flowRx :: Connection -> IORef Flow
flowTx :: Connection -> TVar Flow
peerStreamId :: Connection -> IORef Concurrency
myUniStreamId :: Connection -> TVar Concurrency
myStreamId :: Connection -> TVar Concurrency
streamTable :: Connection -> IORef StreamTable
peerPacketNumber :: Connection -> IORef StreamId
delayedAckCancel :: Connection -> IORef (IO ())
delayedAckCount :: Connection -> IORef StreamId
shared :: Connection -> Shared
migrationQ :: Connection -> MigrationQ
outputQ :: Connection -> OutputQ
cryptoQ :: Connection -> CryptoQ
inputQ :: Connection -> InputQ
peerCIDDB :: Connection -> TVar CIDDB
peerParameters :: Connection -> IORef Parameters
myCIDDB :: Connection -> IORef CIDDB
myParameters :: Connection -> Parameters
quicVersion :: Connection -> IORef Version
roleInfo :: Connection -> IORef RoleInfo
mainThreadId :: Connection -> ThreadId
tmouter :: Connection -> IORef (IO ())
readers :: Connection -> IORef (IO ())
sockets :: Connection -> IORef [Socket]
connRecvQ :: Connection -> RecvQ
connHooks :: Connection -> Hooks
connQLog :: Connection -> QLogger
connDebugLog :: Connection -> DebugLogger
connState :: Connection -> ConnState
..} Stream
strm =
    IORef StreamTable -> (StreamTable -> StreamTable) -> IO ()
forall a. IORef a -> (a -> a) -> IO ()
atomicModifyIORef'' IORef StreamTable
streamTable ((StreamTable -> StreamTable) -> IO ())
-> (StreamTable -> StreamTable) -> IO ()
forall a b. (a -> b) -> a -> b
$ StreamId -> StreamTable -> StreamTable
deleteStream (StreamId -> StreamTable -> StreamTable)
-> StreamId -> StreamTable -> StreamTable
forall a b. (a -> b) -> a -> b
$ Stream -> StreamId
streamId Stream
strm

initialRxMaxStreamData :: Connection -> StreamId -> Int
initialRxMaxStreamData :: Connection -> StreamId -> StreamId
initialRxMaxStreamData Connection
conn StreamId
sid
    | Connection -> Bool
forall a. Connector a => a -> Bool
isClient Connection
conn = StreamId -> Parameters -> StreamId
clientInitial StreamId
sid Parameters
params
    | Bool
otherwise     = StreamId -> Parameters -> StreamId
serverInitial StreamId
sid Parameters
params
  where
    params :: Parameters
params = Connection -> Parameters
getMyParameters Connection
conn

clientInitial :: StreamId -> Parameters -> Int
clientInitial :: StreamId -> Parameters -> StreamId
clientInitial StreamId
sid Parameters
params
  | StreamId -> Bool
isClientInitiatedBidirectional  StreamId
sid = Parameters -> StreamId
initialMaxStreamDataBidiRemote Parameters
params
  | StreamId -> Bool
isServerInitiatedBidirectional  StreamId
sid = Parameters -> StreamId
initialMaxStreamDataBidiLocal  Parameters
params
  -- intentionally not using isClientInitiatedUnidirectional
  | Bool
otherwise                           = Parameters -> StreamId
initialMaxStreamDataUni        Parameters
params

serverInitial :: StreamId -> Parameters -> Int
serverInitial :: StreamId -> Parameters -> StreamId
serverInitial StreamId
sid Parameters
params
  | StreamId -> Bool
isServerInitiatedBidirectional  StreamId
sid = Parameters -> StreamId
initialMaxStreamDataBidiRemote Parameters
params
  | StreamId -> Bool
isClientInitiatedBidirectional  StreamId
sid = Parameters -> StreamId
initialMaxStreamDataBidiLocal  Parameters
params
  | Bool
otherwise                           = Parameters -> StreamId
initialMaxStreamDataUni        Parameters
params

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

setupCryptoStreams :: Connection -> IO ()
setupCryptoStreams :: Connection -> IO ()
setupCryptoStreams conn :: Connection
conn@Connection{Array EncryptionLevel (TVar [ReceivedPacket])
IOArray Bool Coder1RTT
IOArray EncryptionLevel Cipher
IOArray EncryptionLevel Protector
IOArray EncryptionLevel Coder
ThreadId
TVar Bool
TVar StreamId
TVar Flow
TVar Concurrency
TVar MigrationState
TVar CIDDB
IORef StreamId
IORef [Socket]
IORef (IO ())
IORef (Bool, StreamId)
IORef Microseconds
IORef Version
IORef Flow
IORef StreamTable
IORef AuthCIDs
IORef Parameters
IORef Concurrency
IORef Negotiated
IORef CIDDB
IORef RoleInfo
MigrationQ
OutputQ
CryptoQ
InputQ
RecvQ
ConnState
Parameters
LDCC
Hooks
Shared
DebugLogger
QLogger
connLDCC :: LDCC
connResources :: IORef (IO ())
handshakeCIDs :: IORef AuthCIDs
negotiated :: IORef Negotiated
currentKeyPhase :: IORef (Bool, StreamId)
protectors :: IOArray EncryptionLevel Protector
coders1RTT :: IOArray Bool Coder1RTT
coders :: IOArray EncryptionLevel Coder
ciphers :: IOArray EncryptionLevel Cipher
pendingQ :: Array EncryptionLevel (TVar [ReceivedPacket])
addressValidated :: TVar Bool
bytesRx :: TVar StreamId
bytesTx :: TVar StreamId
minIdleTimeout :: IORef Microseconds
migrationState :: TVar MigrationState
flowRx :: IORef Flow
flowTx :: TVar Flow
peerStreamId :: IORef Concurrency
myUniStreamId :: TVar Concurrency
myStreamId :: TVar Concurrency
streamTable :: IORef StreamTable
peerPacketNumber :: IORef StreamId
delayedAckCancel :: IORef (IO ())
delayedAckCount :: IORef StreamId
shared :: Shared
migrationQ :: MigrationQ
outputQ :: OutputQ
cryptoQ :: CryptoQ
inputQ :: InputQ
peerCIDDB :: TVar CIDDB
peerParameters :: IORef Parameters
myCIDDB :: IORef CIDDB
myParameters :: Parameters
quicVersion :: IORef Version
roleInfo :: IORef RoleInfo
mainThreadId :: ThreadId
tmouter :: IORef (IO ())
readers :: IORef (IO ())
sockets :: IORef [Socket]
connRecvQ :: RecvQ
connHooks :: Hooks
connQLog :: QLogger
connDebugLog :: DebugLogger
connState :: ConnState
connLDCC :: Connection -> LDCC
connResources :: Connection -> IORef (IO ())
handshakeCIDs :: Connection -> IORef AuthCIDs
negotiated :: Connection -> IORef Negotiated
currentKeyPhase :: Connection -> IORef (Bool, StreamId)
protectors :: Connection -> IOArray EncryptionLevel Protector
coders1RTT :: Connection -> IOArray Bool Coder1RTT
coders :: Connection -> IOArray EncryptionLevel Coder
ciphers :: Connection -> IOArray EncryptionLevel Cipher
pendingQ :: Connection -> Array EncryptionLevel (TVar [ReceivedPacket])
addressValidated :: Connection -> TVar Bool
bytesRx :: Connection -> TVar StreamId
bytesTx :: Connection -> TVar StreamId
minIdleTimeout :: Connection -> IORef Microseconds
migrationState :: Connection -> TVar MigrationState
flowRx :: Connection -> IORef Flow
flowTx :: Connection -> TVar Flow
peerStreamId :: Connection -> IORef Concurrency
myUniStreamId :: Connection -> TVar Concurrency
myStreamId :: Connection -> TVar Concurrency
streamTable :: Connection -> IORef StreamTable
peerPacketNumber :: Connection -> IORef StreamId
delayedAckCancel :: Connection -> IORef (IO ())
delayedAckCount :: Connection -> IORef StreamId
shared :: Connection -> Shared
migrationQ :: Connection -> MigrationQ
outputQ :: Connection -> OutputQ
cryptoQ :: Connection -> CryptoQ
inputQ :: Connection -> InputQ
peerCIDDB :: Connection -> TVar CIDDB
peerParameters :: Connection -> IORef Parameters
myCIDDB :: Connection -> IORef CIDDB
myParameters :: Connection -> Parameters
quicVersion :: Connection -> IORef Version
roleInfo :: Connection -> IORef RoleInfo
mainThreadId :: Connection -> ThreadId
tmouter :: Connection -> IORef (IO ())
readers :: Connection -> IORef (IO ())
sockets :: Connection -> IORef [Socket]
connRecvQ :: Connection -> RecvQ
connHooks :: Connection -> Hooks
connQLog :: Connection -> QLogger
connDebugLog :: Connection -> DebugLogger
connState :: Connection -> ConnState
..} = do
    StreamTable
stbl0 <- IORef StreamTable -> IO StreamTable
forall a. IORef a -> IO a
readIORef IORef StreamTable
streamTable
    StreamTable
stbl <- Connection -> StreamTable -> IO StreamTable
insertCryptoStreams Connection
conn StreamTable
stbl0
    IORef StreamTable -> StreamTable -> IO ()
forall a. IORef a -> a -> IO ()
writeIORef IORef StreamTable
streamTable StreamTable
stbl

clearCryptoStream :: Connection -> EncryptionLevel -> IO ()
clearCryptoStream :: Connection -> EncryptionLevel -> IO ()
clearCryptoStream Connection{Array EncryptionLevel (TVar [ReceivedPacket])
IOArray Bool Coder1RTT
IOArray EncryptionLevel Cipher
IOArray EncryptionLevel Protector
IOArray EncryptionLevel Coder
ThreadId
TVar Bool
TVar StreamId
TVar Flow
TVar Concurrency
TVar MigrationState
TVar CIDDB
IORef StreamId
IORef [Socket]
IORef (IO ())
IORef (Bool, StreamId)
IORef Microseconds
IORef Version
IORef Flow
IORef StreamTable
IORef AuthCIDs
IORef Parameters
IORef Concurrency
IORef Negotiated
IORef CIDDB
IORef RoleInfo
MigrationQ
OutputQ
CryptoQ
InputQ
RecvQ
ConnState
Parameters
LDCC
Hooks
Shared
DebugLogger
QLogger
connLDCC :: LDCC
connResources :: IORef (IO ())
handshakeCIDs :: IORef AuthCIDs
negotiated :: IORef Negotiated
currentKeyPhase :: IORef (Bool, StreamId)
protectors :: IOArray EncryptionLevel Protector
coders1RTT :: IOArray Bool Coder1RTT
coders :: IOArray EncryptionLevel Coder
ciphers :: IOArray EncryptionLevel Cipher
pendingQ :: Array EncryptionLevel (TVar [ReceivedPacket])
addressValidated :: TVar Bool
bytesRx :: TVar StreamId
bytesTx :: TVar StreamId
minIdleTimeout :: IORef Microseconds
migrationState :: TVar MigrationState
flowRx :: IORef Flow
flowTx :: TVar Flow
peerStreamId :: IORef Concurrency
myUniStreamId :: TVar Concurrency
myStreamId :: TVar Concurrency
streamTable :: IORef StreamTable
peerPacketNumber :: IORef StreamId
delayedAckCancel :: IORef (IO ())
delayedAckCount :: IORef StreamId
shared :: Shared
migrationQ :: MigrationQ
outputQ :: OutputQ
cryptoQ :: CryptoQ
inputQ :: InputQ
peerCIDDB :: TVar CIDDB
peerParameters :: IORef Parameters
myCIDDB :: IORef CIDDB
myParameters :: Parameters
quicVersion :: IORef Version
roleInfo :: IORef RoleInfo
mainThreadId :: ThreadId
tmouter :: IORef (IO ())
readers :: IORef (IO ())
sockets :: IORef [Socket]
connRecvQ :: RecvQ
connHooks :: Hooks
connQLog :: QLogger
connDebugLog :: DebugLogger
connState :: ConnState
connLDCC :: Connection -> LDCC
connResources :: Connection -> IORef (IO ())
handshakeCIDs :: Connection -> IORef AuthCIDs
negotiated :: Connection -> IORef Negotiated
currentKeyPhase :: Connection -> IORef (Bool, StreamId)
protectors :: Connection -> IOArray EncryptionLevel Protector
coders1RTT :: Connection -> IOArray Bool Coder1RTT
coders :: Connection -> IOArray EncryptionLevel Coder
ciphers :: Connection -> IOArray EncryptionLevel Cipher
pendingQ :: Connection -> Array EncryptionLevel (TVar [ReceivedPacket])
addressValidated :: Connection -> TVar Bool
bytesRx :: Connection -> TVar StreamId
bytesTx :: Connection -> TVar StreamId
minIdleTimeout :: Connection -> IORef Microseconds
migrationState :: Connection -> TVar MigrationState
flowRx :: Connection -> IORef Flow
flowTx :: Connection -> TVar Flow
peerStreamId :: Connection -> IORef Concurrency
myUniStreamId :: Connection -> TVar Concurrency
myStreamId :: Connection -> TVar Concurrency
streamTable :: Connection -> IORef StreamTable
peerPacketNumber :: Connection -> IORef StreamId
delayedAckCancel :: Connection -> IORef (IO ())
delayedAckCount :: Connection -> IORef StreamId
shared :: Connection -> Shared
migrationQ :: Connection -> MigrationQ
outputQ :: Connection -> OutputQ
cryptoQ :: Connection -> CryptoQ
inputQ :: Connection -> InputQ
peerCIDDB :: Connection -> TVar CIDDB
peerParameters :: Connection -> IORef Parameters
myCIDDB :: Connection -> IORef CIDDB
myParameters :: Connection -> Parameters
quicVersion :: Connection -> IORef Version
roleInfo :: Connection -> IORef RoleInfo
mainThreadId :: Connection -> ThreadId
tmouter :: Connection -> IORef (IO ())
readers :: Connection -> IORef (IO ())
sockets :: Connection -> IORef [Socket]
connRecvQ :: Connection -> RecvQ
connHooks :: Connection -> Hooks
connQLog :: Connection -> QLogger
connDebugLog :: Connection -> DebugLogger
connState :: Connection -> ConnState
..} EncryptionLevel
lvl =
    IORef StreamTable -> (StreamTable -> StreamTable) -> IO ()
forall a. IORef a -> (a -> a) -> IO ()
atomicModifyIORef'' IORef StreamTable
streamTable ((StreamTable -> StreamTable) -> IO ())
-> (StreamTable -> StreamTable) -> IO ()
forall a b. (a -> b) -> a -> b
$ EncryptionLevel -> StreamTable -> StreamTable
deleteCryptoStream EncryptionLevel
lvl

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

getCryptoStream :: Connection -> EncryptionLevel -> IO (Maybe Stream)
getCryptoStream :: Connection -> EncryptionLevel -> IO (Maybe Stream)
getCryptoStream Connection{Array EncryptionLevel (TVar [ReceivedPacket])
IOArray Bool Coder1RTT
IOArray EncryptionLevel Cipher
IOArray EncryptionLevel Protector
IOArray EncryptionLevel Coder
ThreadId
TVar Bool
TVar StreamId
TVar Flow
TVar Concurrency
TVar MigrationState
TVar CIDDB
IORef StreamId
IORef [Socket]
IORef (IO ())
IORef (Bool, StreamId)
IORef Microseconds
IORef Version
IORef Flow
IORef StreamTable
IORef AuthCIDs
IORef Parameters
IORef Concurrency
IORef Negotiated
IORef CIDDB
IORef RoleInfo
MigrationQ
OutputQ
CryptoQ
InputQ
RecvQ
ConnState
Parameters
LDCC
Hooks
Shared
DebugLogger
QLogger
connLDCC :: LDCC
connResources :: IORef (IO ())
handshakeCIDs :: IORef AuthCIDs
negotiated :: IORef Negotiated
currentKeyPhase :: IORef (Bool, StreamId)
protectors :: IOArray EncryptionLevel Protector
coders1RTT :: IOArray Bool Coder1RTT
coders :: IOArray EncryptionLevel Coder
ciphers :: IOArray EncryptionLevel Cipher
pendingQ :: Array EncryptionLevel (TVar [ReceivedPacket])
addressValidated :: TVar Bool
bytesRx :: TVar StreamId
bytesTx :: TVar StreamId
minIdleTimeout :: IORef Microseconds
migrationState :: TVar MigrationState
flowRx :: IORef Flow
flowTx :: TVar Flow
peerStreamId :: IORef Concurrency
myUniStreamId :: TVar Concurrency
myStreamId :: TVar Concurrency
streamTable :: IORef StreamTable
peerPacketNumber :: IORef StreamId
delayedAckCancel :: IORef (IO ())
delayedAckCount :: IORef StreamId
shared :: Shared
migrationQ :: MigrationQ
outputQ :: OutputQ
cryptoQ :: CryptoQ
inputQ :: InputQ
peerCIDDB :: TVar CIDDB
peerParameters :: IORef Parameters
myCIDDB :: IORef CIDDB
myParameters :: Parameters
quicVersion :: IORef Version
roleInfo :: IORef RoleInfo
mainThreadId :: ThreadId
tmouter :: IORef (IO ())
readers :: IORef (IO ())
sockets :: IORef [Socket]
connRecvQ :: RecvQ
connHooks :: Hooks
connQLog :: QLogger
connDebugLog :: DebugLogger
connState :: ConnState
connLDCC :: Connection -> LDCC
connResources :: Connection -> IORef (IO ())
handshakeCIDs :: Connection -> IORef AuthCIDs
negotiated :: Connection -> IORef Negotiated
currentKeyPhase :: Connection -> IORef (Bool, StreamId)
protectors :: Connection -> IOArray EncryptionLevel Protector
coders1RTT :: Connection -> IOArray Bool Coder1RTT
coders :: Connection -> IOArray EncryptionLevel Coder
ciphers :: Connection -> IOArray EncryptionLevel Cipher
pendingQ :: Connection -> Array EncryptionLevel (TVar [ReceivedPacket])
addressValidated :: Connection -> TVar Bool
bytesRx :: Connection -> TVar StreamId
bytesTx :: Connection -> TVar StreamId
minIdleTimeout :: Connection -> IORef Microseconds
migrationState :: Connection -> TVar MigrationState
flowRx :: Connection -> IORef Flow
flowTx :: Connection -> TVar Flow
peerStreamId :: Connection -> IORef Concurrency
myUniStreamId :: Connection -> TVar Concurrency
myStreamId :: Connection -> TVar Concurrency
streamTable :: Connection -> IORef StreamTable
peerPacketNumber :: Connection -> IORef StreamId
delayedAckCancel :: Connection -> IORef (IO ())
delayedAckCount :: Connection -> IORef StreamId
shared :: Connection -> Shared
migrationQ :: Connection -> MigrationQ
outputQ :: Connection -> OutputQ
cryptoQ :: Connection -> CryptoQ
inputQ :: Connection -> InputQ
peerCIDDB :: Connection -> TVar CIDDB
peerParameters :: Connection -> IORef Parameters
myCIDDB :: Connection -> IORef CIDDB
myParameters :: Connection -> Parameters
quicVersion :: Connection -> IORef Version
roleInfo :: Connection -> IORef RoleInfo
mainThreadId :: Connection -> ThreadId
tmouter :: Connection -> IORef (IO ())
readers :: Connection -> IORef (IO ())
sockets :: Connection -> IORef [Socket]
connRecvQ :: Connection -> RecvQ
connHooks :: Connection -> Hooks
connQLog :: Connection -> QLogger
connDebugLog :: Connection -> DebugLogger
connState :: Connection -> ConnState
..} EncryptionLevel
lvl =
    EncryptionLevel -> StreamTable -> Maybe Stream
lookupCryptoStream EncryptionLevel
lvl (StreamTable -> Maybe Stream)
-> IO StreamTable -> IO (Maybe Stream)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> IORef StreamTable -> IO StreamTable
forall a. IORef a -> IO a
readIORef IORef StreamTable
streamTable