Safe Haskell | None |
---|---|
Language | Haskell2010 |
Network.QUIC.Internal
Synopsis
- defaultHooks :: Hooks
- data Hooks = Hooks {
- onCloseCompleted :: IO ()
- onPlainCreated :: EncryptionLevel -> Plain -> Plain
- onTransportParametersCreated :: Parameters -> Parameters
- onTLSExtensionCreated :: [ExtensionRaw] -> [ExtensionRaw]
- onTLSHandshakeCreated :: [(EncryptionLevel, CryptoData)] -> ([(EncryptionLevel, CryptoData)], Bool)
- onResetStreamReceived :: Stream -> ApplicationProtocolError -> IO ()
- onServerReady :: IO ()
- onConnectionEstablished :: ConnectionInfo -> IO ()
- data ClientConfig = ClientConfig {
- ccVersion :: Version
- ccVersions :: [Version]
- ccCiphers :: [Cipher]
- ccGroups :: [Group]
- ccParameters :: Parameters
- ccKeyLog :: String -> IO ()
- ccQLog :: Maybe FilePath
- ccCredentials :: Credentials
- ccHooks :: Hooks
- ccTlsHooks :: ClientHooks
- ccUse0RTT :: Bool
- ccServerName :: HostName
- ccPortName :: ServiceName
- ccALPN :: Version -> IO (Maybe [ByteString])
- ccValidate :: Bool
- ccResumption :: ResumptionInfo
- ccPacketSize :: Maybe Int
- ccDebugLog :: Bool
- ccSockConnected :: Bool
- ccWatchDog :: Bool
- ccServerNameOverride :: Maybe HostName
- defaultClientConfig :: ClientConfig
- data ServerConfig = ServerConfig {
- scVersions :: [Version]
- scCiphers :: [Cipher]
- scGroups :: [Group]
- scParameters :: Parameters
- scKeyLog :: String -> IO ()
- scQLog :: Maybe FilePath
- scCredentials :: Credentials
- scHooks :: Hooks
- scTlsHooks :: ServerHooks
- scUse0RTT :: Bool
- scAddresses :: [(IP, PortNumber)]
- scALPN :: Maybe (Version -> [ByteString] -> IO ByteString)
- scRequireRetry :: Bool
- scSessionManager :: SessionManager
- scDebugLog :: Maybe FilePath
- scTicketLifetime :: Int
- defaultServerConfig :: ServerConfig
- newtype Input = InpStream Stream
- timeout :: Microseconds -> String -> IO a -> IO (Maybe a)
- data Coder = Coder {
- encrypt :: Buffer -> PlainText -> AssDat -> PacketNumber -> IO Int
- decrypt :: Buffer -> CipherText -> AssDat -> PacketNumber -> IO Int
- supplement :: Maybe Supplement
- data Shared = Shared {}
- getVersion :: Connection -> IO Version
- setVersion :: Connection -> Version -> IO ()
- data Negotiated = Negotiated {}
- data Connection = Connection {
- connState :: ConnState
- connDebugLog :: DebugLogger
- connQLog :: QLogger
- connHooks :: Hooks
- connSend :: ~Send
- connRecv :: ~Recv
- connRecvQ :: RecvQ
- connSocket :: IORef Socket
- genStatelessResetToken :: CID -> StatelessResetToken
- readers :: IORef (Map Word64 (Weak ThreadId))
- mainThreadId :: ThreadId
- controlRate :: Rate
- roleInfo :: IORef RoleInfo
- quicVersionInfo :: IORef VersionInfo
- origVersionInfo :: VersionInfo
- myParameters :: Parameters
- myCIDDB :: IORef CIDDB
- peerParameters :: IORef Parameters
- peerCIDDB :: TVar CIDDB
- peerInfo :: IORef PeerInfo
- inputQ :: InputQ
- cryptoQ :: CryptoQ
- outputQ :: OutputQ
- outputRate :: Rate
- shared :: Shared
- delayedAckCount :: IORef Int
- delayedAckCancel :: IORef (IO ())
- peerPacketNumber :: IORef PacketNumber
- streamTable :: IORef StreamTable
- myStreamId :: TVar Concurrency
- myUniStreamId :: TVar Concurrency
- peerStreamId :: IORef Concurrency
- peerUniStreamId :: IORef Concurrency
- flowTx :: TVar TxFlow
- flowRx :: IORef RxFlow
- migrationState :: TVar MigrationState
- sentRetirePriorTo :: IORef Bool
- minIdleTimeout :: IORef Microseconds
- bytesTx :: IORef Int
- bytesRx :: IORef Int
- pendingQ :: Array EncryptionLevel (TVar [ReceivedPacket])
- ciphers :: IOArray EncryptionLevel Cipher
- coders :: IOArray EncryptionLevel Coder
- coders1RTT :: IOArray Bool Coder1RTT
- protectors :: IOArray EncryptionLevel Protector
- currentKeyPhase :: IORef (Bool, PacketNumber)
- negotiated :: IORef Negotiated
- connMyAuthCIDs :: IORef AuthCIDs
- connPeerAuthCIDs :: IORef AuthCIDs
- encodeBuf :: Buffer
- encryptRes :: SizedBuffer
- decryptBuf :: Buffer
- connResources :: IORef (IO ())
- connLDCC :: LDCC
- abortConnection :: Connection -> ApplicationProtocolError -> ReasonPhrase -> IO ()
- wait0RTTReady :: Connection -> IO ()
- wait1RTTReady :: Connection -> IO ()
- waitEstablished :: Connection -> IO ()
- getResumptionInfo :: Connection -> IO ResumptionInfo
- data Crypto = InpHandshake EncryptionLevel ByteString
- setEncryptionLevel :: Connection -> EncryptionLevel -> IO ()
- waitEncryptionLevel :: Connection -> EncryptionLevel -> IO ()
- putOffCrypto :: Connection -> EncryptionLevel -> ReceivedPacket -> IO ()
- getCipher :: Connection -> EncryptionLevel -> IO Cipher
- setCipher :: Connection -> EncryptionLevel -> Cipher -> IO ()
- getTLSMode :: Connection -> IO HandshakeMode13
- getApplicationProtocol :: Connection -> IO (Maybe NegotiatedProtocol)
- setNegotiated :: Connection -> HandshakeMode13 -> Maybe NegotiatedProtocol -> ApplicationSecretInfo -> IO ()
- dropSecrets :: Connection -> EncryptionLevel -> IO ()
- initializeCoder :: Connection -> EncryptionLevel -> TrafficSecrets a -> IO ()
- initializeCoder1RTT :: Connection -> TrafficSecrets ApplicationSecret -> IO ()
- updateCoder1RTT :: Connection -> Bool -> IO ()
- getCoder :: Connection -> EncryptionLevel -> Bool -> IO Coder
- getProtector :: Connection -> EncryptionLevel -> IO Protector
- getCurrentKeyPhase :: Connection -> IO (Bool, PacketNumber)
- setCurrentKeyPhase :: Connection -> Bool -> PacketNumber -> IO ()
- getMyCID :: Connection -> IO CID
- getMyCIDs :: Connection -> IO [CID]
- getPeerCID :: Connection -> IO CID
- isMyCID :: Connection -> CID -> IO Bool
- myCIDsInclude :: Connection -> CID -> IO (Maybe Int)
- shouldUpdateMyCID :: Connection -> Int -> IO Bool
- shouldUpdatePeerCID :: Connection -> IO Bool
- resetPeerCID :: Connection -> CID -> IO ()
- getNewMyCID :: Connection -> IO CIDInfo
- getMyCIDSeqNum :: Connection -> IO Int
- setMyCID :: Connection -> CID -> IO ()
- setPeerCIDAndRetireCIDs :: Connection -> Int -> IO [Int]
- retirePeerCID :: Connection -> Int -> IO ()
- retireMyCID :: Connection -> Int -> IO (Maybe CIDInfo)
- addPeerCID :: Connection -> CIDInfo -> IO Bool
- waitPeerCID :: Connection -> IO CIDInfo
- choosePeerCIDForPrivacy :: Connection -> IO ()
- setPeerStatelessResetToken :: Connection -> StatelessResetToken -> IO ()
- isStatelessRestTokenValid :: Connection -> StatelessResetToken -> IO Bool
- setMigrationStarted :: Connection -> IO ()
- isPathValidating :: Connection -> IO Bool
- checkResponse :: Connection -> PathData -> IO ()
- validatePath :: Connection -> PathInfo -> Maybe CIDInfo -> IO ()
- getMyRetirePriorTo :: Connection -> IO Int
- setMyRetirePriorTo :: Connection -> Int -> IO ()
- getPeerRetirePriorTo :: Connection -> IO Int
- setPeerRetirePriorTo :: Connection -> Int -> IO ()
- checkPeerCIDCapacity :: Connection -> IO Bool
- setVersionInfo :: Connection -> VersionInfo -> IO ()
- getVersionInfo :: Connection -> IO VersionInfo
- getOriginalVersion :: Connection -> Version
- getSocket :: Connection -> IO Socket
- setSocket :: Connection -> Socket -> IO Socket
- clearSocket :: Connection -> IO Socket
- getPathInfo :: Connection -> IO PathInfo
- addPathInfo :: Connection -> PathInfo -> IO ()
- findPathInfo :: Connection -> SockAddr -> IO (Maybe PathInfo)
- getPeerAuthCIDs :: Connection -> IO AuthCIDs
- setPeerAuthCIDs :: Connection -> (AuthCIDs -> AuthCIDs) -> IO ()
- getClientDstCID :: Connection -> IO CID
- getMyParameters :: Connection -> Parameters
- getPeerParameters :: Connection -> IO Parameters
- setPeerParameters :: Connection -> Parameters -> IO ()
- modifytPeerParameters :: Connection -> ResumptionInfo -> IO ()
- delayedAck :: Connection -> IO ()
- resetDealyedAck :: Connection -> IO ()
- setMaxPacketSize :: Connection -> Int -> IO ()
- forkManaged :: Connection -> IO () -> IO ()
- killReaders :: Connection -> IO ()
- addResource :: Connection -> IO () -> IO ()
- freeResources :: Connection -> IO ()
- readMinIdleTimeout :: Connection -> IO Microseconds
- setMinIdleTimeout :: Connection -> Microseconds -> IO ()
- sendFrames :: Connection -> EncryptionLevel -> [Frame] -> IO ()
- closeConnection :: Connection -> TransportError -> ReasonPhrase -> IO ()
- nextPacketNumber :: Connection -> IO PacketNumber
- setPeerPacketNumber :: Connection -> PacketNumber -> IO ()
- getPeerPacketNumber :: Connection -> IO PacketNumber
- takeInput :: Connection -> IO Input
- setToken :: Connection -> Token -> IO ()
- getToken :: Connection -> IO Token
- setRetried :: Connection -> Bool -> IO ()
- getRetried :: Connection -> IO Bool
- setIncompatibleVN :: Connection -> Bool -> IO ()
- getIncompatibleVN :: Connection -> IO Bool
- setResumptionSession :: Connection -> SessionEstablish
- setNewToken :: Connection -> Token -> IO ()
- setResumptionParameters :: Connection -> Parameters -> IO ()
- setRegister :: Connection -> (CID -> Connection -> IO ()) -> (CID -> IO ()) -> IO ()
- getRegister :: Connection -> IO (CID -> Connection -> IO ())
- getUnregister :: Connection -> IO (CID -> IO ())
- setTokenManager :: Connection -> TokenManager -> IO ()
- getTokenManager :: Connection -> IO TokenManager
- setStopServer :: Connection -> IO () -> IO ()
- getStopServer :: Connection -> IO (IO ())
- setCertificateChain :: Connection -> Maybe CertificateChain -> IO ()
- getCertificateChain :: Connection -> IO (Maybe CertificateChain)
- setSockConnected :: Connection -> Bool -> IO ()
- getSockConnected :: Connection -> IO Bool
- setConnection0RTTReady :: Connection -> IO ()
- isConnection1RTTReady :: Connection -> IO Bool
- setConnection1RTTReady :: Connection -> IO ()
- isConnectionEstablished :: Connector a => a -> IO Bool
- setConnectionEstablished :: Connection -> IO ()
- isConnectionClosed :: Connection -> IO Bool
- setConnectionClosed :: Connection -> IO ()
- readConnectionFlowTx :: Connection -> STM TxFlow
- addTxData :: Connection -> Int -> STM ()
- setTxMaxData :: Connection -> Int -> IO ()
- getRxMaxData :: Connection -> IO Int
- updateFlowRx :: Connection -> Int -> IO (Maybe Int)
- checkRxMaxData :: Connection -> Int -> IO Bool
- addTxBytes :: Connection -> Int -> IO ()
- getTxBytes :: Connection -> IO Int
- addRxBytes :: Connection -> Int -> IO ()
- getRxBytes :: Connection -> IO Int
- addPathTxBytes :: PathInfo -> Int -> IO ()
- addPathRxBytes :: PathInfo -> Int -> IO ()
- setAddressValidated :: PathInfo -> IO ()
- waitAntiAmplificationFree :: Connection -> PathInfo -> Int -> IO ()
- checkAntiAmplificationFree :: PathInfo -> Int -> IO Bool
- getMyStreamId :: Connection -> IO Int
- possibleMyStreams :: Connection -> IO Int
- waitMyNewStreamId :: Connection -> IO StreamId
- waitMyNewUniStreamId :: Connection -> IO StreamId
- setTxMaxStreams :: Connection -> Int -> IO ()
- setTxUniMaxStreams :: Connection -> Int -> IO ()
- checkRxMaxStreams :: Connection -> StreamId -> IO Bool
- updatePeerStreamId :: Connection -> StreamId -> IO ()
- checkStreamIdRoom :: Connection -> Direction -> IO (Maybe Int)
- createStream :: Connection -> StreamId -> IO Stream
- findStream :: Connection -> StreamId -> IO (Maybe Stream)
- addStream :: Connection -> StreamId -> IO Stream
- delStream :: Connection -> Stream -> IO ()
- initialRxMaxStreamData :: Connection -> StreamId -> Int
- setupCryptoStreams :: Connection -> IO ()
- clearCryptoStream :: Connection -> EncryptionLevel -> IO ()
- getCryptoStream :: Connection -> EncryptionLevel -> IO (Maybe Stream)
- fire :: Connection -> Microseconds -> TimeoutCallback -> IO ()
- fire' :: Microseconds -> TimeoutCallback -> IO ()
- cfire :: Connection -> Microseconds -> TimeoutCallback -> IO (IO ())
- delay :: Microseconds -> IO ()
- dummySecrets :: TrafficSecrets a
- data CIDDB = CIDDB {
- usedCIDInfo :: CIDInfo
- cidInfos :: IntMap CIDInfo
- revInfos :: Map CID Int
- nextSeqNum :: Int
- retirePriorTo :: Int
- triggeredByMe :: Bool
- data RoleInfo
- = ClientInfo { }
- | ServerInfo {
- tokenManager :: ~TokenManager
- registerCID :: CID -> Connection -> IO ()
- unregisterCID :: CID -> IO ()
- askRetry :: Bool
- stopServer :: IO ()
- certChain :: Maybe CertificateChain
- defaultClientRoleInfo :: RoleInfo
- defaultServerRoleInfo :: RoleInfo
- newCIDDB :: CID -> CIDDB
- data MigrationState
- data PathInfo = PathInfo {}
- initialCoder :: Coder
- data Coder1RTT = Coder1RTT {}
- initialCoder1RTT :: Coder1RTT
- data Protector = Protector {}
- initialProtector :: Protector
- initialNegotiated :: Negotiated
- defaultTrafficSecrets :: (ClientTrafficSecret a, ServerTrafficSecret a)
- newtype StreamIdBase = StreamIdBase {}
- data Concurrency = Concurrency {}
- newConcurrency :: Role -> Direction -> Int -> Concurrency
- type Send = Buffer -> Int -> IO ()
- type Recv = IO ReceivedPacket
- data PeerInfo = PeerInfo {}
- newPathInfo :: SockAddr -> IO PathInfo
- type InputQ = TQueue Input
- type CryptoQ = TQueue Crypto
- type OutputQ = TQueue Output
- setDead :: Connection -> IO ()
- makePendingQ :: IO (Array EncryptionLevel (TVar [ReceivedPacket]))
- newConnection :: Role -> Parameters -> VersionInfo -> AuthCIDs -> AuthCIDs -> DebugLogger -> QLogger -> Hooks -> IORef Socket -> IORef PeerInfo -> RecvQ -> Send -> Recv -> (CID -> StatelessResetToken) -> IO Connection
- newShared :: IO Shared
- data Output
- clientConnection :: ClientConfig -> VersionInfo -> AuthCIDs -> AuthCIDs -> DebugLogger -> QLogger -> Hooks -> IORef Socket -> IORef PeerInfo -> RecvQ -> Send -> Recv -> (CID -> StatelessResetToken) -> IO Connection
- serverConnection :: ServerConfig -> VersionInfo -> AuthCIDs -> AuthCIDs -> DebugLogger -> QLogger -> Hooks -> IORef Socket -> IORef PeerInfo -> RecvQ -> Send -> Recv -> (CID -> StatelessResetToken) -> IO Connection
- type SendStreamQ = TQueue TxStreamData
- putInput :: Connection -> Input -> IO ()
- takeCrypto :: Connection -> IO Crypto
- putCrypto :: Connection -> Crypto -> IO ()
- isEmptyCryptoSTM :: Connection -> STM Bool
- takeOutputSTM :: Connection -> STM Output
- tryTakeOutput :: Connection -> IO (Maybe Output)
- tryPeekOutput :: Connection -> IO (Maybe Output)
- putOutput :: Connection -> Output -> IO ()
- isEmptyOutputSTM :: Connection -> STM Bool
- takeSendStreamQ :: Connection -> IO TxStreamData
- takeSendStreamQSTM :: Connection -> STM TxStreamData
- tryPeekSendStreamQ :: Connection -> IO (Maybe TxStreamData)
- putSendStreamQ :: Connection -> TxStreamData -> IO ()
- isEmptyStreamSTM :: Connection -> STM Bool
- outputLimit :: Int
- rateOK :: Connection -> IO Bool
- data Role
- class Connector a where
- getRole :: a -> Role
- getEncryptionLevel :: a -> IO EncryptionLevel
- getMaxPacketSize :: a -> IO Int
- getConnectionState :: a -> IO ConnectionState
- getPacketNumber :: a -> IO PacketNumber
- getAlive :: a -> IO Bool
- data ConnectionState
- data ConnState = ConnState {}
- isConnectionEstablished :: Connector a => a -> IO Bool
- newConnState :: Role -> IO ConnState
- isClient :: Connector a => a -> Bool
- isServer :: Connector a => a -> Bool
- newtype Mask = Mask ByteString
- newtype Key = Key ByteString
- data Cipher
- newtype IV = IV ByteString
- newtype Nonce = Nonce ByteString
- type Salt = ByteString
- type CipherText = ByteString
- type PlainText = ByteString
- newtype Label = Label ByteString
- type TrafficSecrets a = (ClientTrafficSecret a, ServerTrafficSecret a)
- newtype ServerTrafficSecret a = ServerTrafficSecret ByteString
- newtype ClientTrafficSecret a = ClientTrafficSecret ByteString
- data FusionContext
- fusionNewContext :: IO FusionContext
- fusionSetup :: Cipher -> FusionContext -> Key -> IV -> IO ()
- fusionEncrypt :: FusionContext -> Supplement -> Buffer -> PlainText -> AssDat -> PacketNumber -> IO Int
- fusionDecrypt :: FusionContext -> Buffer -> CipherText -> AssDat -> PacketNumber -> IO Int
- data Supplement
- fusionSetupSupplement :: Cipher -> Key -> IO Supplement
- fusionSetSample :: Supplement -> Buffer -> IO ()
- fusionGetMask :: Supplement -> IO Buffer
- isFusionAvailable :: IO Bool
- defaultCipher :: Cipher
- initialSecrets :: Version -> CID -> TrafficSecrets InitialSecret
- clientInitialSecret :: Version -> CID -> ClientTrafficSecret InitialSecret
- serverInitialSecret :: Version -> CID -> ServerTrafficSecret InitialSecret
- aeadKey :: Version -> Cipher -> Secret -> Key
- initialVector :: Version -> Cipher -> Secret -> IV
- nextSecret :: Version -> Cipher -> Secret -> Secret
- headerProtectionKey :: Version -> Cipher -> Secret -> Key
- niteEncrypt :: Cipher -> Key -> IV -> PlainText -> AssDat -> PacketNumber -> Maybe (CipherText, CipherText)
- niteEncrypt' :: Cipher -> Key -> Nonce -> PlainText -> AssDat -> Maybe (CipherText, CipherText)
- niteDecrypt :: Cipher -> Key -> IV -> CipherText -> AssDat -> PacketNumber -> Maybe PlainText
- niteDecrypt' :: Cipher -> Key -> Nonce -> CipherText -> AssDat -> Maybe PlainText
- protectionMask :: Cipher -> Key -> Sample -> Mask
- aes128gcmEncrypt :: Key -> Nonce -> PlainText -> AssDat -> Maybe (CipherText, CipherText)
- makeNonce :: IV -> ByteString -> Nonce
- makeNiteEncrypt :: Cipher -> Key -> IV -> NiteEncrypt
- makeNiteDecrypt :: Cipher -> Key -> IV -> NiteDecrypt
- makeNiteProtector :: Cipher -> Key -> IO (Buffer -> IO (), IO Buffer)
- data CID
- newtype Secret = Secret ByteString
- newtype AssDat = AssDat ByteString
- newtype Sample = Sample ByteString
- data InitialSecret
- tagLength :: Cipher -> Int
- sampleLength :: Cipher -> Int
- bsXOR :: ByteString -> ByteString -> ByteString
- calculateIntegrityTag :: Version -> CID -> ByteString -> ByteString
- data Builder
- type DebugLogger = Builder -> IO ()
- bhow :: Show a => a -> Builder
- stdoutLogger :: DebugLogger
- dirDebugLogger :: Maybe FilePath -> CID -> IO (DebugLogger, IO ())
- encryptToken :: TokenManager -> CryptoToken -> IO Token
- decryptToken :: TokenManager -> Token -> IO (Maybe CryptoToken)
- encodeVersionNegotiationPacket :: VersionNegotiationPacket -> IO ByteString
- encodeRetryPacket :: RetryPacket -> IO ByteString
- encodePlainPacket :: Connection -> SizedBuffer -> PlainPacket -> Maybe Int -> IO (Int, Int)
- decodePacket :: ByteString -> Bool -> IO (PacketI, ByteString)
- decodePackets :: ByteString -> Bool -> IO [PacketI]
- decodeCryptPackets :: ByteString -> Bool -> IO [(CryptPacket, EncryptionLevel, Int)]
- decryptCrypt :: Connection -> Crypt -> EncryptionLevel -> IO (Maybe Plain)
- decodeStatelessResetToken :: ByteString -> Maybe StatelessResetToken
- encodeFrames :: [Frame] -> IO ByteString
- decodeFramesBuffer :: Buffer -> BufferSize -> IO (Maybe [Frame])
- decodeFramesBS :: ByteString -> IO (Maybe [Frame])
- countZero :: Ptr Word8 -> Ptr Word8 -> IO Int
- isLong :: Word8 -> Bool
- isShort :: Flags Protected -> Bool
- protectFlags :: Flags Raw -> Word8 -> Flags Protected
- unprotectFlags :: Flags Protected -> Word8 -> Flags Raw
- encodeLongHeaderFlags :: Version -> LongHeaderPacketType -> Flags Raw -> Flags Raw -> Bool -> IO (Flags Raw)
- encodeShortHeaderFlags :: Flags Raw -> Flags Raw -> Bool -> Bool -> IO (Flags Raw)
- decodeLongHeaderPacketType :: Version -> Flags Protected -> LongHeaderPacketType
- encodePktNumLength :: Int -> Flags Raw
- decodePktNumLength :: Flags Raw -> Int
- versionNegotiationPacketType :: IO (Flags Raw)
- retryPacketType :: Version -> IO (Flags Raw)
- data CryptoToken = CryptoToken {}
- isRetryToken :: CryptoToken -> Bool
- generateToken :: Version -> Int -> IO CryptoToken
- generateRetryToken :: Version -> Int -> CID -> CID -> CID -> IO CryptoToken
- data Parameters = Parameters {
- originalDestinationConnectionId :: Maybe CID
- maxIdleTimeout :: Milliseconds
- statelessResetToken :: Maybe StatelessResetToken
- maxUdpPayloadSize :: Int
- initialMaxData :: Int
- initialMaxStreamDataBidiLocal :: Int
- initialMaxStreamDataBidiRemote :: Int
- initialMaxStreamDataUni :: Int
- initialMaxStreamsBidi :: Int
- initialMaxStreamsUni :: Int
- ackDelayExponent :: Int
- maxAckDelay :: Milliseconds
- disableActiveMigration :: Bool
- preferredAddress :: Maybe ByteString
- activeConnectionIdLimit :: Int
- initialSourceConnectionId :: Maybe CID
- retrySourceConnectionId :: Maybe CID
- grease :: Maybe ByteString
- greaseQuicBit :: Bool
- versionInformation :: Maybe VersionInfo
- defaultParameters :: Parameters
- baseParameters :: Parameters
- encodeParameters :: Parameters -> ByteString
- decodeParameters :: ByteString -> Maybe Parameters
- data AuthCIDs = AuthCIDs {
- initSrcCID :: Maybe CID
- origDstCID :: Maybe CID
- retrySrcCID :: Maybe CID
- defaultAuthCIDs :: AuthCIDs
- setCIDsToParameters :: AuthCIDs -> Parameters -> Parameters
- getCIDsToParameters :: Parameters -> AuthCIDs
- newtype Debug = Debug LogStr
- packetType :: Header -> LogStr
- class Qlog a where
- type QLogger = QlogMsg -> IO ()
- newQlogger :: TimeMicrosecond -> ByteString -> CID -> FastLogger -> IO QLogger
- class KeepQlog a where
- data QlogMsg
- = QRecvInitial
- | QSentRetry
- | QSent LogStr TimeMicrosecond
- | QReceived LogStr TimeMicrosecond
- | QDropped LogStr TimeMicrosecond
- | QMetricsUpdated LogStr TimeMicrosecond
- | QPacketLost LogStr TimeMicrosecond
- | QCongestionStateUpdated LogStr TimeMicrosecond
- | QLossTimerUpdated LogStr TimeMicrosecond
- | QDebug LogStr TimeMicrosecond
- | QParamsSet LogStr TimeMicrosecond
- | QCIDUpdate LogStr TimeMicrosecond
- qlogReceived :: (KeepQlog q, Qlog a) => q -> a -> TimeMicrosecond -> IO ()
- qlogDropped :: (KeepQlog q, Qlog a) => q -> a -> IO ()
- qlogRecvInitial :: KeepQlog q => q -> IO ()
- qlogSentRetry :: KeepQlog q => q -> IO ()
- qlogParamsSet :: KeepQlog q => q -> (Parameters, String) -> IO ()
- qlogDebug :: KeepQlog q => q -> Debug -> IO ()
- qlogCIDUpdate :: KeepQlog q => q -> LR -> IO ()
- data LR
- sw :: Show a => a -> LogStr
- data Stream
- data StreamTable
- newStream :: Connection -> Int -> Int -> StreamId -> IO Stream
- data TxStreamData = TxStreamData Stream [StreamData] Length Fin
- data StreamState = StreamState {
- streamOffset :: Offset
- streamFin :: Fin
- data RecvStreamQ = RecvStreamQ {}
- data RxStreamData = RxStreamData {
- rxstrmData :: StreamData
- rxstrmOff :: Offset
- rxstrmLen :: Length
- rxstrmFin :: Fin
- type Length = Int
- syncFinTx :: Stream -> IO ()
- waitFinTx :: Stream -> IO ()
- getTxStreamOffset :: Stream -> Int -> IO Offset
- isTxStreamClosed :: Stream -> IO Bool
- setTxStreamClosed :: Stream -> IO ()
- getRxStreamOffset :: Stream -> Int -> IO Offset
- isRxStreamClosed :: Stream -> IO Bool
- setRxStreamClosed :: Stream -> IO ()
- readStreamFlowTx :: Stream -> STM TxFlow
- addTxStreamData :: Stream -> Int -> STM ()
- setTxMaxStreamData :: Stream -> Int -> IO ()
- getRxMaxStreamData :: Stream -> IO Int
- updateStreamFlowRx :: Stream -> Int -> IO (Maybe Int)
- takeRecvStreamQwithSize :: Stream -> Int -> IO ByteString
- putRxStreamData :: Stream -> RxStreamData -> IO FlowCntl
- data FlowCntl
- tryReassemble :: Stream -> RxStreamData -> (StreamData -> IO ()) -> IO () -> IO Bool
- emptyStreamTable :: StreamTable
- lookupStream :: StreamId -> StreamTable -> Maybe Stream
- insertStream :: StreamId -> Stream -> StreamTable -> StreamTable
- deleteStream :: StreamId -> StreamTable -> StreamTable
- insertCryptoStreams :: Connection -> StreamTable -> IO StreamTable
- deleteCryptoStream :: EncryptionLevel -> StreamTable -> StreamTable
- lookupCryptoStream :: EncryptionLevel -> StreamTable -> Maybe Stream
- clientHandshaker :: QUICCallbacks -> ClientConfig -> Version -> AuthCIDs -> SessionEstablish -> Bool -> IO ()
- serverHandshaker :: QUICCallbacks -> ServerConfig -> Version -> IO Parameters -> IO ()
- data Header
- newtype Version = Version Word32
- decodeInt :: ByteString -> Int64
- encodeInt :: Int64 -> ByteString
- encodeInt8 :: Int64 -> ByteString
- type Bytes = ShortByteString
- data Raw
- type Range = Int
- data QUICException
- = ConnectionIsClosed ReasonPhrase
- | TransportErrorIsReceived TransportError ReasonPhrase
- | TransportErrorIsSent TransportError ReasonPhrase
- | ApplicationProtocolErrorIsReceived ApplicationProtocolError ReasonPhrase
- | ApplicationProtocolErrorIsSent ApplicationProtocolError ReasonPhrase
- | ConnectionIsTimeout String
- | ConnectionIsReset
- | StreamIsClosed
- | HandshakeFailed AlertDescription
- | VersionIsUnknown Word32
- | NoVersionIsSpecified
- | VersionNegotiationFailed
- | BadThingHappen SomeException
- pattern InternalError :: TransportError
- is0RTTPossible :: ResumptionInfo -> Bool
- data Direction
- type StreamId = Int
- isClientInitiatedBidirectional :: StreamId -> Bool
- isServerInitiatedBidirectional :: StreamId -> Bool
- isClientInitiatedUnidirectional :: StreamId -> Bool
- isServerInitiatedUnidirectional :: StreamId -> Bool
- newtype TransportError = TransportError Int
- pattern NoError :: TransportError
- pattern ConnectionRefused :: TransportError
- pattern FlowControlError :: TransportError
- pattern StreamLimitError :: TransportError
- pattern StreamStateError :: TransportError
- pattern FinalSizeError :: TransportError
- pattern FrameEncodingError :: TransportError
- pattern TransportParameterError :: TransportError
- pattern ConnectionIdLimitError :: TransportError
- pattern ProtocolViolation :: TransportError
- pattern InvalidToken :: TransportError
- pattern ApplicationError :: TransportError
- pattern CryptoBufferExceeded :: TransportError
- pattern KeyUpdateError :: TransportError
- pattern AeadLimitReached :: TransportError
- pattern NoViablePath :: TransportError
- cryptoError :: AlertDescription -> TransportError
- newtype ApplicationProtocolError = ApplicationProtocolError Int
- data ResumptionInfo = ResumptionInfo {
- resumptionVersion :: Version
- resumptionSession :: [(SessionID, SessionData)]
- resumptionToken :: Token
- resumptionRetry :: Bool
- resumptionActiveConnectionIdLimit :: Int
- resumptionInitialMaxData :: Int
- resumptionInitialMaxStreamDataBidiLocal :: Int
- resumptionInitialMaxStreamDataBidiRemote :: Int
- resumptionInitialMaxStreamDataUni :: Int
- resumptionInitialMaxStreamsBidi :: Int
- resumptionInitialMaxStreamsUni :: Int
- isResumptionPossible :: ResumptionInfo -> Bool
- type PacketNumber = Int
- type Token = ByteString
- newtype CID = CID Bytes
- data Frame
- = Padding Int
- | Ping
- | Ack AckInfo Delay
- | ResetStream StreamId ApplicationProtocolError Int
- | StopSending StreamId ApplicationProtocolError
- | CryptoF Offset CryptoData
- | NewToken Token
- | StreamF StreamId Offset [StreamData] Fin
- | MaxData Int
- | MaxStreamData StreamId Int
- | MaxStreams Direction Int
- | DataBlocked Int
- | StreamDataBlocked StreamId Int
- | StreamsBlocked Direction Int
- | NewConnectionID CIDInfo SeqNum
- | RetireConnectionID SeqNum
- | PathChallenge PathData
- | PathResponse PathData
- | ConnectionClose TransportError FrameType ReasonPhrase
- | ConnectionCloseApp ApplicationProtocolError ReasonPhrase
- | HandshakeDone
- | UnknownFrame Int
- newtype PeerPacketNumbers = PeerPacketNumbers IntSet
- newtype RecvQ = RecvQ (TQueue ReceivedPacket)
- type Close = IO ()
- data SizedBuffer = SizedBuffer Buffer BufferSize
- myCIDLength :: Int
- newCID :: IO CID
- fromCID :: CID -> ByteString
- toCID :: ByteString -> CID
- makeCID :: ShortByteString -> CID
- unpackCID :: CID -> (ShortByteString, Word8)
- nonZeroLengthCID :: CID -> SockAddr -> CID
- newtype StatelessResetToken = StatelessResetToken Bytes
- fromStatelessResetToken :: StatelessResetToken -> ByteString
- makeGenStatelessReset :: IO (CID -> StatelessResetToken)
- newtype PathData = PathData Bytes
- newPathData :: IO PathData
- data CIDInfo
- newCIDInfo :: Int -> CID -> StatelessResetToken -> CIDInfo
- maximumUdpPayloadSize :: Int
- type FrameType = Int
- encodeInt' :: WriteBuffer -> Int64 -> IO ()
- encodeInt'2 :: WriteBuffer -> Int64 -> IO ()
- encodeInt'4 :: WriteBuffer -> Int64 -> IO ()
- decodeInt' :: ReadBuffer -> IO Int64
- type SessionEstablish = SessionID -> SessionData -> IO (Maybe Ticket)
- newtype Milliseconds = Milliseconds Int64
- newtype Microseconds = Microseconds Int
- milliToMicro :: Milliseconds -> Microseconds
- microToMilli :: Microseconds -> Milliseconds
- type TimeMicrosecond = UnixTime
- timeMicrosecond0 :: UnixTime
- getTimeMicrosecond :: IO TimeMicrosecond
- getElapsedTimeMicrosecond :: TimeMicrosecond -> IO Microseconds
- elapsedTimeMicrosecond :: UnixTime -> UnixTime -> Microseconds
- getTimeoutInMicrosecond :: TimeMicrosecond -> IO Microseconds
- getPastTimeMicrosecond :: Microseconds -> IO TimeMicrosecond
- getFutureTimeMicrosecond :: Microseconds -> IO TimeMicrosecond
- addMicroseconds :: TimeMicrosecond -> Microseconds -> TimeMicrosecond
- type Gap = Int
- data AckInfo = AckInfo PacketNumber Range [(Gap, Range)]
- ackInfo0 :: AckInfo
- toAckInfo :: [PacketNumber] -> AckInfo
- fromAckInfo :: AckInfo -> [PacketNumber]
- fromAckInfoWithMin :: AckInfo -> PacketNumber -> [PacketNumber]
- fromAckInfoToPred :: AckInfo -> PacketNumber -> Bool
- emptyPeerPacketNumbers :: PeerPacketNumbers
- pattern VersionNegotiationError :: TransportError
- defaultQUICPacketSize :: Int
- defaultQUICPacketSizeForIPv4 :: Int
- defaultQUICPacketSizeForIPv6 :: Int
- maximumQUICHeaderSize :: Int
- idleTimeout :: Milliseconds
- type ReasonPhrase = ShortByteString
- type SeqNum = Int
- type Delay = Milliseconds
- type CryptoData = ByteString
- type StreamData = ByteString
- type Fin = Bool
- isClientInitiated :: StreamId -> Bool
- isServerInitiated :: StreamId -> Bool
- isBidirectional :: StreamId -> Bool
- isUnidirectional :: StreamId -> Bool
- emptyToken :: Token
- ackEliciting :: Frame -> Bool
- pathValidating :: Frame -> Bool
- inFlight :: Frame -> Bool
- rateControled :: Frame -> Bool
- pattern Negotiation :: Version
- pattern Version1 :: Version
- pattern Version2 :: Version
- pattern Draft29 :: Version
- pattern GreasingVersion :: Version
- pattern GreasingVersion2 :: Version
- isGreasingVersion :: Version -> Bool
- data VersionInfo = VersionInfo {
- chosenVersion :: Version
- otherVersions :: [Version]
- brokenVersionInfo :: VersionInfo
- extensionIDForTtransportParameter :: Version -> ExtensionID
- data PacketI
- data VersionNegotiationPacket = VersionNegotiationPacket CID CID [Version]
- data RetryPacket = RetryPacket Version CID CID Token (Either CID (ByteString, ByteString))
- data CryptPacket = CryptPacket Header Crypt
- data EncryptionLevel
- data BrokenPacket = BrokenPacket
- data PacketO
- data PlainPacket = PlainPacket Header Plain
- headerMyCID :: Header -> CID
- headerPeerCID :: Header -> CID
- data Plain = Plain {
- plainFlags :: Flags Raw
- plainPacketNumber :: PacketNumber
- plainFrames :: [Frame]
- plainMarks :: Int
- data Crypt = Crypt {}
- newtype Flags a = Flags Word8
- defaultPlainMarks :: Int
- setIllegalReservedBits :: Int -> Int
- setUnknownFrame :: Int -> Int
- setNoFrames :: Int -> Int
- setNoPaddings :: Int -> Int
- set4bytesPN :: Int -> Int
- isIllegalReservedBits :: Int -> Bool
- isUnknownFrame :: Int -> Bool
- isNoFrames :: Int -> Bool
- isNoPaddings :: Int -> Bool
- is4bytesPN :: Int -> Bool
- isCryptDelayed :: Crypt -> Bool
- setCryptDelayed :: Crypt -> Crypt
- data StatelessReset = StatelessReset
- data ReceivedPacket = ReceivedPacket {}
- mkReceivedPacket :: CryptPacket -> TimeMicrosecond -> Int -> EncryptionLevel -> ReceivedPacket
- data LongHeaderPacketType
- packetEncryptionLevel :: Header -> EncryptionLevel
- data Protected
- type EncodedPacketNumber = Word32
- defaultResumptionInfo :: ResumptionInfo
- newRecvQ :: IO RecvQ
- readRecvQ :: RecvQ -> IO ReceivedPacket
- writeRecvQ :: RecvQ -> ReceivedPacket -> IO ()
- prependRecvQ :: RecvQ -> ReceivedPacket -> STM ()
- data InternalControl
- newtype NextVersion = NextVersion VersionInfo
- data Abort
- fromRight :: b -> Either a b -> b
- getRandomBytes :: Int -> IO ShortByteString
- isAsyncException :: Exception e => e -> Bool
- ignore :: SomeException -> IO ()
- totalLen :: [ByteString] -> Int
- dec16 :: ByteString -> ByteString
- enc16 :: ByteString -> ByteString
- dec16s :: ShortByteString -> ShortByteString
- enc16s :: ShortByteString -> ShortByteString
- shortToString :: ShortByteString -> String
- getRandomOneByte :: IO Word8
- sum' :: (Functor f, Foldable f) => f Int -> Int
- withByteString :: ByteString -> (Ptr Word8 -> IO a) -> IO a
- shortpack :: String -> ShortByteString
- throughAsync :: IO a -> SomeException -> IO a
- checkWindowOpenSTM :: LDCC -> Int -> STM ()
- takePingSTM :: LDCC -> STM EncryptionLevel
- speedup :: LDCC -> EncryptionLevel -> LogStr -> IO ()
- resender :: LDCC -> IO ()
- onPacketSent :: LDCC -> SentPacket -> IO ()
- onPacketReceived :: LDCC -> EncryptionLevel -> PacketNumber -> IO ()
- onAckReceived :: LDCC -> EncryptionLevel -> AckInfo -> Microseconds -> IO ()
- onPacketNumberSpaceDiscarded :: LDCC -> EncryptionLevel -> IO ()
- setInitialCongestionWindow :: LDCC -> Int -> IO ()
- getPreviousRTT1PPNs :: LDCC -> IO PeerPacketNumbers
- setPreviousRTT1PPNs :: LDCC -> PeerPacketNumbers -> IO ()
- getSpeedingUp :: LDCC -> IO Bool
- getPacketNumberSpaceDiscarded :: LDCC -> EncryptionLevel -> IO Bool
- getAndSetPacketNumberSpaceDiscarded :: LDCC -> EncryptionLevel -> IO Bool
- setMaxAckDaley :: LDCC -> Microseconds -> IO ()
- getPeerPacketNumbers :: LDCC -> EncryptionLevel -> IO PeerPacketNumbers
- fromPeerPacketNumbers :: PeerPacketNumbers -> [PacketNumber]
- nullPeerPacketNumbers :: PeerPacketNumbers -> Bool
- findDuration :: Seq SentPacket -> PacketNumber -> Maybe UnixDiffTime
- getPTO :: LDCC -> IO Microseconds
- releaseByRetry :: LDCC -> IO (Seq PlainPacket)
- releaseOldest :: LDCC -> EncryptionLevel -> IO (Maybe SentPacket)
- beforeAntiAmp :: LDCC -> IO ()
- ldccTimer :: LDCC -> IO ()
- data SentPacket
- mkSentPacket :: PacketNumber -> EncryptionLevel -> PlainPacket -> PeerPacketNumbers -> Bool -> SentPacket
- fixSentPacket :: SentPacket -> Int -> Int -> SentPacket
- data LDCC
- newLDCC :: ConnState -> QLogger -> (PlainPacket -> IO ()) -> IO LDCC
- qlogSent :: (KeepQlog q, Qlog pkt) => q -> pkt -> TimeMicrosecond -> IO ()
- data ConnectionControl
- controlConnection :: Connection -> ConnectionControl -> IO Bool
- windowsThreadBlockHack :: IO a -> IO a
- clientSocket :: HostName -> ServiceName -> IO (Socket, SockAddr)
- serverSocket :: (IP, PortNumber) -> IO Socket
- natRebinding :: SockAddr -> IO Socket
Documentation
defaultHooks :: Hooks Source #
Default hooks.
Hooks.
Constructors
Hooks | |
Fields
|
data ClientConfig Source #
Client configuration.
Constructors
ClientConfig | |
Fields
|
defaultClientConfig :: ClientConfig Source #
The default value for client configuration.
data ServerConfig Source #
Server configuration.
Constructors
ServerConfig | |
Fields
|
defaultServerConfig :: ServerConfig Source #
The default value for server configuration.
Constructors
Coder | |
Fields
|
Constructors
Shared | |
Fields |
getVersion :: Connection -> IO Version Source #
setVersion :: Connection -> Version -> IO () Source #
data Negotiated Source #
Constructors
Negotiated | |
data Connection Source #
A quic connection to carry multiple streams.
Constructors
Instances
Connector Connection Source # | |
Defined in Network.QUIC.Connection.Types Methods getRole :: Connection -> Role Source # getEncryptionLevel :: Connection -> IO EncryptionLevel Source # getMaxPacketSize :: Connection -> IO Int Source # getConnectionState :: Connection -> IO ConnectionState Source # | |
KeepQlog Connection Source # | |
Defined in Network.QUIC.Connection.Types Methods keepQlog :: Connection -> QLogger Source # |
abortConnection :: Connection -> ApplicationProtocolError -> ReasonPhrase -> IO () Source #
Closing a connection with an application protocol error.
wait0RTTReady :: Connection -> IO () Source #
Waiting until 0-RTT data can be sent.
wait1RTTReady :: Connection -> IO () Source #
Waiting until 1-RTT data can be sent.
waitEstablished :: Connection -> IO () Source #
For clients, waiting until HANDSHAKE_DONE is received. For servers, waiting until a TLS stack reports that the handshake is complete.
getResumptionInfo :: Connection -> IO ResumptionInfo Source #
Getting information about resumption.
Constructors
InpHandshake EncryptionLevel ByteString |
setEncryptionLevel :: Connection -> EncryptionLevel -> IO () Source #
waitEncryptionLevel :: Connection -> EncryptionLevel -> IO () Source #
putOffCrypto :: Connection -> EncryptionLevel -> ReceivedPacket -> IO () Source #
getCipher :: Connection -> EncryptionLevel -> IO Cipher Source #
setCipher :: Connection -> EncryptionLevel -> Cipher -> IO () Source #
getTLSMode :: Connection -> IO HandshakeMode13 Source #
setNegotiated :: Connection -> HandshakeMode13 -> Maybe NegotiatedProtocol -> ApplicationSecretInfo -> IO () Source #
dropSecrets :: Connection -> EncryptionLevel -> IO () Source #
initializeCoder :: Connection -> EncryptionLevel -> TrafficSecrets a -> IO () Source #
initializeCoder1RTT :: Connection -> TrafficSecrets ApplicationSecret -> IO () Source #
updateCoder1RTT :: Connection -> Bool -> IO () Source #
getCoder :: Connection -> EncryptionLevel -> Bool -> IO Coder Source #
getProtector :: Connection -> EncryptionLevel -> IO Protector Source #
getCurrentKeyPhase :: Connection -> IO (Bool, PacketNumber) Source #
setCurrentKeyPhase :: Connection -> Bool -> PacketNumber -> IO () Source #
getPeerCID :: Connection -> IO CID Source #
myCIDsInclude :: Connection -> CID -> IO (Maybe Int) Source #
shouldUpdateMyCID :: Connection -> Int -> IO Bool Source #
shouldUpdatePeerCID :: Connection -> IO Bool Source #
resetPeerCID :: Connection -> CID -> IO () Source #
Reseting to Initial CID in the client side.
getNewMyCID :: Connection -> IO CIDInfo Source #
Sending NewConnectionID
getMyCIDSeqNum :: Connection -> IO Int Source #
setPeerCIDAndRetireCIDs :: Connection -> Int -> IO [Int] Source #
Receiving NewConnectionID
retirePeerCID :: Connection -> Int -> IO () Source #
After sending RetireConnectionID
retireMyCID :: Connection -> Int -> IO (Maybe CIDInfo) Source #
Receiving RetireConnectionID
addPeerCID :: Connection -> CIDInfo -> IO Bool Source #
Receiving NewConnectionID
waitPeerCID :: Connection -> IO CIDInfo Source #
Only for the internal "migration" API
choosePeerCIDForPrivacy :: Connection -> IO () Source #
Automatic CID update
setPeerStatelessResetToken :: Connection -> StatelessResetToken -> IO () Source #
setMigrationStarted :: Connection -> IO () Source #
isPathValidating :: Connection -> IO Bool Source #
checkResponse :: Connection -> PathData -> IO () Source #
validatePath :: Connection -> PathInfo -> Maybe CIDInfo -> IO () Source #
getMyRetirePriorTo :: Connection -> IO Int Source #
setMyRetirePriorTo :: Connection -> Int -> IO () Source #
getPeerRetirePriorTo :: Connection -> IO Int Source #
setPeerRetirePriorTo :: Connection -> Int -> IO () Source #
checkPeerCIDCapacity :: Connection -> IO Bool Source #
setVersionInfo :: Connection -> VersionInfo -> IO () Source #
getVersionInfo :: Connection -> IO VersionInfo Source #
clearSocket :: Connection -> IO Socket Source #
getPathInfo :: Connection -> IO PathInfo Source #
addPathInfo :: Connection -> PathInfo -> IO () Source #
findPathInfo :: Connection -> SockAddr -> IO (Maybe PathInfo) Source #
getPeerAuthCIDs :: Connection -> IO AuthCIDs Source #
setPeerAuthCIDs :: Connection -> (AuthCIDs -> AuthCIDs) -> IO () Source #
getClientDstCID :: Connection -> IO CID Source #
setPeerParameters :: Connection -> Parameters -> IO () Source #
modifytPeerParameters :: Connection -> ResumptionInfo -> IO () Source #
delayedAck :: Connection -> IO () Source #
resetDealyedAck :: Connection -> IO () Source #
setMaxPacketSize :: Connection -> Int -> IO () Source #
forkManaged :: Connection -> IO () -> IO () Source #
killReaders :: Connection -> IO () Source #
addResource :: Connection -> IO () -> IO () Source #
freeResources :: Connection -> IO () Source #
setMinIdleTimeout :: Connection -> Microseconds -> IO () Source #
sendFrames :: Connection -> EncryptionLevel -> [Frame] -> IO () Source #
closeConnection :: Connection -> TransportError -> ReasonPhrase -> IO () Source #
Closing a connection with/without a transport error. Internal threads should use this.
setPeerPacketNumber :: Connection -> PacketNumber -> IO () Source #
setRetried :: Connection -> Bool -> IO () Source #
getRetried :: Connection -> IO Bool Source #
setIncompatibleVN :: Connection -> Bool -> IO () Source #
getIncompatibleVN :: Connection -> IO Bool Source #
setNewToken :: Connection -> Token -> IO () Source #
setResumptionParameters :: Connection -> Parameters -> IO () Source #
setRegister :: Connection -> (CID -> Connection -> IO ()) -> (CID -> IO ()) -> IO () Source #
getRegister :: Connection -> IO (CID -> Connection -> IO ()) Source #
getUnregister :: Connection -> IO (CID -> IO ()) Source #
setTokenManager :: Connection -> TokenManager -> IO () Source #
setStopServer :: Connection -> IO () -> IO () Source #
getStopServer :: Connection -> IO (IO ()) Source #
setCertificateChain :: Connection -> Maybe CertificateChain -> IO () Source #
setSockConnected :: Connection -> Bool -> IO () Source #
getSockConnected :: Connection -> IO Bool Source #
setConnection0RTTReady :: Connection -> IO () Source #
isConnection1RTTReady :: Connection -> IO Bool Source #
setConnection1RTTReady :: Connection -> IO () Source #
setConnectionEstablished :: Connection -> IO () Source #
isConnectionClosed :: Connection -> IO Bool Source #
setConnectionClosed :: Connection -> IO () Source #
setTxMaxData :: Connection -> Int -> IO () Source #
getRxMaxData :: Connection -> IO Int Source #
updateFlowRx :: Connection -> Int -> IO (Maybe Int) Source #
checkRxMaxData :: Connection -> Int -> IO Bool Source #
addTxBytes :: Connection -> Int -> IO () Source #
getTxBytes :: Connection -> IO Int Source #
addRxBytes :: Connection -> Int -> IO () Source #
getRxBytes :: Connection -> IO Int Source #
setAddressValidated :: PathInfo -> IO () Source #
waitAntiAmplificationFree :: Connection -> PathInfo -> Int -> IO () Source #
getMyStreamId :: Connection -> IO Int Source #
possibleMyStreams :: Connection -> IO Int Source #
waitMyNewStreamId :: Connection -> IO StreamId Source #
setTxMaxStreams :: Connection -> Int -> IO () Source #
setTxUniMaxStreams :: Connection -> Int -> IO () Source #
checkRxMaxStreams :: Connection -> StreamId -> IO Bool Source #
updatePeerStreamId :: Connection -> StreamId -> IO () Source #
checkStreamIdRoom :: Connection -> Direction -> IO (Maybe Int) Source #
createStream :: Connection -> StreamId -> IO Stream Source #
findStream :: Connection -> StreamId -> IO (Maybe Stream) Source #
initialRxMaxStreamData :: Connection -> StreamId -> Int Source #
setupCryptoStreams :: Connection -> IO () Source #
clearCryptoStream :: Connection -> EncryptionLevel -> IO () Source #
getCryptoStream :: Connection -> EncryptionLevel -> IO (Maybe Stream) Source #
fire :: Connection -> Microseconds -> TimeoutCallback -> IO () Source #
fire' :: Microseconds -> TimeoutCallback -> IO () Source #
cfire :: Connection -> Microseconds -> TimeoutCallback -> IO (IO ()) Source #
delay :: Microseconds -> IO () Source #
Constructors
CIDDB | |
Fields
|
Constructors
ClientInfo | |
Fields | |
ServerInfo | |
Fields
|
data MigrationState Source #
Instances
Eq MigrationState Source # | |
Defined in Network.QUIC.Connection.Types Methods (==) :: MigrationState -> MigrationState -> Bool # (/=) :: MigrationState -> MigrationState -> Bool # |
Constructors
PathInfo | |
Fields
|
initialCoder :: Coder Source #
Constructors
Coder1RTT | |
Fields |
newtype StreamIdBase Source #
Constructors
StreamIdBase | |
Fields |
Instances
Show StreamIdBase Source # | |
Defined in Network.QUIC.Connection.Types Methods showsPrec :: Int -> StreamIdBase -> ShowS # show :: StreamIdBase -> String # showList :: [StreamIdBase] -> ShowS # | |
Eq StreamIdBase Source # | |
Defined in Network.QUIC.Connection.Types |
data Concurrency Source #
Constructors
Concurrency | |
Fields |
Instances
Show Concurrency Source # | |
Defined in Network.QUIC.Connection.Types Methods showsPrec :: Int -> Concurrency -> ShowS # show :: Concurrency -> String # showList :: [Concurrency] -> ShowS # |
newConcurrency :: Role -> Direction -> Int -> Concurrency Source #
type Recv = IO ReceivedPacket Source #
Constructors
PeerInfo | |
Fields |
setDead :: Connection -> IO () Source #
makePendingQ :: IO (Array EncryptionLevel (TVar [ReceivedPacket])) Source #
newConnection :: Role -> Parameters -> VersionInfo -> AuthCIDs -> AuthCIDs -> DebugLogger -> QLogger -> Hooks -> IORef Socket -> IORef PeerInfo -> RecvQ -> Send -> Recv -> (CID -> StatelessResetToken) -> IO Connection Source #
Constructors
OutControl EncryptionLevel [Frame] | |
OutHandshake [(EncryptionLevel, ByteString)] | |
OutRetrans PlainPacket |
clientConnection :: ClientConfig -> VersionInfo -> AuthCIDs -> AuthCIDs -> DebugLogger -> QLogger -> Hooks -> IORef Socket -> IORef PeerInfo -> RecvQ -> Send -> Recv -> (CID -> StatelessResetToken) -> IO Connection Source #
serverConnection :: ServerConfig -> VersionInfo -> AuthCIDs -> AuthCIDs -> DebugLogger -> QLogger -> Hooks -> IORef Socket -> IORef PeerInfo -> RecvQ -> Send -> Recv -> (CID -> StatelessResetToken) -> IO Connection Source #
type SendStreamQ = TQueue TxStreamData Source #
takeCrypto :: Connection -> IO Crypto Source #
isEmptyCryptoSTM :: Connection -> STM Bool Source #
takeOutputSTM :: Connection -> STM Output Source #
tryTakeOutput :: Connection -> IO (Maybe Output) Source #
tryPeekOutput :: Connection -> IO (Maybe Output) Source #
isEmptyOutputSTM :: Connection -> STM Bool Source #
tryPeekSendStreamQ :: Connection -> IO (Maybe TxStreamData) Source #
putSendStreamQ :: Connection -> TxStreamData -> IO () Source #
isEmptyStreamSTM :: Connection -> STM Bool Source #
outputLimit :: Int Source #
class Connector a where Source #
Methods
getEncryptionLevel :: a -> IO EncryptionLevel Source #
getMaxPacketSize :: a -> IO Int Source #
getConnectionState :: a -> IO ConnectionState Source #
getPacketNumber :: a -> IO PacketNumber Source #
Instances
Connector Connection Source # | |
Defined in Network.QUIC.Connection.Types Methods getRole :: Connection -> Role Source # getEncryptionLevel :: Connection -> IO EncryptionLevel Source # getMaxPacketSize :: Connection -> IO Int Source # getConnectionState :: Connection -> IO ConnectionState Source # | |
Connector LDCC Source # | |
Defined in Network.QUIC.Recovery.Types Methods getRole :: LDCC -> Role Source # getEncryptionLevel :: LDCC -> IO EncryptionLevel Source # getMaxPacketSize :: LDCC -> IO Int Source # getConnectionState :: LDCC -> IO ConnectionState Source # getPacketNumber :: LDCC -> IO PacketNumber Source # |
data ConnectionState Source #
Constructors
Handshaking | |
ReadyFor0RTT | |
ReadyFor1RTT | |
Established | |
Closed |
Instances
Show ConnectionState Source # | |
Defined in Network.QUIC.Connector Methods showsPrec :: Int -> ConnectionState -> ShowS # show :: ConnectionState -> String # showList :: [ConnectionState] -> ShowS # | |
Eq ConnectionState Source # | |
Defined in Network.QUIC.Connector Methods (==) :: ConnectionState -> ConnectionState -> Bool # (/=) :: ConnectionState -> ConnectionState -> Bool # | |
Ord ConnectionState Source # | |
Defined in Network.QUIC.Connector Methods compare :: ConnectionState -> ConnectionState -> Ordering # (<) :: ConnectionState -> ConnectionState -> Bool # (<=) :: ConnectionState -> ConnectionState -> Bool # (>) :: ConnectionState -> ConnectionState -> Bool # (>=) :: ConnectionState -> ConnectionState -> Bool # max :: ConnectionState -> ConnectionState -> ConnectionState # min :: ConnectionState -> ConnectionState -> ConnectionState # |
Constructors
ConnState | |
Fields |
Constructors
Mask ByteString |
Constructors
Key ByteString |
Cipher algorithm
Constructors
IV ByteString |
Constructors
Nonce ByteString |
type Salt = ByteString Source #
type CipherText = ByteString Source #
type PlainText = ByteString Source #
Constructors
Label ByteString |
type TrafficSecrets a = (ClientTrafficSecret a, ServerTrafficSecret a) #
Hold both client and server traffic secrets at the same step.
newtype ServerTrafficSecret a #
A server traffic secret, typed with a parameter indicating a step in the TLS key schedule.
Constructors
ServerTrafficSecret ByteString |
Instances
Show (ServerTrafficSecret a) | |
Defined in Network.TLS.Types.Secret Methods showsPrec :: Int -> ServerTrafficSecret a -> ShowS # show :: ServerTrafficSecret a -> String # showList :: [ServerTrafficSecret a] -> ShowS # |
newtype ClientTrafficSecret a #
A client traffic secret, typed with a parameter indicating a step in the TLS key schedule.
Constructors
ClientTrafficSecret ByteString |
Instances
Show (ClientTrafficSecret a) | |
Defined in Network.TLS.Types.Secret Methods showsPrec :: Int -> ClientTrafficSecret a -> ShowS # show :: ClientTrafficSecret a -> String # showList :: [ClientTrafficSecret a] -> ShowS # |
data FusionContext Source #
fusionSetup :: Cipher -> FusionContext -> Key -> IV -> IO () Source #
fusionEncrypt :: FusionContext -> Supplement -> Buffer -> PlainText -> AssDat -> PacketNumber -> IO Int Source #
fusionDecrypt :: FusionContext -> Buffer -> CipherText -> AssDat -> PacketNumber -> IO Int Source #
data Supplement Source #
fusionSetupSupplement :: Cipher -> Key -> IO Supplement Source #
fusionSetSample :: Supplement -> Buffer -> IO () Source #
fusionGetMask :: Supplement -> IO Buffer Source #
initialSecrets :: Version -> CID -> TrafficSecrets InitialSecret Source #
niteEncrypt :: Cipher -> Key -> IV -> PlainText -> AssDat -> PacketNumber -> Maybe (CipherText, CipherText) Source #
niteEncrypt' :: Cipher -> Key -> Nonce -> PlainText -> AssDat -> Maybe (CipherText, CipherText) Source #
niteDecrypt :: Cipher -> Key -> IV -> CipherText -> AssDat -> PacketNumber -> Maybe PlainText Source #
niteDecrypt' :: Cipher -> Key -> Nonce -> CipherText -> AssDat -> Maybe PlainText Source #
aes128gcmEncrypt :: Key -> Nonce -> PlainText -> AssDat -> Maybe (CipherText, CipherText) Source #
A type for conneciton ID.
Constructors
Secret ByteString |
Instances
Constructors
AssDat ByteString |
Instances
Constructors
Sample ByteString |
Instances
data InitialSecret Source #
sampleLength :: Cipher -> Int Source #
bsXOR :: ByteString -> ByteString -> ByteString Source #
calculateIntegrityTag :: Version -> CID -> ByteString -> ByteString Source #
Builder
s denote sequences of bytes.
They are Monoid
s where
mempty
is the zero-length sequence and
mappend
is concatenation, which runs in O(1).
type DebugLogger = Builder -> IO () Source #
A type for debug logger.
dirDebugLogger :: Maybe FilePath -> CID -> IO (DebugLogger, IO ()) Source #
encryptToken :: TokenManager -> CryptoToken -> IO Token Source #
decryptToken :: TokenManager -> Token -> IO (Maybe CryptoToken) Source #
encodeVersionNegotiationPacket :: VersionNegotiationPacket -> IO ByteString Source #
This is not used internally.
encodePlainPacket :: Connection -> SizedBuffer -> PlainPacket -> Maybe Int -> IO (Int, Int) Source #
decodePacket :: ByteString -> Bool -> IO (PacketI, ByteString) Source #
decodePackets :: ByteString -> Bool -> IO [PacketI] Source #
decodeCryptPackets :: ByteString -> Bool -> IO [(CryptPacket, EncryptionLevel, Int)] Source #
decryptCrypt :: Connection -> Crypt -> EncryptionLevel -> IO (Maybe Plain) Source #
encodeFrames :: [Frame] -> IO ByteString Source #
decodeFramesBuffer :: Buffer -> BufferSize -> IO (Maybe [Frame]) Source #
decodeFramesBS :: ByteString -> IO (Maybe [Frame]) Source #
encodeLongHeaderFlags :: Version -> LongHeaderPacketType -> Flags Raw -> Flags Raw -> Bool -> IO (Flags Raw) Source #
data CryptoToken Source #
Constructors
CryptoToken | |
Fields
|
Instances
isRetryToken :: CryptoToken -> Bool Source #
generateToken :: Version -> Int -> IO CryptoToken Source #
generateRetryToken :: Version -> Int -> CID -> CID -> CID -> IO CryptoToken Source #
data Parameters Source #
QUIC transport parameters.
Constructors
Parameters | |
Fields
|
Instances
Show Parameters Source # | |
Defined in Network.QUIC.Parameters Methods showsPrec :: Int -> Parameters -> ShowS # show :: Parameters -> String # showList :: [Parameters] -> ShowS # | |
Eq Parameters Source # | |
Defined in Network.QUIC.Parameters | |
Qlog (Parameters, String) Source # | |
Defined in Network.QUIC.Qlog |
defaultParameters :: Parameters Source #
An example parameters obsoleted in the near future.
>>>
defaultParameters
Parameters {originalDestinationConnectionId = Nothing, maxIdleTimeout = 30000, statelessResetToken = Nothing, maxUdpPayloadSize = 2048, initialMaxData = 16777216, initialMaxStreamDataBidiLocal = 262144, initialMaxStreamDataBidiRemote = 262144, initialMaxStreamDataUni = 262144, initialMaxStreamsBidi = 64, initialMaxStreamsUni = 3, ackDelayExponent = 3, maxAckDelay = 25, disableActiveMigration = False, preferredAddress = Nothing, activeConnectionIdLimit = 5, initialSourceConnectionId = Nothing, retrySourceConnectionId = Nothing, grease = Nothing, greaseQuicBit = True, versionInformation = Nothing}
baseParameters :: Parameters Source #
The default value for QUIC transport parameters.
Constructors
AuthCIDs | |
Fields
|
setCIDsToParameters :: AuthCIDs -> Parameters -> Parameters Source #
packetType :: Header -> LogStr Source #
Instances
Qlog Debug Source # | |
Qlog LR Source # | |
Qlog SentPacket Source # | |
Defined in Network.QUIC.Recovery.Types Methods qlog :: SentPacket -> LogStr Source # | |
Qlog Frame Source # | |
Qlog CryptPacket Source # | |
Defined in Network.QUIC.Qlog Methods qlog :: CryptPacket -> LogStr Source # | |
Qlog Header Source # | |
Qlog PlainPacket Source # | |
Defined in Network.QUIC.Qlog Methods qlog :: PlainPacket -> LogStr Source # | |
Qlog RetryPacket Source # | |
Defined in Network.QUIC.Qlog Methods qlog :: RetryPacket -> LogStr Source # | |
Qlog StatelessReset Source # | |
Defined in Network.QUIC.Qlog Methods qlog :: StatelessReset -> LogStr Source # | |
Qlog VersionNegotiationPacket Source # | |
Defined in Network.QUIC.Qlog Methods | |
Qlog (Parameters, String) Source # | |
Defined in Network.QUIC.Qlog | |
Qlog (Header, String) Source # | |
newQlogger :: TimeMicrosecond -> ByteString -> CID -> FastLogger -> IO QLogger Source #
class KeepQlog a where Source #
Instances
KeepQlog Connection Source # | |
Defined in Network.QUIC.Connection.Types Methods keepQlog :: Connection -> QLogger Source # | |
KeepQlog LDCC Source # | |
Constructors
QRecvInitial | |
QSentRetry | |
QSent LogStr TimeMicrosecond | |
QReceived LogStr TimeMicrosecond | |
QDropped LogStr TimeMicrosecond | |
QMetricsUpdated LogStr TimeMicrosecond | |
QPacketLost LogStr TimeMicrosecond | |
QCongestionStateUpdated LogStr TimeMicrosecond | |
QLossTimerUpdated LogStr TimeMicrosecond | |
QDebug LogStr TimeMicrosecond | |
QParamsSet LogStr TimeMicrosecond | |
QCIDUpdate LogStr TimeMicrosecond |
qlogReceived :: (KeepQlog q, Qlog a) => q -> a -> TimeMicrosecond -> IO () Source #
qlogRecvInitial :: KeepQlog q => q -> IO () Source #
qlogSentRetry :: KeepQlog q => q -> IO () Source #
qlogParamsSet :: KeepQlog q => q -> (Parameters, String) -> IO () Source #
An abstract data type for streams.
data StreamTable Source #
data TxStreamData Source #
Constructors
TxStreamData Stream [StreamData] Length Fin |
data StreamState Source #
Constructors
StreamState | |
Fields
|
Instances
Show StreamState Source # | |
Defined in Network.QUIC.Stream.Types Methods showsPrec :: Int -> StreamState -> ShowS # show :: StreamState -> String # showList :: [StreamState] -> ShowS # | |
Eq StreamState Source # | |
Defined in Network.QUIC.Stream.Types |
data RecvStreamQ Source #
Constructors
RecvStreamQ | |
Fields
|
data RxStreamData Source #
Constructors
RxStreamData | |
Fields
|
Instances
Show RxStreamData Source # | |
Defined in Network.QUIC.Stream.Types Methods showsPrec :: Int -> RxStreamData -> ShowS # show :: RxStreamData -> String # showList :: [RxStreamData] -> ShowS # | |
Eq RxStreamData Source # | |
Defined in Network.QUIC.Stream.Types |
setTxStreamClosed :: Stream -> IO () Source #
setRxStreamClosed :: Stream -> IO () Source #
takeRecvStreamQwithSize :: Stream -> Int -> IO ByteString Source #
putRxStreamData :: Stream -> RxStreamData -> IO FlowCntl Source #
Constructors
OverLimit | |
Duplicated | |
Reassembled |
tryReassemble :: Stream -> RxStreamData -> (StreamData -> IO ()) -> IO () -> IO Bool Source #
lookupStream :: StreamId -> StreamTable -> Maybe Stream Source #
insertStream :: StreamId -> Stream -> StreamTable -> StreamTable Source #
deleteStream :: StreamId -> StreamTable -> StreamTable Source #
insertCryptoStreams :: Connection -> StreamTable -> IO StreamTable Source #
clientHandshaker :: QUICCallbacks -> ClientConfig -> Version -> AuthCIDs -> SessionEstablish -> Bool -> IO () Source #
serverHandshaker :: QUICCallbacks -> ServerConfig -> Version -> IO Parameters -> IO () Source #
QUIC version.
Instances
Generic Version Source # | |||||
Defined in Network.QUIC.Types.Packet Associated Types
| |||||
Show Version Source # | |||||
Eq Version Source # | |||||
Ord Version Source # | |||||
Defined in Network.QUIC.Types.Packet | |||||
Serialise Version Source # | |||||
type Rep Version Source # | |||||
Defined in Network.QUIC.Types.Packet |
decodeInt :: ByteString -> Int64 Source #
>>>
decodeInt (dec16 "c2197c5eff14e88c")
151288809941952652>>>
decodeInt (dec16 "9d7f3e7d")
494878333>>>
decodeInt (dec16 "7bbd")
15293>>>
decodeInt (dec16 "25")
37
encodeInt :: Int64 -> ByteString Source #
>>>
enc16 $ encodeInt 151288809941952652
"c2197c5eff14e88c">>>
enc16 $ encodeInt 494878333
"9d7f3e7d">>>
enc16 $ encodeInt 15293
"7bbd">>>
enc16 $ encodeInt 37
"25"
encodeInt8 :: Int64 -> ByteString Source #
type Bytes = ShortByteString Source #
All internal byte sequences.
ByteString
should be used for FFI related stuff.
data QUICException Source #
User level exceptions for QUIC.
Constructors
ConnectionIsClosed ReasonPhrase | |
TransportErrorIsReceived TransportError ReasonPhrase | |
TransportErrorIsSent TransportError ReasonPhrase | |
ApplicationProtocolErrorIsReceived ApplicationProtocolError ReasonPhrase | |
ApplicationProtocolErrorIsSent ApplicationProtocolError ReasonPhrase | |
ConnectionIsTimeout String | |
ConnectionIsReset | |
StreamIsClosed | |
HandshakeFailed AlertDescription | |
VersionIsUnknown Word32 | |
NoVersionIsSpecified | |
VersionNegotiationFailed | |
BadThingHappen SomeException |
Instances
Exception QUICException Source # | |
Defined in Network.QUIC.Types.Exception Methods toException :: QUICException -> SomeException # fromException :: SomeException -> Maybe QUICException # displayException :: QUICException -> String # | |
Show QUICException Source # | |
Defined in Network.QUIC.Types.Exception Methods showsPrec :: Int -> QUICException -> ShowS # show :: QUICException -> String # showList :: [QUICException] -> ShowS # |
pattern InternalError :: TransportError Source #
is0RTTPossible :: ResumptionInfo -> Bool Source #
Is 0RTT possible?
Constructors
Unidirectional | |
Bidirectional |
Stream identifier. This should be 62-bit interger. On 32-bit machines, the total number of stream identifiers is limited.
isClientInitiatedBidirectional :: StreamId -> Bool Source #
Checking if a stream is client-initiated bidirectional.
isServerInitiatedBidirectional :: StreamId -> Bool Source #
Checking if a stream is server-initiated bidirectional.
isClientInitiatedUnidirectional :: StreamId -> Bool Source #
Checking if a stream is client-initiated unidirectional.
isServerInitiatedUnidirectional :: StreamId -> Bool Source #
Checking if a stream is server-initiated unidirectional.
newtype TransportError Source #
Transport errors of QUIC.
Constructors
TransportError Int |
Instances
Show TransportError Source # | |
Defined in Network.QUIC.Types.Error Methods showsPrec :: Int -> TransportError -> ShowS # show :: TransportError -> String # showList :: [TransportError] -> ShowS # | |
Eq TransportError Source # | |
Defined in Network.QUIC.Types.Error Methods (==) :: TransportError -> TransportError -> Bool # (/=) :: TransportError -> TransportError -> Bool # |
pattern NoError :: TransportError Source #
pattern ConnectionRefused :: TransportError Source #
pattern FlowControlError :: TransportError Source #
pattern StreamLimitError :: TransportError Source #
pattern StreamStateError :: TransportError Source #
pattern FinalSizeError :: TransportError Source #
pattern FrameEncodingError :: TransportError Source #
pattern TransportParameterError :: TransportError Source #
pattern ConnectionIdLimitError :: TransportError Source #
pattern ProtocolViolation :: TransportError Source #
pattern InvalidToken :: TransportError Source #
pattern ApplicationError :: TransportError Source #
pattern CryptoBufferExceeded :: TransportError Source #
pattern KeyUpdateError :: TransportError Source #
pattern AeadLimitReached :: TransportError Source #
pattern NoViablePath :: TransportError Source #
cryptoError :: AlertDescription -> TransportError Source #
Converting a TLS alert to a corresponding transport error.
newtype ApplicationProtocolError Source #
Application protocol errors of QUIC.
Constructors
ApplicationProtocolError Int |
Instances
Show ApplicationProtocolError Source # | |
Defined in Network.QUIC.Types.Error Methods showsPrec :: Int -> ApplicationProtocolError -> ShowS # show :: ApplicationProtocolError -> String # showList :: [ApplicationProtocolError] -> ShowS # | |
Eq ApplicationProtocolError Source # | |
Defined in Network.QUIC.Types.Error Methods (==) :: ApplicationProtocolError -> ApplicationProtocolError -> Bool # (/=) :: ApplicationProtocolError -> ApplicationProtocolError -> Bool # |
data ResumptionInfo Source #
Information about resumption
Constructors
ResumptionInfo | |
Fields
|
Instances
Generic ResumptionInfo Source # | |||||
Defined in Network.QUIC.Types.Resumption Associated Types
Methods from :: ResumptionInfo -> Rep ResumptionInfo x # to :: Rep ResumptionInfo x -> ResumptionInfo # | |||||
Show ResumptionInfo Source # | |||||
Defined in Network.QUIC.Types.Resumption Methods showsPrec :: Int -> ResumptionInfo -> ShowS # show :: ResumptionInfo -> String # showList :: [ResumptionInfo] -> ShowS # | |||||
Eq ResumptionInfo Source # | |||||
Defined in Network.QUIC.Types.Resumption Methods (==) :: ResumptionInfo -> ResumptionInfo -> Bool # (/=) :: ResumptionInfo -> ResumptionInfo -> Bool # | |||||
Serialise ResumptionInfo Source # | |||||
Defined in Network.QUIC.Types.Resumption Methods encode :: ResumptionInfo -> Encoding # decode :: Decoder s ResumptionInfo # encodeList :: [ResumptionInfo] -> Encoding # decodeList :: Decoder s [ResumptionInfo] # | |||||
type Rep ResumptionInfo Source # | |||||
Defined in Network.QUIC.Types.Resumption type Rep ResumptionInfo = D1 ('MetaData "ResumptionInfo" "Network.QUIC.Types.Resumption" "quic-0.2.14-4y5RJLeDlnOKTB2lFP0ffp" 'False) (C1 ('MetaCons "ResumptionInfo" 'PrefixI 'True) (((S1 ('MetaSel ('Just "resumptionVersion") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Version) :*: S1 ('MetaSel ('Just "resumptionSession") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 [(SessionID, SessionData)])) :*: (S1 ('MetaSel ('Just "resumptionToken") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Token) :*: (S1 ('MetaSel ('Just "resumptionRetry") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Bool) :*: S1 ('MetaSel ('Just "resumptionActiveConnectionIdLimit") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Int)))) :*: ((S1 ('MetaSel ('Just "resumptionInitialMaxData") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Int) :*: (S1 ('MetaSel ('Just "resumptionInitialMaxStreamDataBidiLocal") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Int) :*: S1 ('MetaSel ('Just "resumptionInitialMaxStreamDataBidiRemote") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Int))) :*: (S1 ('MetaSel ('Just "resumptionInitialMaxStreamDataUni") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Int) :*: (S1 ('MetaSel ('Just "resumptionInitialMaxStreamsBidi") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Int) :*: S1 ('MetaSel ('Just "resumptionInitialMaxStreamsUni") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Int)))))) |
isResumptionPossible :: ResumptionInfo -> Bool Source #
Is resumption possible?
type PacketNumber = Int Source #
type Token = ByteString Source #
A type for conneciton ID.
Constructors
Padding Int | |
Ping | |
Ack AckInfo Delay | |
ResetStream StreamId ApplicationProtocolError Int | |
StopSending StreamId ApplicationProtocolError | |
CryptoF Offset CryptoData | |
NewToken Token | |
StreamF StreamId Offset [StreamData] Fin | |
MaxData Int | |
MaxStreamData StreamId Int | |
MaxStreams Direction Int | |
DataBlocked Int | |
StreamDataBlocked StreamId Int | |
StreamsBlocked Direction Int | |
NewConnectionID CIDInfo SeqNum | |
RetireConnectionID SeqNum | |
PathChallenge PathData | |
PathResponse PathData | |
ConnectionClose TransportError FrameType ReasonPhrase | |
ConnectionCloseApp ApplicationProtocolError ReasonPhrase | |
HandshakeDone | |
UnknownFrame Int |
newtype PeerPacketNumbers Source #
Constructors
PeerPacketNumbers IntSet |
Instances
Show PeerPacketNumbers Source # | |
Defined in Network.QUIC.Types.Ack Methods showsPrec :: Int -> PeerPacketNumbers -> ShowS # show :: PeerPacketNumbers -> String # showList :: [PeerPacketNumbers] -> ShowS # | |
Eq PeerPacketNumbers Source # | |
Defined in Network.QUIC.Types.Ack Methods (==) :: PeerPacketNumbers -> PeerPacketNumbers -> Bool # (/=) :: PeerPacketNumbers -> PeerPacketNumbers -> Bool # |
data SizedBuffer Source #
Constructors
SizedBuffer Buffer BufferSize |
myCIDLength :: Int Source #
fromCID :: CID -> ByteString Source #
Converting a connection ID.
toCID :: ByteString -> CID Source #
makeCID :: ShortByteString -> CID Source #
newtype StatelessResetToken Source #
Constructors
StatelessResetToken Bytes |
Instances
Show StatelessResetToken Source # | |
Defined in Network.QUIC.Types.CID Methods showsPrec :: Int -> StatelessResetToken -> ShowS # show :: StatelessResetToken -> String # showList :: [StatelessResetToken] -> ShowS # | |
Eq StatelessResetToken Source # | |
Defined in Network.QUIC.Types.CID Methods (==) :: StatelessResetToken -> StatelessResetToken -> Bool # (/=) :: StatelessResetToken -> StatelessResetToken -> Bool # | |
Ord StatelessResetToken Source # | |
Defined in Network.QUIC.Types.CID Methods compare :: StatelessResetToken -> StatelessResetToken -> Ordering # (<) :: StatelessResetToken -> StatelessResetToken -> Bool # (<=) :: StatelessResetToken -> StatelessResetToken -> Bool # (>) :: StatelessResetToken -> StatelessResetToken -> Bool # (>=) :: StatelessResetToken -> StatelessResetToken -> Bool # max :: StatelessResetToken -> StatelessResetToken -> StatelessResetToken # min :: StatelessResetToken -> StatelessResetToken -> StatelessResetToken # |
makeGenStatelessReset :: IO (CID -> StatelessResetToken) Source #
newPathData :: IO PathData Source #
newCIDInfo :: Int -> CID -> StatelessResetToken -> CIDInfo Source #
encodeInt' :: WriteBuffer -> Int64 -> IO () Source #
encodeInt'2 :: WriteBuffer -> Int64 -> IO () Source #
encodeInt'4 :: WriteBuffer -> Int64 -> IO () Source #
decodeInt' :: ReadBuffer -> IO Int64 Source #
type SessionEstablish = SessionID -> SessionData -> IO (Maybe Ticket) Source #
newtype Milliseconds Source #
Constructors
Milliseconds Int64 |
Instances
Bits Milliseconds Source # | |
Defined in Network.QUIC.Types.Time Methods (.&.) :: Milliseconds -> Milliseconds -> Milliseconds # (.|.) :: Milliseconds -> Milliseconds -> Milliseconds # xor :: Milliseconds -> Milliseconds -> Milliseconds # complement :: Milliseconds -> Milliseconds # shift :: Milliseconds -> Int -> Milliseconds # rotate :: Milliseconds -> Int -> Milliseconds # bit :: Int -> Milliseconds # setBit :: Milliseconds -> Int -> Milliseconds # clearBit :: Milliseconds -> Int -> Milliseconds # complementBit :: Milliseconds -> Int -> Milliseconds # testBit :: Milliseconds -> Int -> Bool # bitSizeMaybe :: Milliseconds -> Maybe Int # bitSize :: Milliseconds -> Int # isSigned :: Milliseconds -> Bool # shiftL :: Milliseconds -> Int -> Milliseconds # unsafeShiftL :: Milliseconds -> Int -> Milliseconds # shiftR :: Milliseconds -> Int -> Milliseconds # unsafeShiftR :: Milliseconds -> Int -> Milliseconds # rotateL :: Milliseconds -> Int -> Milliseconds # rotateR :: Milliseconds -> Int -> Milliseconds # popCount :: Milliseconds -> Int # | |
Num Milliseconds Source # | |
Defined in Network.QUIC.Types.Time Methods (+) :: Milliseconds -> Milliseconds -> Milliseconds # (-) :: Milliseconds -> Milliseconds -> Milliseconds # (*) :: Milliseconds -> Milliseconds -> Milliseconds # negate :: Milliseconds -> Milliseconds # abs :: Milliseconds -> Milliseconds # signum :: Milliseconds -> Milliseconds # fromInteger :: Integer -> Milliseconds # | |
Show Milliseconds Source # | |
Defined in Network.QUIC.Types.Time Methods showsPrec :: Int -> Milliseconds -> ShowS # show :: Milliseconds -> String # showList :: [Milliseconds] -> ShowS # | |
Eq Milliseconds Source # | |
Defined in Network.QUIC.Types.Time | |
Ord Milliseconds Source # | |
Defined in Network.QUIC.Types.Time Methods compare :: Milliseconds -> Milliseconds -> Ordering # (<) :: Milliseconds -> Milliseconds -> Bool # (<=) :: Milliseconds -> Milliseconds -> Bool # (>) :: Milliseconds -> Milliseconds -> Bool # (>=) :: Milliseconds -> Milliseconds -> Bool # max :: Milliseconds -> Milliseconds -> Milliseconds # min :: Milliseconds -> Milliseconds -> Milliseconds # |
newtype Microseconds Source #
Constructors
Microseconds Int |
Instances
Bits Microseconds Source # | |
Defined in Network.QUIC.Types.Time Methods (.&.) :: Microseconds -> Microseconds -> Microseconds # (.|.) :: Microseconds -> Microseconds -> Microseconds # xor :: Microseconds -> Microseconds -> Microseconds # complement :: Microseconds -> Microseconds # shift :: Microseconds -> Int -> Microseconds # rotate :: Microseconds -> Int -> Microseconds # bit :: Int -> Microseconds # setBit :: Microseconds -> Int -> Microseconds # clearBit :: Microseconds -> Int -> Microseconds # complementBit :: Microseconds -> Int -> Microseconds # testBit :: Microseconds -> Int -> Bool # bitSizeMaybe :: Microseconds -> Maybe Int # bitSize :: Microseconds -> Int # isSigned :: Microseconds -> Bool # shiftL :: Microseconds -> Int -> Microseconds # unsafeShiftL :: Microseconds -> Int -> Microseconds # shiftR :: Microseconds -> Int -> Microseconds # unsafeShiftR :: Microseconds -> Int -> Microseconds # rotateL :: Microseconds -> Int -> Microseconds # rotateR :: Microseconds -> Int -> Microseconds # popCount :: Microseconds -> Int # | |
Num Microseconds Source # | |
Defined in Network.QUIC.Types.Time Methods (+) :: Microseconds -> Microseconds -> Microseconds # (-) :: Microseconds -> Microseconds -> Microseconds # (*) :: Microseconds -> Microseconds -> Microseconds # negate :: Microseconds -> Microseconds # abs :: Microseconds -> Microseconds # signum :: Microseconds -> Microseconds # fromInteger :: Integer -> Microseconds # | |
Show Microseconds Source # | |
Defined in Network.QUIC.Types.Time Methods showsPrec :: Int -> Microseconds -> ShowS # show :: Microseconds -> String # showList :: [Microseconds] -> ShowS # | |
Eq Microseconds Source # | |
Defined in Network.QUIC.Types.Time | |
Ord Microseconds Source # | |
Defined in Network.QUIC.Types.Time Methods compare :: Microseconds -> Microseconds -> Ordering # (<) :: Microseconds -> Microseconds -> Bool # (<=) :: Microseconds -> Microseconds -> Bool # (>) :: Microseconds -> Microseconds -> Bool # (>=) :: Microseconds -> Microseconds -> Bool # max :: Microseconds -> Microseconds -> Microseconds # min :: Microseconds -> Microseconds -> Microseconds # |
type TimeMicrosecond = UnixTime Source #
Constructors
AckInfo PacketNumber Range [(Gap, Range)] |
Instances
toAckInfo :: [PacketNumber] -> AckInfo Source #
>>>
toAckInfo [9]
AckInfo 9 0 []>>>
toAckInfo [9,8,7]
AckInfo 9 2 []>>>
toAckInfo [8,7,3,2]
AckInfo 8 1 [(2,1)]>>>
toAckInfo [9,8,7,5,4]
AckInfo 9 2 [(0,1)]
fromAckInfo :: AckInfo -> [PacketNumber] Source #
>>>
fromAckInfo $ AckInfo 9 0 []
[9]>>>
fromAckInfo $ AckInfo 9 2 []
[7,8,9]>>>
fromAckInfo $ AckInfo 8 1 [(2,1)]
[2,3,7,8]>>>
fromAckInfo $ AckInfo 9 2 [(0,1)]
[4,5,7,8,9]
fromAckInfoWithMin :: AckInfo -> PacketNumber -> [PacketNumber] Source #
>>>
fromAckInfoWithMin (AckInfo 9 0 []) 1
[9]>>>
fromAckInfoWithMin (AckInfo 9 2 []) 8
[8,9]>>>
fromAckInfoWithMin (AckInfo 8 1 [(2,1)]) 3
[3,7,8]>>>
fromAckInfoWithMin (AckInfo 9 2 [(0,1)]) 8
[8,9]
fromAckInfoToPred :: AckInfo -> PacketNumber -> Bool Source #
pattern VersionNegotiationError :: TransportError Source #
type ReasonPhrase = ShortByteString Source #
type Delay = Milliseconds Source #
type CryptoData = ByteString Source #
type StreamData = ByteString Source #
isClientInitiated :: StreamId -> Bool Source #
isServerInitiated :: StreamId -> Bool Source #
isBidirectional :: StreamId -> Bool Source #
isUnidirectional :: StreamId -> Bool Source #
emptyToken :: Token Source #
ackEliciting :: Frame -> Bool Source #
pathValidating :: Frame -> Bool Source #
rateControled :: Frame -> Bool Source #
pattern Negotiation :: Version Source #
pattern GreasingVersion :: Version Source #
pattern GreasingVersion2 :: Version Source #
isGreasingVersion :: Version -> Bool Source #
data VersionInfo Source #
Constructors
VersionInfo | |
Fields
|
Instances
Show VersionInfo Source # | |
Defined in Network.QUIC.Types.Packet Methods showsPrec :: Int -> VersionInfo -> ShowS # show :: VersionInfo -> String # showList :: [VersionInfo] -> ShowS # | |
Eq VersionInfo Source # | |
Defined in Network.QUIC.Types.Packet |
Constructors
PacketIV VersionNegotiationPacket | |
PacketIR RetryPacket | |
PacketIC CryptPacket EncryptionLevel Int | |
PacketIB BrokenPacket Int |
data VersionNegotiationPacket Source #
Constructors
VersionNegotiationPacket CID CID [Version] |
Instances
Show VersionNegotiationPacket Source # | |
Defined in Network.QUIC.Types.Packet Methods showsPrec :: Int -> VersionNegotiationPacket -> ShowS # show :: VersionNegotiationPacket -> String # showList :: [VersionNegotiationPacket] -> ShowS # | |
Eq VersionNegotiationPacket Source # | |
Defined in Network.QUIC.Types.Packet Methods (==) :: VersionNegotiationPacket -> VersionNegotiationPacket -> Bool # (/=) :: VersionNegotiationPacket -> VersionNegotiationPacket -> Bool # | |
Qlog VersionNegotiationPacket Source # | |
Defined in Network.QUIC.Qlog Methods |
data RetryPacket Source #
Constructors
RetryPacket Version CID CID Token (Either CID (ByteString, ByteString)) |
Instances
Show RetryPacket Source # | |
Defined in Network.QUIC.Types.Packet Methods showsPrec :: Int -> RetryPacket -> ShowS # show :: RetryPacket -> String # showList :: [RetryPacket] -> ShowS # | |
Eq RetryPacket Source # | |
Defined in Network.QUIC.Types.Packet | |
Qlog RetryPacket Source # | |
Defined in Network.QUIC.Qlog Methods qlog :: RetryPacket -> LogStr Source # |
data CryptPacket Source #
Constructors
CryptPacket Header Crypt |
Instances
Show CryptPacket Source # | |
Defined in Network.QUIC.Types.Packet Methods showsPrec :: Int -> CryptPacket -> ShowS # show :: CryptPacket -> String # showList :: [CryptPacket] -> ShowS # | |
Eq CryptPacket Source # | |
Defined in Network.QUIC.Types.Packet | |
Qlog CryptPacket Source # | |
Defined in Network.QUIC.Qlog Methods qlog :: CryptPacket -> LogStr Source # |
data EncryptionLevel Source #
Constructors
InitialLevel | |
RTT0Level | |
HandshakeLevel | |
RTT1Level |
Instances
Ix EncryptionLevel Source # | |
Defined in Network.QUIC.Types.Packet Methods range :: (EncryptionLevel, EncryptionLevel) -> [EncryptionLevel] # index :: (EncryptionLevel, EncryptionLevel) -> EncryptionLevel -> Int # unsafeIndex :: (EncryptionLevel, EncryptionLevel) -> EncryptionLevel -> Int # inRange :: (EncryptionLevel, EncryptionLevel) -> EncryptionLevel -> Bool # rangeSize :: (EncryptionLevel, EncryptionLevel) -> Int # unsafeRangeSize :: (EncryptionLevel, EncryptionLevel) -> Int # | |
Show EncryptionLevel Source # | |
Defined in Network.QUIC.Types.Packet Methods showsPrec :: Int -> EncryptionLevel -> ShowS # show :: EncryptionLevel -> String # showList :: [EncryptionLevel] -> ShowS # | |
Eq EncryptionLevel Source # | |
Defined in Network.QUIC.Types.Packet Methods (==) :: EncryptionLevel -> EncryptionLevel -> Bool # (/=) :: EncryptionLevel -> EncryptionLevel -> Bool # | |
Ord EncryptionLevel Source # | |
Defined in Network.QUIC.Types.Packet Methods compare :: EncryptionLevel -> EncryptionLevel -> Ordering # (<) :: EncryptionLevel -> EncryptionLevel -> Bool # (<=) :: EncryptionLevel -> EncryptionLevel -> Bool # (>) :: EncryptionLevel -> EncryptionLevel -> Bool # (>=) :: EncryptionLevel -> EncryptionLevel -> Bool # max :: EncryptionLevel -> EncryptionLevel -> EncryptionLevel # min :: EncryptionLevel -> EncryptionLevel -> EncryptionLevel # |
data BrokenPacket Source #
Constructors
BrokenPacket |
Instances
Show BrokenPacket Source # | |
Defined in Network.QUIC.Types.Packet Methods showsPrec :: Int -> BrokenPacket -> ShowS # show :: BrokenPacket -> String # showList :: [BrokenPacket] -> ShowS # | |
Eq BrokenPacket Source # | |
Defined in Network.QUIC.Types.Packet |
data PlainPacket Source #
Constructors
PlainPacket Header Plain |
Instances
Show PlainPacket Source # | |
Defined in Network.QUIC.Types.Packet Methods showsPrec :: Int -> PlainPacket -> ShowS # show :: PlainPacket -> String # showList :: [PlainPacket] -> ShowS # | |
Eq PlainPacket Source # | |
Defined in Network.QUIC.Types.Packet | |
Qlog PlainPacket Source # | |
Defined in Network.QUIC.Qlog Methods qlog :: PlainPacket -> LogStr Source # |
headerMyCID :: Header -> CID Source #
headerPeerCID :: Header -> CID Source #
Constructors
Plain | |
Fields
|
Constructors
Crypt | |
Fields
|
setIllegalReservedBits :: Int -> Int Source #
setUnknownFrame :: Int -> Int Source #
setNoFrames :: Int -> Int Source #
setNoPaddings :: Int -> Int Source #
set4bytesPN :: Int -> Int Source #
isIllegalReservedBits :: Int -> Bool Source #
isUnknownFrame :: Int -> Bool Source #
isNoFrames :: Int -> Bool Source #
isNoPaddings :: Int -> Bool Source #
is4bytesPN :: Int -> Bool Source #
isCryptDelayed :: Crypt -> Bool Source #
setCryptDelayed :: Crypt -> Crypt Source #
data StatelessReset Source #
Constructors
StatelessReset |
Instances
Show StatelessReset Source # | |
Defined in Network.QUIC.Types.Packet Methods showsPrec :: Int -> StatelessReset -> ShowS # show :: StatelessReset -> String # showList :: [StatelessReset] -> ShowS # | |
Eq StatelessReset Source # | |
Defined in Network.QUIC.Types.Packet Methods (==) :: StatelessReset -> StatelessReset -> Bool # (/=) :: StatelessReset -> StatelessReset -> Bool # | |
Qlog StatelessReset Source # | |
Defined in Network.QUIC.Qlog Methods qlog :: StatelessReset -> LogStr Source # |
data ReceivedPacket Source #
Constructors
ReceivedPacket | |
Instances
Show ReceivedPacket Source # | |
Defined in Network.QUIC.Types.Packet Methods showsPrec :: Int -> ReceivedPacket -> ShowS # show :: ReceivedPacket -> String # showList :: [ReceivedPacket] -> ShowS # | |
Eq ReceivedPacket Source # | |
Defined in Network.QUIC.Types.Packet Methods (==) :: ReceivedPacket -> ReceivedPacket -> Bool # (/=) :: ReceivedPacket -> ReceivedPacket -> Bool # |
mkReceivedPacket :: CryptPacket -> TimeMicrosecond -> Int -> EncryptionLevel -> ReceivedPacket Source #
data LongHeaderPacketType Source #
Instances
Show LongHeaderPacketType Source # | |
Defined in Network.QUIC.Types.Packet Methods showsPrec :: Int -> LongHeaderPacketType -> ShowS # show :: LongHeaderPacketType -> String # showList :: [LongHeaderPacketType] -> ShowS # | |
Eq LongHeaderPacketType Source # | |
Defined in Network.QUIC.Types.Packet Methods (==) :: LongHeaderPacketType -> LongHeaderPacketType -> Bool # (/=) :: LongHeaderPacketType -> LongHeaderPacketType -> Bool # |
type EncodedPacketNumber = Word32 Source #
writeRecvQ :: RecvQ -> ReceivedPacket -> IO () Source #
prependRecvQ :: RecvQ -> ReceivedPacket -> STM () Source #
data InternalControl Source #
Constructors
MustNotReached | |
ExitConnection | |
WrongTransportParameter | |
WrongVersionInformation | |
BreakForever |
Instances
Exception InternalControl Source # | |
Defined in Network.QUIC.Types.Exception Methods toException :: InternalControl -> SomeException # | |
Show InternalControl Source # | |
Defined in Network.QUIC.Types.Exception Methods showsPrec :: Int -> InternalControl -> ShowS # show :: InternalControl -> String # showList :: [InternalControl] -> ShowS # | |
Eq InternalControl Source # | |
Defined in Network.QUIC.Types.Exception Methods (==) :: InternalControl -> InternalControl -> Bool # (/=) :: InternalControl -> InternalControl -> Bool # |
newtype NextVersion Source #
Constructors
NextVersion VersionInfo |
Instances
Exception NextVersion Source # | |
Defined in Network.QUIC.Types.Exception Methods toException :: NextVersion -> SomeException # fromException :: SomeException -> Maybe NextVersion # displayException :: NextVersion -> String # | |
Show NextVersion Source # | |
Defined in Network.QUIC.Types.Exception Methods showsPrec :: Int -> NextVersion -> ShowS # show :: NextVersion -> String # showList :: [NextVersion] -> ShowS # |
Constructors
Abort ApplicationProtocolError ReasonPhrase | |
VerNego VersionInfo |
Instances
Exception Abort Source # | |
Defined in Network.QUIC.Types.Exception Methods toException :: Abort -> SomeException # fromException :: SomeException -> Maybe Abort # displayException :: Abort -> String # | |
Show Abort Source # | |
getRandomBytes :: Int -> IO ShortByteString Source #
isAsyncException :: Exception e => e -> Bool Source #
ignore :: SomeException -> IO () Source #
totalLen :: [ByteString] -> Int Source #
dec16 :: ByteString -> ByteString Source #
enc16 :: ByteString -> ByteString Source #
withByteString :: ByteString -> (Ptr Word8 -> IO a) -> IO a Source #
shortpack :: String -> ShortByteString Source #
throughAsync :: IO a -> SomeException -> IO a Source #
takePingSTM :: LDCC -> STM EncryptionLevel Source #
onPacketSent :: LDCC -> SentPacket -> IO () Source #
onPacketReceived :: LDCC -> EncryptionLevel -> PacketNumber -> IO () Source #
onAckReceived :: LDCC -> EncryptionLevel -> AckInfo -> Microseconds -> IO () Source #
onPacketNumberSpaceDiscarded :: LDCC -> EncryptionLevel -> IO () Source #
setPreviousRTT1PPNs :: LDCC -> PeerPacketNumbers -> IO () Source #
setMaxAckDaley :: LDCC -> Microseconds -> IO () Source #
findDuration :: Seq SentPacket -> PacketNumber -> Maybe UnixDiffTime Source #
releaseByRetry :: LDCC -> IO (Seq PlainPacket) Source #
releaseOldest :: LDCC -> EncryptionLevel -> IO (Maybe SentPacket) Source #
beforeAntiAmp :: LDCC -> IO () Source #
data SentPacket Source #
Instances
Show SentPacket Source # | |
Defined in Network.QUIC.Recovery.Types Methods showsPrec :: Int -> SentPacket -> ShowS # show :: SentPacket -> String # showList :: [SentPacket] -> ShowS # | |
Eq SentPacket Source # | |
Defined in Network.QUIC.Recovery.Types | |
Ord SentPacket Source # | |
Defined in Network.QUIC.Recovery.Types Methods compare :: SentPacket -> SentPacket -> Ordering # (<) :: SentPacket -> SentPacket -> Bool # (<=) :: SentPacket -> SentPacket -> Bool # (>) :: SentPacket -> SentPacket -> Bool # (>=) :: SentPacket -> SentPacket -> Bool # max :: SentPacket -> SentPacket -> SentPacket # min :: SentPacket -> SentPacket -> SentPacket # | |
Qlog SentPacket Source # | |
Defined in Network.QUIC.Recovery.Types Methods qlog :: SentPacket -> LogStr Source # |
mkSentPacket :: PacketNumber -> EncryptionLevel -> PlainPacket -> PeerPacketNumbers -> Bool -> SentPacket Source #
fixSentPacket :: SentPacket -> Int -> Int -> SentPacket Source #
Instances
Connector LDCC Source # | |
Defined in Network.QUIC.Recovery.Types Methods getRole :: LDCC -> Role Source # getEncryptionLevel :: LDCC -> IO EncryptionLevel Source # getMaxPacketSize :: LDCC -> IO Int Source # getConnectionState :: LDCC -> IO ConnectionState Source # getPacketNumber :: LDCC -> IO PacketNumber Source # | |
KeepQlog LDCC Source # | |
data ConnectionControl Source #
How to control a connection.
Constructors
ChangeServerCID | |
ChangeClientCID | |
NATRebinding | |
ActiveMigration |
Instances
Show ConnectionControl Source # | |
Defined in Network.QUIC.Client.Reader Methods showsPrec :: Int -> ConnectionControl -> ShowS # show :: ConnectionControl -> String # showList :: [ConnectionControl] -> ShowS # | |
Eq ConnectionControl Source # | |
Defined in Network.QUIC.Client.Reader Methods (==) :: ConnectionControl -> ConnectionControl -> Bool # (/=) :: ConnectionControl -> ConnectionControl -> Bool # |
controlConnection :: Connection -> ConnectionControl -> IO Bool Source #
windowsThreadBlockHack :: IO a -> IO a Source #
clientSocket :: HostName -> ServiceName -> IO (Socket, SockAddr) Source #
serverSocket :: (IP, PortNumber) -> IO Socket Source #