quic-0.0.1: QUIC
Safe HaskellNone
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 () 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 Coder Source #

Constructors

Coder 

Fields

data Protector Source #

Constructors

Protector 

Fields

data Connection Source #

A quic connection to carry multiple streams.

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
Eq Role Source # 
Instance details

Defined in Network.QUIC.Connector

Methods

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

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

Show Role Source # 
Instance details

Defined in Network.QUIC.Connector

Methods

showsPrec :: Int -> Role -> ShowS #

show :: Role -> String #

showList :: [Role] -> ShowS #

Payload encryption

Header Protection

Types

newtype Key Source #

Constructors

Key ByteString 

Instances

Instances details
Eq Key Source # 
Instance details

Defined in Network.QUIC.Crypto

Methods

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

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

Show Key Source # 
Instance details

Defined in Network.QUIC.Crypto

Methods

showsPrec :: Int -> Key -> ShowS #

show :: Key -> String #

showList :: [Key] -> ShowS #

newtype IV Source #

Constructors

IV ByteString 

Instances

Instances details
Eq IV Source # 
Instance details

Defined in Network.QUIC.Crypto

Methods

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

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

Show IV Source # 
Instance details

Defined in Network.QUIC.Crypto

Methods

showsPrec :: Int -> IV -> ShowS #

show :: IV -> String #

showList :: [IV] -> ShowS #

data CID Source #

A type for conneciton ID.

Instances

Instances details
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 #

Show CID Source # 
Instance details

Defined in Network.QUIC.Types.CID

Methods

showsPrec :: Int -> CID -> ShowS #

show :: CID -> String #

showList :: [CID] -> ShowS #

newtype Secret Source #

Constructors

Secret ByteString 

Instances

Instances details
Eq Secret Source # 
Instance details

Defined in Network.QUIC.Crypto

Methods

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

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

Show Secret Source # 
Instance details

Defined in Network.QUIC.Crypto

newtype AddDat Source #

Constructors

AddDat ByteString 

Instances

Instances details
Eq AddDat Source # 
Instance details

Defined in Network.QUIC.Crypto

Methods

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

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

Show AddDat Source # 
Instance details

Defined in Network.QUIC.Crypto

newtype Sample Source #

Constructors

Sample ByteString 

Instances

Instances details
Eq Sample Source # 
Instance details

Defined in Network.QUIC.Crypto

Methods

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

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

Show Sample Source # 
Instance details

Defined in Network.QUIC.Crypto

newtype Mask Source #

Constructors

Mask ByteString 

Instances

Instances details
Eq Mask Source # 
Instance details

Defined in Network.QUIC.Crypto

Methods

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

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

Show Mask Source # 
Instance details

Defined in Network.QUIC.Crypto

Methods

showsPrec :: Int -> Mask -> ShowS #

show :: Mask -> String #

showList :: [Mask] -> ShowS #

newtype Nonce Source #

Constructors

Nonce ByteString 

Instances

Instances details
Eq Nonce Source # 
Instance details

Defined in Network.QUIC.Crypto

Methods

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

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

Show Nonce Source # 
Instance details

Defined in Network.QUIC.Crypto

Methods

showsPrec :: Int -> Nonce -> ShowS #

show :: Nonce -> String #

showList :: [Nonce] -> ShowS #

data Cipher #

Cipher algorithm

Instances

Instances details
Eq Cipher 
Instance details

Defined in Network.TLS.Cipher

Methods

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

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

Show Cipher 
Instance details

Defined in Network.TLS.Cipher

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

Misc

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
Semigroup Builder 
Instance details

Defined in Data.ByteString.Builder.Internal

Monoid 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

defaultParameters :: Parameters Source #

An example parameters obsoleted in the near future.

baseParameters :: Parameters Source #

The default value for QUIC transport parameters.

data AuthCIDs Source #

Instances

Instances details
Eq AuthCIDs Source # 
Instance details

Defined in Network.QUIC.Parameters

Show 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 Frame Source # 
Instance details

Defined in Network.QUIC.Qlog

Methods

qlog :: Frame -> LogStr Source #

Qlog StatelessReset Source # 
Instance details

Defined in Network.QUIC.Qlog

Qlog CryptPacket Source # 
Instance details

Defined in Network.QUIC.Qlog

Qlog PlainPacket Source # 
Instance details

Defined in Network.QUIC.Qlog

Qlog Header Source # 
Instance details

Defined in Network.QUIC.Qlog

Methods

qlog :: Header -> LogStr Source #

Qlog RetryPacket Source # 
Instance details

Defined in Network.QUIC.Qlog

Qlog VersionNegotiationPacket Source # 
Instance details

Defined in Network.QUIC.Qlog

Qlog LR Source # 
Instance details

Defined in Network.QUIC.Qlog

Methods

qlog :: LR -> LogStr Source #

Qlog Debug Source # 
Instance details

Defined in Network.QUIC.Qlog

Methods

qlog :: Debug -> LogStr Source #

Qlog SentPacket Source # 
Instance details

Defined in Network.QUIC.Recovery.Types

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 Flow Source #

Constructors

Flow 

Fields

