tls-1.5.5: TLS/SSL protocol native implementation (Server and Client)
LicenseBSD-style
MaintainerVincent Hanquez <vincent@snarc.org>
Stabilityexperimental
Portabilityunknown
Safe HaskellNone
LanguageHaskell2010

Network.TLS.QUIC

Description

Experimental API to run the TLS handshake establishing a QUIC connection.

On the northbound API:

TLS invokes QUIC callbacks to use the QUIC transport

  • TLS uses quicSend and quicRecv to send and receive handshake message fragments.
  • TLS calls quicInstallKeys to provide to QUIC the traffic secrets it should use for encryption/decryption.
  • TLS calls quicNotifyExtensions to notify to QUIC the transport parameters exchanged through the handshake protocol.
  • TLS calls quicDone when the handshake is done.
Synopsis

Handshakers

tlsQUICClient :: ClientParams -> QUICCallbacks -> IO () Source #

Start a TLS handshake thread for a QUIC client. The client will use the specified TLS parameters and call the provided callback functions to send and receive handshake data.

tlsQUICServer :: ServerParams -> QUICCallbacks -> IO () Source #

Start a TLS handshake thread for a QUIC server. The server will use the specified TLS parameters and call the provided callback functions to send and receive handshake data.

Callback

data QUICCallbacks Source #

Callbacks implemented by QUIC and to be called by TLS at specific points during the handshake. TLS may invoke them from external threads but calls are not concurrent. Only a single callback function is called at a given point in time.

Constructors

QUICCallbacks 

Fields

  • quicSend :: [(CryptLevel, ByteString)] -> IO ()

    Called by TLS so that QUIC sends one or more handshake fragments. The content transiting on this API is the plaintext of the fragments and QUIC responsability is to encrypt this payload with the key material given for the specified level and an appropriate encryption scheme.

    The size of the fragments may exceed QUIC datagram limits so QUIC may break them into smaller fragments.

    The handshake protocol sometimes combines content at two levels in a single flight. The TLS library does its best to provide this in the same quicSend call and with a multi-valued argument. QUIC can then decide how to transmit this optimally.

  • quicRecv :: CryptLevel -> IO (Either TLSError ByteString)

    Called by TLS to receive from QUIC the next plaintext handshake fragment. The argument specifies with which encryption level the fragment should be decrypted.

    QUIC may return partial fragments to TLS. TLS will then call quicRecv again as long as necessary. Note however that fragments must be returned in the correct sequence, i.e. the order the TLS peer emitted them.

    The function may return an error to TLS if end of stream is reached or if a protocol error has been received, believing the handshake cannot proceed any longer. If the TLS handshake protocol cannot recover from this error, the failure condition will be reported back to QUIC through the control interface.

  • quicInstallKeys :: Context -> KeyScheduleEvent -> IO ()

    Called by TLS when new encryption material is ready to be used in the handshake. The next quicSend or quicRecv may now use the associated encryption level (although the previous level is also possible: directions Send/Recv do not change at the same time).

  • quicNotifyExtensions :: Context -> [ExtensionRaw] -> IO ()

    Called by TLS when QUIC-specific extensions have been received from the peer.

  • quicDone :: Context -> IO ()

    Called when handshake is done. tlsQUICServer is finished after calling this hook. tlsQUICClient calls recvData after calling this hook to wait for new session tickets.

data CryptLevel Source #

TLS encryption level.

Constructors

CryptInitial

Unprotected traffic

CryptMasterSecret

Protected with master secret (TLS < 1.3)

CryptEarlySecret

Protected with early traffic secret (TLS 1.3)

CryptHandshakeSecret

Protected with handshake traffic secret (TLS 1.3)

CryptApplicationSecret

Protected with application traffic secret (TLS 1.3)

Instances

Instances details
Eq CryptLevel Source # 
Instance details

Defined in Network.TLS.Record.State

Show CryptLevel Source # 
Instance details

Defined in Network.TLS.Record.State

data KeyScheduleEvent Source #

Argument given to quicInstallKeys when encryption material is available.

Constructors

InstallEarlyKeys (Maybe EarlySecretInfo)

Key material and parameters for traffic at 0-RTT level

InstallHandshakeKeys HandshakeSecretInfo

Key material and parameters for traffic at handshake level

InstallApplicationKeys ApplicationSecretInfo

Key material and parameters for traffic at application level

Secrets

data EarlySecretInfo Source #

Handshake information generated for traffic at 0-RTT level.

Instances

Instances details
Show EarlySecretInfo Source # 
Instance details

Defined in Network.TLS.Handshake.Control

data HandshakeSecretInfo Source #

Handshake information generated for traffic at handshake level.

newtype ApplicationSecretInfo Source #

Handshake information generated for traffic at application level.

data EarlySecret Source #

Phantom type indicating early traffic secret.

data HandshakeSecret Source #

Phantom type indicating handshake traffic secrets.

data ApplicationSecret Source #

Phantom type indicating application traffic secrets.

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

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

newtype ServerTrafficSecret a Source #

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

Instances

Instances details
Show (ServerTrafficSecret a) Source # 
Instance details

Defined in Network.TLS.Types

newtype ClientTrafficSecret a Source #

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

Instances

Instances details
Show (ClientTrafficSecret a) Source # 
Instance details

Defined in Network.TLS.Types

Negotiated parameters

type NegotiatedProtocol = ByteString Source #

ID of the application-level protocol negotiated between client and server. See values listed in the IANA registry.

data HandshakeMode13 Source #

Type to show which handshake mode is used in TLS 1.3.

Constructors

FullHandshake

Full handshake is used.

HelloRetryRequest

Full handshake is used with hello retry request.

PreSharedKey

Server authentication is skipped.

RTT0

Server authentication is skipped and early data is sent.

Extensions

data ExtensionRaw Source #

The raw content of a TLS extension.

Instances

Instances details
Eq ExtensionRaw Source # 
Instance details

Defined in Network.TLS.Struct

Show ExtensionRaw Source # 
Instance details

Defined in Network.TLS.Struct

type ExtensionID = Word16 Source #

Identifier of a TLS extension.

Errors

errorTLS :: String -> IO a Source #

Can be used by callbacks to signal an unexpected condition. This will then generate an "internal_error" alert in the TLS stack.

errorToAlertDescription :: TLSError -> AlertDescription Source #

Return the alert that a TLS endpoint would send to the peer for the specified library error.

errorToAlertMessage :: TLSError -> String Source #

Return the message that a TLS endpoint can add to its local log for the specified library error.

fromAlertDescription :: AlertDescription -> Word8 Source #

Encode an alert to the assigned value.

toAlertDescription :: Word8 -> Maybe AlertDescription Source #

Decode an alert from the assigned value.

Hash

hkdfExpandLabel :: Hash -> ByteString -> ByteString -> ByteString -> Int -> ByteString Source #

HKDF-Expand-Label function. Returns output keying material of the specified length from the PRK, customized for a TLS label and context.

hkdfExtract :: Hash -> ByteString -> ByteString -> ByteString Source #

HKDF-Extract function. Returns the pseudorandom key (PRK) from salt and input keying material (IKM).

hashDigestSize :: Hash -> Int Source #

Digest size in bytes.

Constants

quicMaxEarlyDataSize :: Int Source #

Max early data size for QUIC.

Supported