Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
API to run the TLS handshake establishing a QUIC connection.
On the northbound API:
- QUIC starts a TLS client or server thread with
tlsQUICClient
ortlsQUICServer
.
TLS invokes QUIC callbacks to use the QUIC transport
- TLS uses
quicSend
andquicRecv
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
- tlsQUICClient :: ClientParams -> QUICCallbacks -> IO ()
- tlsQUICServer :: ServerParams -> QUICCallbacks -> IO ()
- data QUICCallbacks = QUICCallbacks {
- quicSend :: [(CryptLevel, ByteString)] -> IO ()
- quicRecv :: CryptLevel -> IO (Either TLSError ByteString)
- quicInstallKeys :: Context -> KeyScheduleEvent -> IO ()
- quicNotifyExtensions :: Context -> [ExtensionRaw] -> IO ()
- quicDone :: Context -> IO ()
- data CryptLevel
- data KeyScheduleEvent
- data EarlySecretInfo = EarlySecretInfo Cipher (ClientTrafficSecret EarlySecret)
- data HandshakeSecretInfo = HandshakeSecretInfo Cipher (TrafficSecrets HandshakeSecret)
- newtype ApplicationSecretInfo = ApplicationSecretInfo (TrafficSecrets ApplicationSecret)
- data EarlySecret
- data HandshakeSecret
- data ApplicationSecret
- type TrafficSecrets a = (ClientTrafficSecret a, ServerTrafficSecret a)
- newtype ServerTrafficSecret a = ServerTrafficSecret ByteString
- newtype ClientTrafficSecret a = ClientTrafficSecret ByteString
- type NegotiatedProtocol = ByteString
- data HandshakeMode13
- data ExtensionRaw = ExtensionRaw ExtensionID ByteString
- newtype ExtensionID where
- errorTLS :: String -> IO a
- errorToAlertDescription :: TLSError -> AlertDescription
- errorToAlertMessage :: TLSError -> String
- fromAlertDescription :: AlertDescription -> Word8
- toAlertDescription :: Word8 -> AlertDescription
- hkdfExpandLabel :: Hash -> ByteString -> ByteString -> ByteString -> Int -> ByteString
- hkdfExtract :: Hash -> ByteString -> ByteString -> ByteString
- hashDigestSize :: Hash -> Int
- quicMaxEarlyDataSize :: Int
- defaultSupported :: Supported
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.
QUICCallbacks | |
|
data CryptLevel Source #
TLS encryption level.
CryptInitial | Unprotected traffic |
CryptMainSecret | Protected with main 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
Show CryptLevel Source # | |
Defined in Network.TLS.Record.State showsPrec :: Int -> CryptLevel -> ShowS # show :: CryptLevel -> String # showList :: [CryptLevel] -> ShowS # | |
Eq CryptLevel Source # | |
Defined in Network.TLS.Record.State (==) :: CryptLevel -> CryptLevel -> Bool # (/=) :: CryptLevel -> CryptLevel -> Bool # |
data KeyScheduleEvent Source #
Argument given to quicInstallKeys
when encryption material is available.
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
Show EarlySecretInfo Source # | |
Defined in Network.TLS.Handshake.Control showsPrec :: Int -> EarlySecretInfo -> ShowS # show :: EarlySecretInfo -> String # showList :: [EarlySecretInfo] -> ShowS # |
data HandshakeSecretInfo Source #
Handshake information generated for traffic at handshake level.
Instances
Show HandshakeSecretInfo Source # | |
Defined in Network.TLS.Handshake.Control showsPrec :: Int -> HandshakeSecretInfo -> ShowS # show :: HandshakeSecretInfo -> String # showList :: [HandshakeSecretInfo] -> ShowS # |
newtype ApplicationSecretInfo Source #
Handshake information generated for traffic at application level.
Instances
Show ApplicationSecretInfo Source # | |
Defined in Network.TLS.Handshake.Control showsPrec :: Int -> ApplicationSecretInfo -> ShowS # show :: ApplicationSecretInfo -> String # showList :: [ApplicationSecretInfo] -> ShowS # |
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
Show (ServerTrafficSecret a) Source # | |
Defined in Network.TLS.Types showsPrec :: Int -> ServerTrafficSecret a -> ShowS # show :: ServerTrafficSecret a -> String # showList :: [ServerTrafficSecret a] -> ShowS # |
newtype ClientTrafficSecret a Source #
A client traffic secret, typed with a parameter indicating a step in the TLS key schedule.
Instances
Show (ClientTrafficSecret a) Source # | |
Defined in Network.TLS.Types showsPrec :: Int -> ClientTrafficSecret a -> ShowS # show :: ClientTrafficSecret a -> String # showList :: [ClientTrafficSecret a] -> ShowS # |
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.
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. |
Instances
Show HandshakeMode13 Source # | |
Defined in Network.TLS.Handshake.State showsPrec :: Int -> HandshakeMode13 -> ShowS # show :: HandshakeMode13 -> String # showList :: [HandshakeMode13] -> ShowS # | |
Eq HandshakeMode13 Source # | |
Defined in Network.TLS.Handshake.State (==) :: HandshakeMode13 -> HandshakeMode13 -> Bool # (/=) :: HandshakeMode13 -> HandshakeMode13 -> Bool # |
Extensions
data ExtensionRaw Source #
The raw content of a TLS extension.
Instances
Show ExtensionRaw Source # | |
Defined in Network.TLS.Struct showsPrec :: Int -> ExtensionRaw -> ShowS # show :: ExtensionRaw -> String # showList :: [ExtensionRaw] -> ShowS # | |
Eq ExtensionRaw Source # | |
Defined in Network.TLS.Struct (==) :: ExtensionRaw -> ExtensionRaw -> Bool # (/=) :: ExtensionRaw -> ExtensionRaw -> Bool # |
newtype ExtensionID Source #
Identifier of a TLS extension. http://www.iana.org/assignments/tls-extensiontype-values/tls-extensiontype-values.txt
pattern EID_QuicTransportParameters :: ExtensionID |
Instances
Show ExtensionID Source # | |
Defined in Network.TLS.Struct showsPrec :: Int -> ExtensionID -> ShowS # show :: ExtensionID -> String # showList :: [ExtensionID] -> ShowS # | |
Eq ExtensionID Source # | |
Defined in Network.TLS.Struct (==) :: ExtensionID -> ExtensionID -> Bool # (/=) :: ExtensionID -> ExtensionID -> Bool # |
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.
toAlertDescription :: Word8 -> 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.