quic-0.1.20: QUIC
Safe HaskellSafe-Inferred
LanguageHaskell2010

Network.QUIC.Internal

Synopsis

Documentation

defaultHooks :: Hooks Source #

Default hooks.

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.

resetPeerCID :: Connection -> CID -> IO () Source #

Reseting to Initial CID in the client side.

getNewMyCID :: Connection -> IO CIDInfo Source #

Sending NewConnectionID

setMyCID :: Connection -> CID -> IO () Source #

Peer starts using a new CID.

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

closeConnection :: TransportError -> ReasonPhrase -> IO () Source #

Closing a connection with/without a transport error. Internal threads should use this.

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.

setRegister :: Connection -> (CID -> Connection -> IO ()) -> (CID -> IO ()) -> IO () Source #

data CIDDB Source #

Instances

Instances details
Show CIDDB Source # 
Instance details

Defined in Network.QUIC.Connection.Types

Methods

showsPrec :: Int -> CIDDB -> ShowS #

show :: CIDDB -> String #

showList :: [CIDDB] -> ShowS #

data Protector Source #

Constructors

Protector 

Fields

newtype StreamIdBase Source #

Constructors

StreamIdBase 

Instances

Instances details
Show StreamIdBase Source # 
Instance details

Defined in Network.QUIC.Connection.Types

Eq StreamIdBase Source # 
Instance details

Defined in Network.QUIC.Connection.Types

data Concurrency Source #

Instances

Instances details
Show Concurrency Source # 
Instance details

Defined in Network.QUIC.Connection.Types

type Send = Buffer -> Int -> IO () Source #

data Connection Source #

A quic connection to carry multiple streams.

Constructors

Connection 

Fields

newtype Input Source #

Constructors

InpStream Stream 

Instances

Instances details
Show Input Source # 
Instance details

Defined in Network.QUIC.Connection.Types

Methods

showsPrec :: Int -> Input -> ShowS #

show :: Input -> String #

showList :: [Input] -> ShowS #

data Crypto Source #

Instances

Instances details
Show Crypto Source # 
Instance details

Defined in Network.QUIC.Connection.Types

data Role Source #

Constructors

Client 
Server 

Instances

Instances details
Show Role Source # 
Instance details

Defined in Network.QUIC.Connector

Methods

showsPrec :: Int -> Role -> ShowS #

show :: Role -> String #

showList :: [Role] -> ShowS #

Eq Role Source # 
Instance details

Defined in Network.QUIC.Connector

Methods

(==) :: Role -> Role -> Bool #

(/=) :: Role -> Role -> Bool #

makeNiteEncrypt :: Cipher -> Key -> IV -> NiteEncrypt Source #

makeNiteDecrypt :: Cipher -> Key -> IV -> NiteDecrypt Source #

Types

newtype Key Source #

Constructors

Key ByteString 

Instances

Instances details
Show Key Source # 
Instance details

Defined in Network.QUIC.Crypto.Types

Methods

showsPrec :: Int -> Key -> ShowS #

show :: Key -> String #

showList :: [Key] -> ShowS #

Eq Key Source # 
Instance details

Defined in Network.QUIC.Crypto.Types

Methods

(==) :: Key -> Key -> Bool #

(/=) :: Key -> Key -> Bool #

newtype IV Source #

Constructors

IV ByteString 

Instances

Instances details
Show IV Source # 
Instance details

Defined in Network.QUIC.Crypto.Types

Methods

showsPrec :: Int -> IV -> ShowS #

show :: IV -> String #

showList :: [IV] -> ShowS #

Eq IV Source # 
Instance details

Defined in Network.QUIC.Crypto.Types

Methods

(==) :: IV -> IV -> Bool #

(/=) :: IV -> IV -> Bool #

data CID Source #

A type for conneciton ID.

Instances

Instances details
Generic CID Source # 
Instance details

Defined in Network.QUIC.Types.CID

Associated Types