Instances

Instances details
Eq Flow Source # 
Instance details

Defined in Network.QUIC.Stream.Types

Methods

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

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

Show Flow Source # 
Instance details

Defined in Network.QUIC.Stream.Types

Methods

showsPrec :: Int -> Flow -> ShowS #

show :: Flow -> String #

showList :: [Flow] -> ShowS #

data StreamState Source #

Constructors

StreamState 

Instances

Instances details
Eq StreamState Source # 
Instance details

Defined in Network.QUIC.Stream.Types

Show 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 SendBuf = Buffer -> Int -> IO () Source #

type Close = IO () Source #

data Direction Source #

Instances

Instances details
Eq Direction Source # 
Instance details

Defined in Network.QUIC.Types.Frame

Show 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
Eq AckInfo Source # 
Instance details

Defined in Network.QUIC.Types.Ack

Methods

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

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

Show AckInfo Source # 
Instance details

Defined in Network.QUIC.Types.Ack

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
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 #

Show CID Source # 
Instance details

Defined in Network.QUIC.Types.CID

Methods

showsPrec :: Int -> CID -> ShowS #

show :: CID -> String #

showList :: [CID] -> ShowS #

fromCID :: CID -> ByteString Source #

Converting a connection ID.

newtype PathData Source #

Constructors

PathData Bytes 

Instances

Instances details
Eq PathData Source # 
Instance details

Defined in Network.QUIC.Types.CID

Show PathData Source # 
Instance details

Defined in Network.QUIC.Types.CID

data CIDInfo Source #

Instances

Instances details
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

Show 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
Eq Direction Source # 
Instance details

Defined in Network.QUIC.Types.Frame

Show 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
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

Show Version Source # 
Instance details

Defined in Network.QUIC.Types.Packet

pattern Draft29 :: Version Source #

data PacketO Source #

Instances

Instances details
Eq PacketO Source # 
Instance details

Defined in Network.QUIC.Types.Packet

Methods

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

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

Show PacketO Source # 
Instance details

Defined in Network.QUIC.Types.Packet

data RetryPacket Source #

Instances

Instances details
Eq RetryPacket Source # 
Instance details

Defined in Network.QUIC.Types.Packet

Show 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
Eq BrokenPacket Source # 
Instance details

Defined in Network.QUIC.Types.Packet

Show BrokenPacket Source # 
Instance details

Defined in Network.QUIC.Types.Packet

data Header Source #

Instances

Instances details
Eq Header Source # 
Instance details

Defined in Network.QUIC.Types.Packet

Methods

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

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

Show Header Source # 
Instance details

Defined in Network.QUIC.Types.Packet

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
Eq PlainPacket Source # 
Instance details

Defined in Network.QUIC.Types.Packet

Show 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
Eq CryptPacket Source # 
Instance details

Defined in Network.QUIC.Types.Packet

Show 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
Eq Plain Source # 
Instance details

Defined in Network.QUIC.Types.Packet

Methods

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

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

Show Plain Source # 
Instance details

Defined in Network.QUIC.Types.Packet

Methods

showsPrec :: Int -> Plain -> ShowS #

show :: Plain -> String #

showList :: [Plain] -> ShowS #

data Crypt Source #

Instances

Instances details
Eq Crypt Source # 
Instance details

Defined in Network.QUIC.Types.Packet

Methods

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

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

Show Crypt Source # 
Instance details

Defined in Network.QUIC.Types.Packet

Methods

showsPrec :: Int -> Crypt -> ShowS #

show :: Crypt -> String #

showList :: [Crypt] -> ShowS #

data EncryptionLevel Source #

newtype Flags a Source #

Constructors

Flags Word8 

Instances

Instances details
Eq (Flags a) Source # 
Instance details

Defined in Network.QUIC.Types.Packet

Methods

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

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

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 #

data Raw Source #

newtype RecvQ Source #

Constructors

RecvQ (TQueue ReceivedPacket) 

is0RTTPossible :: ResumptionInfo -> Bool Source #

Is 0RTT possible?

isResumptionPossible :: ResumptionInfo -> Bool Source #

Is resumption possible?

newtype Milliseconds Source #

Constructors

Milliseconds Int64 

Instances

Instances details
Eq Milliseconds Source # 
Instance details

Defined in Network.QUIC.Types.Time

Num Milliseconds Source # 
Instance details

Defined in Network.QUIC.Types.Time

Ord Milliseconds Source # 
Instance details

Defined in Network.QUIC.Types.Time

Show Milliseconds Source # 
Instance details

Defined in Network.QUIC.Types.Time

Bits Milliseconds Source # 
Instance details

Defined in Network.QUIC.Types.Time

newtype Microseconds Source #

Constructors

Microseconds Int 

Instances

Instances details
Eq Microseconds Source # 
Instance details

Defined in Network.QUIC.Types.Time

Num Microseconds Source # 
Instance details

Defined in Network.QUIC.Types.Time

Ord Microseconds Source # 
Instance details

Defined in Network.QUIC.Types.Time

Show Microseconds Source # 
Instance details

Defined in Network.QUIC.Types.Time

Bits 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 #