Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
This main module provides APIs for QUIC.
The -threaded option must be specified to GHC to use this library.
Synopsis
- data Connection
- abortConnection :: Connection -> ApplicationProtocolError -> ReasonPhrase -> IO ()
- data Stream
- type StreamId = Int
- streamId :: Stream -> StreamId
- isClientInitiatedBidirectional :: StreamId -> Bool
- isServerInitiatedBidirectional :: StreamId -> Bool
- isClientInitiatedUnidirectional :: StreamId -> Bool
- isServerInitiatedUnidirectional :: StreamId -> Bool
- stream :: Connection -> IO Stream
- unidirectionalStream :: Connection -> IO Stream
- acceptStream :: Connection -> IO Stream
- closeStream :: Stream -> IO ()
- shutdownStream :: Stream -> IO ()
- resetStream :: Stream -> ApplicationProtocolError -> IO ()
- stopStream :: Stream -> ApplicationProtocolError -> IO ()
- recvStream :: Stream -> Int -> IO ByteString
- sendStream :: Stream -> ByteString -> IO ()
- sendStreamMany :: Stream -> [ByteString] -> IO ()
- data ConnectionInfo = ConnectionInfo {
- version :: Version
- cipher :: Cipher
- alpn :: Maybe ByteString
- handshakeMode :: HandshakeMode13
- retry :: Bool
- localSockAddr :: SockAddr
- remoteSockAddr :: SockAddr
- localCID :: CID
- remoteCID :: CID
- getConnectionInfo :: Connection -> IO ConnectionInfo
- data ConnectionStats = ConnectionStats {}
- getConnectionStats :: Connection -> IO ConnectionStats
- wait0RTTReady :: Connection -> IO ()
- wait1RTTReady :: Connection -> IO ()
- waitEstablished :: Connection -> IO ()
- data QUICException
- = ConnectionIsClosed
- | TransportErrorIsReceived TransportError ReasonPhrase
- | TransportErrorIsSent TransportError ReasonPhrase
- | ApplicationProtocolErrorIsReceived ApplicationProtocolError ReasonPhrase
- | ApplicationProtocolErrorIsSent ApplicationProtocolError ReasonPhrase
- | ConnectionIsTimeout String
- | ConnectionIsReset
- | StreamIsClosed
- | HandshakeFailed AlertDescription
- | VersionIsUnknown Word32
- | NoVersionIsSpecified
- | VersionNegotiationFailed
- | BadThingHappen SomeException
- newtype TransportError where
- TransportError Int
- pattern NoError :: TransportError
- pattern InternalError :: 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
Connection
data Connection Source #
A quic connection to carry multiple streams.
Instances
Connector Connection Source # | |
Defined in Network.QUIC.Connection.Types 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 keepQlog :: Connection -> QLogger Source # |
abortConnection :: Connection -> ApplicationProtocolError -> ReasonPhrase -> IO () Source #
Closing a connection with an application protocol error.
Stream
An abstract data type for streams.
Stream identifier. This should be 62-bit interger. On 32-bit machines, the total number of stream identifiers is limited.
Category
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.
Opening
unidirectionalStream :: Connection -> IO Stream Source #
Creating a unidirectional stream.
acceptStream :: Connection -> IO Stream Source #
Accepting a stream initiated by the peer.
Closing
closeStream :: Stream -> IO () Source #
Closing a stream without an error. This sends FIN if necessary.
shutdownStream :: Stream -> IO () Source #
Sending FIN in a stream.
closeStream
should be called later.
resetStream :: Stream -> ApplicationProtocolError -> IO () Source #
Closing a stream with an error code.
This sends RESET_STREAM to the peer.
This is an alternative of closeStream
.
stopStream :: Stream -> ApplicationProtocolError -> IO () Source #
Asking the peer to stop sending.
This sends STOP_SENDING to the peer
and it will send RESET_STREAM back.
closeStream
should be called later.
IO
recvStream :: Stream -> Int -> IO ByteString Source #
Receiving data in the stream. In the case where a FIN is received an empty bytestring is returned.
sendStream :: Stream -> ByteString -> IO () Source #
Sending data in the stream.
sendStreamMany :: Stream -> [ByteString] -> IO () Source #
Sending a list of data in the stream.
Information
data ConnectionInfo Source #
Information about a connection.
ConnectionInfo | |
|
Instances
Show ConnectionInfo Source # | |
Defined in Network.QUIC.Types.Info showsPrec :: Int -> ConnectionInfo -> ShowS # show :: ConnectionInfo -> String # showList :: [ConnectionInfo] -> ShowS # |
getConnectionInfo :: Connection -> IO ConnectionInfo Source #
Getting information about a connection.
Statistics
data ConnectionStats Source #
Statistics of a connection.
Instances
Show ConnectionStats Source # | |
Defined in Network.QUIC.Info showsPrec :: Int -> ConnectionStats -> ShowS # show :: ConnectionStats -> String # showList :: [ConnectionStats] -> ShowS # | |
Eq ConnectionStats Source # | |
Defined in Network.QUIC.Info (==) :: ConnectionStats -> ConnectionStats -> Bool # (/=) :: ConnectionStats -> ConnectionStats -> Bool # |
getConnectionStats :: Connection -> IO ConnectionStats Source #
Getting statistics of a connection.
Synchronization
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.
Exceptions and Errors
data QUICException Source #
User level exceptions for QUIC.
Instances
Exception QUICException Source # | |
Defined in Network.QUIC.Types.Exception | |
Show QUICException Source # | |
Defined in Network.QUIC.Types.Exception showsPrec :: Int -> QUICException -> ShowS # show :: QUICException -> String # showList :: [QUICException] -> ShowS # |
newtype TransportError Source #
Transport errors of QUIC.
pattern NoError :: TransportError | |
pattern InternalError :: 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 |
Instances
Show TransportError Source # | |
Defined in Network.QUIC.Types.Error showsPrec :: Int -> TransportError -> ShowS # show :: TransportError -> String # showList :: [TransportError] -> ShowS # | |
Eq TransportError Source # | |
Defined in Network.QUIC.Types.Error (==) :: TransportError -> TransportError -> Bool # (/=) :: TransportError -> TransportError -> Bool # |
cryptoError :: AlertDescription -> TransportError Source #
Converting a TLS alert to a corresponding transport error.
newtype ApplicationProtocolError Source #
Application protocol errors of QUIC.
Instances
Show ApplicationProtocolError Source # | |
Defined in Network.QUIC.Types.Error showsPrec :: Int -> ApplicationProtocolError -> ShowS # show :: ApplicationProtocolError -> String # showList :: [ApplicationProtocolError] -> ShowS # | |
Eq ApplicationProtocolError Source # | |
Defined in Network.QUIC.Types.Error |