type Rep CID :: Type -> Type #

Methods

from :: CID -> Rep CID x #

to :: Rep CID x -> CID #

Show CID Source # 
Instance details

Defined in Network.QUIC.Types.CID

Methods

showsPrec :: Int -> CID -> ShowS #

show :: CID -> String #

showList :: [CID] -> ShowS #

Eq CID Source # 
Instance details

Defined in Network.QUIC.Types.CID

Methods

(==) :: CID -> CID -> Bool #

(/=) :: CID -> CID -> Bool #

Ord CID Source # 
Instance details

Defined in Network.QUIC.Types.CID

Methods

compare :: CID -> CID -> Ordering #

(<) :: CID -> CID -> Bool #

(<=) :: CID -> CID -> Bool #

(>) :: CID -> CID -> Bool #

(>=) :: CID -> CID -> Bool #

max :: CID -> CID -> CID #

min :: CID -> CID -> CID #

Serialise CID Source # 
Instance details

Defined in Network.QUIC.Types.CID

type Rep CID Source # 
Instance details

Defined in Network.QUIC.Types.CID

type Rep CID = D1 ('MetaData "CID" "Network.QUIC.Types.CID" "quic-0.1.20-4xBoOzsr86T1PD98iEWMzj" 'True) (C1 ('MetaCons "CID" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bytes)))

newtype Secret Source #

Constructors

Secret ByteString 

Instances

Instances details
Show Secret Source # 
Instance details

Defined in Network.QUIC.Crypto.Types

Eq Secret Source # 
Instance details

Defined in Network.QUIC.Crypto.Types

Methods

(==) :: Secret -> Secret -> Bool #

(/=) :: Secret -> Secret -> Bool #

newtype AssDat Source #

Constructors

AssDat ByteString 

Instances

Instances details
Show AssDat Source # 
Instance details

Defined in Network.QUIC.Crypto.Types

Eq AssDat Source # 
Instance details

Defined in Network.QUIC.Crypto.Types

Methods

(==) :: AssDat -> AssDat -> Bool #

(/=) :: AssDat -> AssDat -> Bool #

newtype Sample Source #

Constructors

Sample ByteString 

Instances

Instances details
Show Sample Source # 
Instance details

Defined in Network.QUIC.Crypto.Types

Eq Sample Source # 
Instance details

Defined in Network.QUIC.Crypto.Types

Methods

(==) :: Sample -> Sample -> Bool #

(/=) :: Sample -> Sample -> Bool #

newtype Mask Source #

Constructors

Mask ByteString 

Instances

Instances details
Show Mask Source # 
Instance details

Defined in Network.QUIC.Crypto.Types

Methods

showsPrec :: Int -> Mask -> ShowS #

show :: Mask -> String #

showList :: [Mask] -> ShowS #

Eq Mask Source # 
Instance details

Defined in Network.QUIC.Crypto.Types

Methods

(==) :: Mask -> Mask -> Bool #

(/=) :: Mask -> Mask -> Bool #

newtype Nonce Source #

Constructors

Nonce ByteString 

Instances

Instances details
Show Nonce Source # 
Instance details

Defined in Network.QUIC.Crypto.Types

Methods

showsPrec :: Int -> Nonce -> ShowS #

show :: Nonce -> String #

showList :: [Nonce] -> ShowS #

Eq Nonce Source # 
Instance details

Defined in Network.QUIC.Crypto.Types

Methods

(==) :: Nonce -> Nonce -> Bool #

(/=) :: Nonce -> Nonce -> Bool #

newtype Label Source #

Constructors

Label ByteString 

Instances

Instances details
Show Label Source # 
Instance details

Defined in Network.QUIC.Crypto.Types

Methods

showsPrec :: Int -> Label -> ShowS #

show :: Label -> String #

showList :: [Label] -> ShowS #

Eq Label Source # 
Instance details

Defined in Network.QUIC.Crypto.Types

Methods

(==) :: Label -> Label -> Bool #

(/=) :: Label -> Label -> Bool #

data Cipher #

Cipher algorithm

Instances

Instances details
Show Cipher 
Instance details

Defined in Network.TLS.Cipher

Eq Cipher 
Instance details

Defined in Network.TLS.Cipher

Methods

(==) :: Cipher -> Cipher -> Bool #

(/=) :: Cipher -> Cipher -> Bool #

type TrafficSecrets a = (ClientTrafficSecret a, ServerTrafficSecret a) #

Hold both client and server traffic secrets at the same step.

newtype ClientTrafficSecret a #

A client traffic secret, typed with a parameter indicating a step in the TLS key schedule.

Instances

Instances details
Show (ClientTrafficSecret a) 
Instance details

Defined in Network.TLS.Types

newtype ServerTrafficSecret a #

A server traffic secret, typed with a parameter indicating a step in the TLS key schedule.

Instances

Instances details
Show (ServerTrafficSecret a) 
Instance details

Defined in Network.TLS.Types

data Builder #

Builders denote sequences of bytes. They are Monoids where mempty is the zero-length sequence and mappend is concatenation, which runs in O(1).

Instances

Instances details
Monoid Builder 
Instance details

Defined in Data.ByteString.Builder.Internal

Semigroup Builder 
Instance details

Defined in Data.ByteString.Builder.Internal

ToLogStr Builder 
Instance details

Defined in System.Log.FastLogger.LogStr

Methods

toLogStr :: Builder -> LogStr #

type DebugLogger = Builder -> IO () Source #

A type for debug logger.

bhow :: Show a => a -> Builder Source #

Encode

Decode

Frame

Header

Token

data CryptoToken Source #

Instances

Instances details
Generic CryptoToken Source # 
Instance details

Defined in Network.QUIC.Packet.Token

Associated Types

type Rep CryptoToken :: Type -> Type #

Serialise CryptoToken Source # 
Instance details

Defined in Network.QUIC.Packet.Token

type Rep CryptoToken Source # 
Instance details

Defined in Network.QUIC.Packet.Token

type Rep CryptoToken = D1 ('MetaData "CryptoToken" "Network.QUIC.Packet.Token" "quic-0.1.20-4xBoOzsr86T1PD98iEWMzj" 'False) (C1 ('MetaCons "CryptoToken" 'PrefixI 'True) ((S1 ('MetaSel ('Just "tokenQUICVersion") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Version) :*: S1 ('MetaSel ('Just "tokenLifeTime") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Word32)) :*: (S1 ('MetaSel ('Just "tokenCreatedTime") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 TimeMicrosecond) :*: S1 ('MetaSel ('Just "tokenCIDs") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Maybe (CID, CID, CID))))))

defaultParameters :: Parameters Source #

An example parameters obsoleted in the near future.

>>> defaultParameters
Parameters {originalDestinationConnectionId = Nothing, maxIdleTimeout = 30000, statelessResetToken = Nothing, maxUdpPayloadSize = 2048, initialMaxData = 1048576, initialMaxStreamDataBidiLocal = 262144, initialMaxStreamDataBidiRemote = 262144, initialMaxStreamDataUni = 262144, initialMaxStreamsBidi = 64, initialMaxStreamsUni = 3, ackDelayExponent = 3, maxAckDelay = 25, disableActiveMigration = False, preferredAddress = Nothing, activeConnectionIdLimit = 3, initialSourceConnectionId = Nothing, retrySourceConnectionId = Nothing, grease = Nothing, greaseQuicBit = True, versionInformation = Nothing}

baseParameters :: Parameters Source #

The default value for QUIC transport parameters.

data AuthCIDs Source #

Instances

Instances details
Show AuthCIDs Source # 
Instance details

Defined in Network.QUIC.Parameters

Eq AuthCIDs Source # 
Instance details

Defined in Network.QUIC.Parameters

type QLogger = QlogMsg -> IO () Source #

class Qlog a where Source #

Methods

qlog :: a -> LogStr Source #

Instances

Instances details
Qlog Debug Source # 
Instance details

Defined in Network.QUIC.Qlog

Methods

qlog :: Debug -> LogStr Source #

Qlog LR Source # 
Instance details

Defined in Network.QUIC.Qlog

Methods

qlog :: LR -> LogStr Source #

Qlog SentPacket Source # 
Instance details

Defined in Network.QUIC.Recovery.Types

Qlog Frame Source # 
Instance details

Defined in Network.QUIC.Qlog

Methods

qlog :: Frame -> LogStr Source #

Qlog CryptPacket Source # 
Instance details

Defined in Network.QUIC.Qlog

Qlog Header Source # 
Instance details

Defined in Network.QUIC.Qlog

Methods

qlog :: Header -> LogStr Source #

Qlog PlainPacket Source # 
Instance details

Defined in Network.QUIC.Qlog

Qlog RetryPacket Source # 
Instance details

Defined in Network.QUIC.Qlog

Qlog StatelessReset Source # 
Instance details

Defined in Network.QUIC.Qlog

Qlog VersionNegotiationPacket Source # 
Instance details

Defined in Network.QUIC.Qlog

Qlog (Parameters, String) Source # 
Instance details

Defined in Network.QUIC.Qlog

class KeepQlog a where Source #

Methods

keepQlog :: a -> QLogger Source #

Instances

Instances details
KeepQlog Connection Source # 
Instance details

Defined in Network.QUIC.Connection.Types

KeepQlog LDCC Source # 
Instance details

Defined in Network.QUIC.Recovery.Types

qlogReceived :: (KeepQlog q, Qlog a) => q -> a -> TimeMicrosecond -> IO () Source #

qlogDropped :: (KeepQlog q, Qlog a) => q -> a -> IO () Source #

qlogSentRetry :: KeepQlog q => q -> IO () Source #

qlogDebug :: KeepQlog q => q -> Debug -> IO () Source #

qlogCIDUpdate :: KeepQlog q => q -> LR -> IO () Source #

newtype Debug Source #

Constructors

Debug LogStr 

Instances

Instances details
Show Debug Source # 
Instance details

Defined in Network.QUIC.Qlog

Methods

showsPrec :: Int -> Debug -> ShowS #

show :: Debug -> String #

showList :: [Debug] -> ShowS #

Qlog Debug Source # 
Instance details

Defined in Network.QUIC.Qlog

Methods

qlog :: Debug -> LogStr Source #

data LR Source #

Constructors

Local CID 
Remote CID 

Instances

Instances details
Qlog LR Source # 
Instance details

Defined in Network.QUIC.Qlog

Methods

qlog :: LR -> LogStr Source #

sw :: Show a => a -> LogStr Source #

Types

data Stream Source #

An abstract data type for streams.

Instances

Instances details
Show Stream Source # 
Instance details

Defined in Network.QUIC.Stream.Types

streamId :: Stream -> StreamId Source #

Getting stream identifier.

data StreamState Source #

Constructors

StreamState 

Instances

Instances details
Show StreamState Source # 
Instance details

Defined in Network.QUIC.Stream.Types

Eq StreamState Source # 
Instance details

Defined in Network.QUIC.Stream.Types

Misc

Reass

Table

type Bytes = ShortByteString Source #

All internal byte sequences. ByteString should be used for FFI related stuff.

type Close = IO () Source #

data Direction Source #

Instances

Instances details
Show Direction Source # 
Instance details

Defined in Network.QUIC.Types.Frame

Eq Direction Source # 
Instance details

Defined in Network.QUIC.Types.Frame

type Range = Int Source #

type Gap = Int Source #

data AckInfo Source #

Constructors

AckInfo PacketNumber Range [(Gap, Range)] 

Instances

Instances details
Show AckInfo Source # 
Instance details

Defined in Network.QUIC.Types.Ack

Eq AckInfo Source # 
Instance details

Defined in Network.QUIC.Types.Ack

Methods

(==) :: AckInfo -> AckInfo -> Bool #

(/=) :: AckInfo -> AckInfo -> Bool #

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]

newtype CID Source #

A type for conneciton ID.

Constructors

CID Bytes 

Instances

Instances details
Generic CID Source # 
Instance details

Defined in Network.QUIC.Types.CID

Associated Types

type Rep CID :: Type -> Type #

Methods

from :: CID -> Rep CID x #

to :: Rep CID x -> CID #

Show CID Source # 
Instance details

Defined in Network.QUIC.Types.CID

Methods

showsPrec :: Int -> CID -> ShowS #

show :: CID -> String #

showList :: [CID] -> ShowS #

Eq CID Source # 
Instance details

Defined in Network.QUIC.Types.CID

Methods

(==) :: CID -> CID -> Bool #

(/=) :: CID -> CID -> Bool #

Ord CID Source # 
Instance details

Defined in Network.QUIC.Types.CID

Methods

compare :: CID -> CID -> Ordering #

(<) :: CID -> CID -> Bool #

(<=) :: CID -> CID -> Bool #

(>) :: CID -> CID -> Bool #

(>=) :: CID -> CID -> Bool #

max :: CID -> CID -> CID #

min :: CID -> CID -> CID #

Serialise CID Source # 
Instance details

Defined in Network.QUIC.Types.CID

type Rep CID Source # 
Instance details

Defined in Network.QUIC.Types.CID

type Rep CID = D1 ('MetaData "CID" "Network.QUIC.Types.CID" "quic-0.1.20-4xBoOzsr86T1PD98iEWMzj" 'True) (C1 ('MetaCons "CID" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bytes)))

fromCID :: CID -> ByteString Source #

Converting a connection ID.

newtype PathData Source #

Constructors

PathData Bytes 

Instances

Instances details
Show PathData Source # 
Instance details

Defined in Network.QUIC.Types.CID

Eq PathData Source # 
Instance details

Defined in Network.QUIC.Types.CID

data CIDInfo Source #

Instances

Instances details
Show CIDInfo Source # 
Instance details

Defined in Network.QUIC.Types.CID

Eq CIDInfo Source # 
Instance details

Defined in Network.QUIC.Types.CID

Methods

(==) :: CIDInfo -> CIDInfo -> Bool #

(/=) :: CIDInfo -> CIDInfo -> Bool #

Ord CIDInfo Source # 
Instance details

Defined in Network.QUIC.Types.CID

newtype TransportError Source #

Transport errors of QUIC.

Constructors

TransportError Int 

cryptoError :: AlertDescription -> TransportError Source #

Converting a TLS alert to a corresponding transport error.

data Direction Source #

Instances

Instances details
Show Direction Source # 
Instance details

Defined in Network.QUIC.Types.Frame

Eq Direction Source # 
Instance details

Defined in Network.QUIC.Types.Frame

type StreamId = Int Source #

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.

type Fin = Bool Source #

encodeInt :: Int64 -> ByteString Source #

>>> enc16 $ encodeInt 151288809941952652
"c2197c5eff14e88c"
>>> enc16 $ encodeInt 494878333
"9d7f3e7d"
>>> enc16 $ encodeInt 15293
"7bbd"
>>> enc16 $ encodeInt 37
"25"

decodeInt :: ByteString -> Int64 Source #

>>> decodeInt (dec16 "c2197c5eff14e88c")
151288809941952652
>>> decodeInt (dec16 "9d7f3e7d")
494878333
>>> decodeInt (dec16 "7bbd")
15293
>>> decodeInt (dec16 "25")
37

newtype Version Source #

QUIC version.

Constructors

Version Word32 

Instances

Instances details
Generic Version Source # 
Instance details

Defined in Network.QUIC.Types.Packet

Associated Types

type Rep Version :: Type -> Type #

Methods

from :: Version -> Rep Version x #

to :: Rep Version x -> Version #

Show Version Source # 
Instance details

Defined in Network.QUIC.Types.Packet

Eq Version Source # 
Instance details

Defined in Network.QUIC.Types.Packet

Methods

(==) :: Version -> Version -> Bool #

(/=) :: Version -> Version -> Bool #

Ord Version Source # 
Instance details

Defined in Network.QUIC.Types.Packet

Serialise Version Source # 
Instance details

Defined in Network.QUIC.Types.Packet

type Rep Version Source # 
Instance details

Defined in Network.QUIC.Types.Packet

type Rep Version = D1 ('MetaData "Version" "Network.QUIC.Types.Packet" "quic-0.1.20-4xBoOzsr86T1PD98iEWMzj" 'True) (C1 ('MetaCons "Version" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Word32)))

pattern Draft29 :: Version Source #

data VersionInfo Source #

Constructors

VersionInfo 

Instances

Instances details
Show VersionInfo Source # 
Instance details

Defined in Network.QUIC.Types.Packet

Eq VersionInfo Source # 
Instance details

Defined in Network.QUIC.Types.Packet

data PacketO Source #

Instances

Instances details
Show PacketO Source # 
Instance details

Defined in Network.QUIC.Types.Packet

Eq PacketO Source # 
Instance details

Defined in Network.QUIC.Types.Packet

Methods

(==) :: PacketO -> PacketO -> Bool #

(/=) :: PacketO -> PacketO -> Bool #

data RetryPacket Source #

Instances

Instances details
Show RetryPacket Source # 
Instance details

Defined in Network.QUIC.Types.Packet

Eq RetryPacket Source # 
Instance details

Defined in Network.QUIC.Types.Packet

Qlog RetryPacket Source # 
Instance details

Defined in Network.QUIC.Qlog

data BrokenPacket Source #

Constructors

BrokenPacket 

Instances

Instances details
Show BrokenPacket Source # 
Instance details

Defined in Network.QUIC.Types.Packet

Eq BrokenPacket Source # 
Instance details

Defined in Network.QUIC.Types.Packet

data Header Source #

Instances

Instances details
Show Header Source # 
Instance details

Defined in Network.QUIC.Types.Packet

Eq Header Source # 
Instance details

Defined in Network.QUIC.Types.Packet

Methods

(==) :: Header -> Header -> Bool #

(/=) :: Header -> Header -> Bool #

Qlog Header Source # 
Instance details

Defined in Network.QUIC.Qlog

Methods

qlog :: Header -> LogStr Source #

data PlainPacket Source #

Constructors

PlainPacket Header Plain 

Instances

Instances details
Show PlainPacket Source # 
Instance details

Defined in Network.QUIC.Types.Packet

Eq PlainPacket Source # 
Instance details

Defined in Network.QUIC.Types.Packet

Qlog PlainPacket Source # 
Instance details

Defined in Network.QUIC.Qlog

data CryptPacket Source #

Constructors

CryptPacket Header Crypt 

Instances

Instances details
Show CryptPacket Source # 
Instance details

Defined in Network.QUIC.Types.Packet

Eq CryptPacket Source # 
Instance details

Defined in Network.QUIC.Types.Packet

Qlog CryptPacket Source # 
Instance details

Defined in Network.QUIC.Qlog

data Plain Source #

Instances

Instances details
Show Plain Source # 
Instance details

Defined in Network.QUIC.Types.Packet

Methods

showsPrec :: Int -> Plain -> ShowS #

show :: Plain -> String #

showList :: [Plain] -> ShowS #

Eq Plain Source # 
Instance details

Defined in Network.QUIC.Types.Packet

Methods

(==) :: Plain -> Plain -> Bool #

(/=) :: Plain -> Plain -> Bool #

data Crypt Source #

Instances

Instances details
Show Crypt Source # 
Instance details

Defined in Network.QUIC.Types.Packet

Methods

showsPrec :: Int -> Crypt -> ShowS #

show :: Crypt -> String #

showList :: [Crypt] -> ShowS #

Eq Crypt Source # 
Instance details

Defined in Network.QUIC.Types.Packet

Methods

(==) :: Crypt -> Crypt -> Bool #

(/=) :: Crypt -> Crypt -> Bool #

data EncryptionLevel Source #

newtype Flags a Source #

Constructors

Flags Word8 

Instances

Instances details
Show (Flags a) Source # 
Instance details

Defined in Network.QUIC.Types.Packet

Methods

showsPrec :: Int -> Flags a -> ShowS #

show :: Flags a -> String #

showList :: [Flags a] -> ShowS #

Eq (Flags a) Source # 
Instance details

Defined in Network.QUIC.Types.Packet

Methods

(==) :: Flags a -> Flags a -> Bool #

(/=) :: Flags a -> Flags a -> Bool #

data Raw Source #

newtype RecvQ Source #

Constructors

RecvQ (TQueue ReceivedPacket) 

data ResumptionInfo Source #

Information about resumption

Instances

Instances details
Generic ResumptionInfo Source # 
Instance details

Defined in Network.QUIC.Types.Resumption

Associated Types

type Rep ResumptionInfo :: Type -> Type #

Show ResumptionInfo Source # 
Instance details

Defined in Network.QUIC.Types.Resumption

Eq ResumptionInfo Source # 
Instance details

Defined in Network.QUIC.Types.Resumption

Serialise ResumptionInfo Source # 
Instance details

Defined in Network.QUIC.Types.Resumption

type Rep ResumptionInfo Source # 
Instance details

Defined in Network.QUIC.Types.Resumption

type Rep ResumptionInfo = D1 ('MetaData "ResumptionInfo" "Network.QUIC.Types.Resumption" "quic-0.1.20-4xBoOzsr86T1PD98iEWMzj" 'False) (C1 ('MetaCons "ResumptionInfo" 'PrefixI 'True) ((S1 ('MetaSel ('Just "resumptionVersion") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Version) :*: S1 ('MetaSel ('Just "resumptionSession") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Maybe (SessionID, SessionData)))) :*: (S1 ('MetaSel ('Just "resumptionToken") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Token) :*: S1 ('MetaSel ('Just "resumptionRetry") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Bool))))

is0RTTPossible :: ResumptionInfo -> Bool Source #

Is 0RTT possible?

isResumptionPossible :: ResumptionInfo -> Bool Source #

Is resumption possible?

newtype Milliseconds Source #

Constructors

Milliseconds Int64 

Instances

Instances details
Bits Milliseconds Source # 
Instance details

Defined in Network.QUIC.Types.Time

Num Milliseconds Source # 
Instance details

Defined in Network.QUIC.Types.Time

Show Milliseconds Source # 
Instance details

Defined in Network.QUIC.Types.Time

Eq Milliseconds Source # 
Instance details

Defined in Network.QUIC.Types.Time

Ord Milliseconds Source # 
Instance details

Defined in Network.QUIC.Types.Time

newtype Microseconds Source #

Constructors

Microseconds Int 

Instances

Instances details
Bits Microseconds Source # 
Instance details

Defined in Network.QUIC.Types.Time

Num Microseconds Source # 
Instance details

Defined in Network.QUIC.Types.Time

Show Microseconds Source # 
Instance details

Defined in Network.QUIC.Types.Time

Eq Microseconds Source # 
Instance details

Defined in Network.QUIC.Types.Time

Ord Microseconds Source # 
Instance details

Defined in Network.QUIC.Types.Time

fromRight :: b -> Either a b -> b Source #

sum' :: (Functor f, Foldable f) => f Int -> Int Source #

qlogSent :: (KeepQlog q, Qlog pkt) => q -> pkt -> TimeMicrosecond -> IO () Source #