rustls-0.2.0.0: TLS bindings for Rustls
Safe HaskellNone
LanguageGHC2021

Rustls

Description

TLS bindings for Rustls via rustls-ffi.

See the README on GitHub for setup instructions.

Currently, most of the functionality exposed by rustls-ffi is available, while rustls-ffi is still missing some more niche Rustls features.

Also see http-client-rustls for making HTTPS requests using http-client and Rustls.

Client example

Suppose you have already opened a Socket to example.org, port 443 (see e.g. the examples at Network.Socket). This small example showcases how to perform a simple HTTP GET request:

>>> :set -XOverloadedStrings
>>> import qualified Rustls
>>> import Network.Socket (Socket)
>>> import Data.Acquire (withAcquire)
>>> :{
example :: Socket -> IO ()
example socket = do
  -- It is encouraged to share a single `clientConfig` when creating multiple
  -- TLS connections.
  clientConfig <-
    Rustls.buildClientConfig =<< Rustls.defaultClientConfigBuilder
  let backend = Rustls.mkSocketBackend socket
      newConnection =
        Rustls.newClientConnection backend clientConfig "example.org"
  withAcquire newConnection $ \conn -> do
    Rustls.writeBS conn "GET /"
    recv <- Rustls.readBS conn 1000 -- max number of bytes to read
    print recv
:}

Using Acquire

Some API functions (like newClientConnection and newServerConnection) return an Acquire from resourcet, as it is a convenient abstraction for exposing a value that should be consumed in a "bracketed" manner.

Usually, it can be used via with or withAcquire, or via allocateAcquire when a MonadResource constraint is available. If you really need the extra flexibility, you can also access separate open… and close… functions by reaching for Data.Acquire.Internal.

Synopsis

Client

Builder

data ClientConfigBuilder Source #

Rustls client config builder.

Constructors

ClientConfigBuilder 

Fields

Instances

Instances details
Generic ClientConfigBuilder Source # 
Instance details

Defined in Rustls.Internal

Associated Types

type Rep ClientConfigBuilder 
Instance details

Defined in Rustls.Internal

type Rep ClientConfigBuilder = D1 ('MetaData "ClientConfigBuilder" "Rustls.Internal" "rustls-0.2.0.0-inplace" 'False) (C1 ('MetaCons "ClientConfigBuilder" 'PrefixI 'True) ((S1 ('MetaSel ('Just "clientConfigCryptoProvider") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 CryptoProvider) :*: S1 ('MetaSel ('Just "clientConfigServerCertVerifier") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 ServerCertVerifier)) :*: (S1 ('MetaSel ('Just "clientConfigALPNProtocols") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 [ALPNProtocol]) :*: (S1 ('MetaSel ('Just "clientConfigEnableSNI") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Bool) :*: S1 ('MetaSel ('Just "clientConfigCertifiedKeys") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 [CertifiedKey])))))
Show ClientConfigBuilder Source # 
Instance details

Defined in Rustls.Internal

type Rep ClientConfigBuilder Source # 
Instance details

Defined in Rustls.Internal

type Rep ClientConfigBuilder = D1 ('MetaData "ClientConfigBuilder" "Rustls.Internal" "rustls-0.2.0.0-inplace" 'False) (C1 ('MetaCons "ClientConfigBuilder" 'PrefixI 'True) ((S1 ('MetaSel ('Just "clientConfigCryptoProvider") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 CryptoProvider) :*: S1 ('MetaSel ('Just "clientConfigServerCertVerifier") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 ServerCertVerifier)) :*: (S1 ('MetaSel ('Just "clientConfigALPNProtocols") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 [ALPNProtocol]) :*: (S1 ('MetaSel ('Just "clientConfigEnableSNI") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Bool) :*: S1 ('MetaSel ('Just "clientConfigCertifiedKeys") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 [CertifiedKey])))))

defaultClientConfigBuilder :: MonadIO m => m ClientConfigBuilder Source #

A ClientConfigBuilder with good defaults, using the OS certificate store.

data ServerCertVerifier Source #

How to verify TLS server certificates.

Constructors

PlatformServerCertVerifier

Verify the validity of TLS certificates based on the operating system's certificate facilities, using rustls-platform-verifier.

ServerCertVerifier 

Fields

Instances

Instances details
Generic ServerCertVerifier Source # 
Instance details

Defined in Rustls.Internal

Associated Types

type Rep ServerCertVerifier 
Instance details

Defined in Rustls.Internal

type Rep ServerCertVerifier = D1 ('MetaData "ServerCertVerifier" "Rustls.Internal" "rustls-0.2.0.0-inplace" 'False) (C1 ('MetaCons "PlatformServerCertVerifier" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ServerCertVerifier" 'PrefixI 'True) (S1 ('MetaSel ('Just "serverCertVerifierCertificates") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (NonEmpty PEMCertificates)) :*: S1 ('MetaSel ('Just "serverCertVerifierCRLs") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 [CertificateRevocationList])))
Show ServerCertVerifier Source # 
Instance details

Defined in Rustls.Internal

type Rep ServerCertVerifier Source # 
Instance details

Defined in Rustls.Internal

type Rep ServerCertVerifier = D1 ('MetaData "ServerCertVerifier" "Rustls.Internal" "rustls-0.2.0.0-inplace" 'False) (C1 ('MetaCons "PlatformServerCertVerifier" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ServerCertVerifier" 'PrefixI 'True) (S1 ('MetaSel ('Just "serverCertVerifierCertificates") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (NonEmpty PEMCertificates)) :*: S1 ('MetaSel ('Just "serverCertVerifierCRLs") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 [CertificateRevocationList])))

Config

data ClientConfig Source #

Assembled configuration for a Rustls client connection.

clientConfigLogCallback :: ClientConfig -> Maybe LogCallback Source #

A logging callback.

Note that this is a record selector, so you can use it as a setter:

>>> :{
setLogCallback :: LogCallback -> ClientConfig -> ClientConfig
setLogCallback logCallback clientConfig =
  clientConfig { clientConfigLogCallback = Just logCallback }
:}

buildClientConfig :: MonadIO m => ClientConfigBuilder -> m ClientConfig Source #

Build a ClientConfigBuilder into a ClientConfig.

This is a relatively expensive operation, so it is a good idea to share one ClientConfig when creating multiple Connections.

Open a connection

newClientConnection Source #

Arguments

:: Backend 
-> ClientConfig 
-> Text

Hostname.

-> Acquire (Connection 'Client) 

Initialize a TLS connection as a client.

Server

Builder

data ServerConfigBuilder Source #

Rustls client config builder.

Constructors

ServerConfigBuilder 

Fields

Instances

Instances details
Generic ServerConfigBuilder Source # 
Instance details

Defined in Rustls.Internal

Associated Types

type Rep ServerConfigBuilder 
Instance details

Defined in Rustls.Internal

type Rep ServerConfigBuilder = D1 ('MetaData "ServerConfigBuilder" "Rustls.Internal" "rustls-0.2.0.0-inplace" 'False) (C1 ('MetaCons "ServerConfigBuilder" 'PrefixI 'True) ((S1 ('MetaSel ('Just "serverConfigCryptoProvider") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 CryptoProvider) :*: S1 ('MetaSel ('Just "serverConfigCertifiedKeys") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (NonEmpty CertifiedKey))) :*: (S1 ('MetaSel ('Just "serverConfigALPNProtocols") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 [ALPNProtocol]) :*: (S1 ('MetaSel ('Just "serverConfigIgnoreClientOrder") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Bool) :*: S1 ('MetaSel ('Just "serverConfigClientCertVerifier") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Maybe ClientCertVerifier))))))
Show ServerConfigBuilder Source # 
Instance details

Defined in Rustls.Internal

type Rep ServerConfigBuilder Source # 
Instance details

Defined in Rustls.Internal

type Rep ServerConfigBuilder = D1 ('MetaData "ServerConfigBuilder" "Rustls.Internal" "rustls-0.2.0.0-inplace" 'False) (C1 ('MetaCons "ServerConfigBuilder" 'PrefixI 'True) ((S1 ('MetaSel ('Just "serverConfigCryptoProvider") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 CryptoProvider) :*: S1 ('MetaSel ('Just "serverConfigCertifiedKeys") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (NonEmpty CertifiedKey))) :*: (S1 ('MetaSel ('Just "serverConfigALPNProtocols") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 [ALPNProtocol]) :*: (S1 ('MetaSel ('Just "serverConfigIgnoreClientOrder") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Bool) :*: S1 ('MetaSel ('Just "serverConfigClientCertVerifier") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Maybe ClientCertVerifier))))))

data ClientCertVerifier Source #

How to verify TLS client certificates.

Constructors

ClientCertVerifier 

Fields

Instances

Instances details
Generic ClientCertVerifier Source # 
Instance details

Defined in Rustls.Internal

Associated Types

type Rep ClientCertVerifier 
Instance details

Defined in Rustls.Internal

type Rep ClientCertVerifier = D1 ('MetaData "ClientCertVerifier" "Rustls.Internal" "rustls-0.2.0.0-inplace" 'False) (C1 ('MetaCons "ClientCertVerifier" 'PrefixI 'True) (S1 ('MetaSel ('Just "clientCertVerifierPolicy") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 ClientCertVerifierPolicy) :*: (S1 ('MetaSel ('Just "clientCertVerifierCertificates") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (NonEmpty PEMCertificates)) :*: S1 ('MetaSel ('Just "clientCertVerifierCRLs") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 [CertificateRevocationList]))))
Show ClientCertVerifier Source # 
Instance details

Defined in Rustls.Internal

type Rep ClientCertVerifier Source # 
Instance details

Defined in Rustls.Internal

type Rep ClientCertVerifier = D1 ('MetaData "ClientCertVerifier" "Rustls.Internal" "rustls-0.2.0.0-inplace" 'False) (C1 ('MetaCons "ClientCertVerifier" 'PrefixI 'True) (S1 ('MetaSel ('Just "clientCertVerifierPolicy") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 ClientCertVerifierPolicy) :*: (S1 ('MetaSel ('Just "clientCertVerifierCertificates") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (NonEmpty PEMCertificates)) :*: S1 ('MetaSel ('Just "clientCertVerifierCRLs") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 [CertificateRevocationList]))))

data ClientCertVerifierPolicy Source #

Which client connections are allowed by a ClientCertVerifier.

Constructors

AllowAnyAuthenticatedClient

Allow any authenticated client (i.e. offering a trusted certificate), and reject clients offering none.

AllowAnyAnonymousOrAuthenticatedClient

Allow any authenticated client (i.e. offering a trusted certificate), but also allow clients offering none.

Instances

Instances details
Bounded ClientCertVerifierPolicy Source # 
Instance details

Defined in Rustls.Internal

Enum ClientCertVerifierPolicy Source # 
Instance details

Defined in Rustls.Internal

Generic ClientCertVerifierPolicy Source # 
Instance details

Defined in Rustls.Internal

Associated Types

type Rep ClientCertVerifierPolicy 
Instance details

Defined in Rustls.Internal

type Rep ClientCertVerifierPolicy = D1 ('MetaData "ClientCertVerifierPolicy" "Rustls.Internal" "rustls-0.2.0.0-inplace" 'False) (C1 ('MetaCons "AllowAnyAuthenticatedClient" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "AllowAnyAnonymousOrAuthenticatedClient" 'PrefixI 'False) (U1 :: Type -> Type))
Show ClientCertVerifierPolicy Source # 
Instance details

Defined in Rustls.Internal

Eq ClientCertVerifierPolicy Source # 
Instance details

Defined in Rustls.Internal

Ord ClientCertVerifierPolicy Source # 
Instance details

Defined in Rustls.Internal

type Rep ClientCertVerifierPolicy Source # 
Instance details

Defined in Rustls.Internal

type Rep ClientCertVerifierPolicy = D1 ('MetaData "ClientCertVerifierPolicy" "Rustls.Internal" "rustls-0.2.0.0-inplace" 'False) (C1 ('MetaCons "AllowAnyAuthenticatedClient" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "AllowAnyAnonymousOrAuthenticatedClient" 'PrefixI 'False) (U1 :: Type -> Type))

Config

data ServerConfig Source #

Assembled configuration for a Rustls server connection.

serverConfigLogCallback :: ServerConfig -> Maybe LogCallback Source #

A logging callback.

Note that this is a record selector, so you can use it as a setter:

>>> :{
setLogCallback :: LogCallback -> ServerConfig -> ServerConfig
setLogCallback logCallback serverConfig =
  serverConfig { serverConfigLogCallback = Just logCallback }
:}

buildServerConfig :: MonadIO m => ServerConfigBuilder -> m ServerConfig Source #

Build a ServerConfigBuilder into a ServerConfig.

This is a relatively expensive operation, so it is a good idea to share one ServerConfig when creating multiple Connections.

Open a connection

newServerConnection :: Backend -> ServerConfig -> Acquire (Connection 'Server) Source #

Initialize a TLS connection as a server.

Connection

data Connection (side :: Side) Source #

A Rustls connection.

data Side Source #

Type-level indicator whether a Connection is client- or server-side.

Constructors

Client 
Server 

Read and write

readBS Source #

Arguments

:: forall m (side :: Side). MonadIO m 
=> Connection side 
-> Int

Maximum result length. Note that a buffer of this size will be allocated.

-> m ByteString 

Read data from the Rustls Connection into a ByteString. The result will not be longer than the given length.

writeBS :: forall m (side :: Side). MonadIO m => Connection side -> ByteString -> m () Source #

Write a ByteString to the Rustls Connection.

Handshaking

handshake :: forall m (side :: Side) a. MonadIO m => Connection side -> HandshakeQuery side a -> m a Source #

Ensure that the connection is handshaked. It is only necessary to call this if you want to obtain connection information. You can do so by providing a HandshakeQuery.

>>> :{
getALPNAndTLSVersion ::
  MonadIO m =>
  Connection side ->
  m (Maybe ALPNProtocol, TLSVersion)
getALPNAndTLSVersion conn =
  handshake conn $ (,) <$> getALPNProtocol <*> getTLSVersion
:}

data HandshakeQuery (side :: Side) a Source #

A Monad to get TLS connection information via handshake.

Instances

Instances details
Applicative (HandshakeQuery side) Source # 
Instance details

Defined in Rustls.Internal

Methods

pure :: a -> HandshakeQuery side a #

(<*>) :: HandshakeQuery side (a -> b) -> HandshakeQuery side a -> HandshakeQuery side b #

liftA2 :: (a -> b -> c) -> HandshakeQuery side a -> HandshakeQuery side b -> HandshakeQuery side c #

(*>) :: HandshakeQuery side a -> HandshakeQuery side b -> HandshakeQuery side b #

(<*) :: HandshakeQuery side a -> HandshakeQuery side b -> HandshakeQuery side a #

Functor (HandshakeQuery side) Source # 
Instance details

Defined in Rustls.Internal

Methods

fmap :: (a -> b) -> HandshakeQuery side a -> HandshakeQuery side b #

(<$) :: a -> HandshakeQuery side b -> HandshakeQuery side a #

Monad (HandshakeQuery side) Source # 
Instance details

Defined in Rustls.Internal

Methods

(>>=) :: HandshakeQuery side a -> (a -> HandshakeQuery side b) -> HandshakeQuery side b #

(>>) :: HandshakeQuery side a -> HandshakeQuery side b -> HandshakeQuery side b #

return :: a -> HandshakeQuery side a #

getALPNProtocol :: forall (side :: Side). HandshakeQuery side (Maybe ALPNProtocol) Source #

Get the negotiated ALPN protocol, if any.

getTLSVersion :: forall (side :: Side). HandshakeQuery side TLSVersion Source #

Get the negotiated TLS protocol version.

getNegotiatedCipherSuite :: forall (side :: Side). HandshakeQuery side NegotiatedCipherSuite Source #

Get the negotiated cipher suite.

getSNIHostname :: HandshakeQuery 'Server (Maybe Text) Source #

Get the SNI hostname set by the client, if any.

getPeerCertificate :: forall (side :: Side). CSize -> HandshakeQuery side (Maybe DERCertificate) Source #

Get the i-th certificate provided by the peer.

Index 0 is the end entity certificate. Higher indices are certificates in the chain. Requesting an index higher than what is available returns Nothing.

Closing

sendCloseNotify :: forall m (side :: Side). MonadIO m => Connection side -> m () Source #

Send a close_notify warning alert. This informs the peer that the connection is being closed.

Logging

data LogCallback Source #

A Rustls connection logging callback.

newLogCallback :: (LogLevel -> Text -> IO ()) -> Acquire LogCallback Source #

Allocate a new logging callback, taking a LogLevel and a message.

If it throws an exception, it will be wrapped in a RustlsLogException and passed to reportError.

🚫 Make sure that its lifetime encloses those of the Connections which you configured to use it.

data LogLevel Source #

Rustls log level.

Instances

Instances details
Bounded LogLevel Source # 
Instance details

Defined in Rustls.Internal

Enum LogLevel Source # 
Instance details

Defined in Rustls.Internal

Generic LogLevel Source # 
Instance details

Defined in Rustls.Internal

Associated Types

type Rep LogLevel 
Instance details

Defined in Rustls.Internal

type Rep LogLevel = D1 ('MetaData "LogLevel" "Rustls.Internal" "rustls-0.2.0.0-inplace" 'False) ((C1 ('MetaCons "LogLevelError" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "LogLevelWarn" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "LogLevelInfo" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "LogLevelDebug" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "LogLevelTrace" 'PrefixI 'False) (U1 :: Type -> Type))))

Methods

from :: LogLevel -> Rep LogLevel x #

to :: Rep LogLevel x -> LogLevel #

Show LogLevel Source # 
Instance details

Defined in Rustls.Internal

Eq LogLevel Source # 
Instance details

Defined in Rustls.Internal

Ord LogLevel Source # 
Instance details

Defined in Rustls.Internal

type Rep LogLevel Source # 
Instance details

Defined in Rustls.Internal

type Rep LogLevel = D1 ('MetaData "LogLevel" "Rustls.Internal" "rustls-0.2.0.0-inplace" 'False) ((C1 ('MetaCons "LogLevelError" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "LogLevelWarn" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "LogLevelInfo" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "LogLevelDebug" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "LogLevelTrace" 'PrefixI 'False) (U1 :: Type -> Type))))

Raw Ptr-based API

readPtr :: forall m (side :: Side). MonadIO m => Connection side -> Ptr Word8 -> CSize -> m CSize Source #

Read data from the Rustls Connection into the given buffer.

writePtr :: forall m (side :: Side). MonadIO m => Connection side -> Ptr Word8 -> CSize -> m CSize Source #

Write data to the Rustls Connection from the given buffer.

Misc

version :: Text Source #

Combined version string of Rustls and rustls-ffi, as well as the Rustls cryptography provider.

>>> version
"rustls-ffi/0.14.0/rustls/0.23.13/aws-lc-rs"

Backend

data Backend Source #

Underlying data source for Rustls.

Constructors

Backend 

Fields

mkByteStringBackend Source #

Arguments

:: (Int -> IO ByteString)

Read a ByteString with the given max length.

This will silently truncate ByteStrings which are too long.

-> (ByteString -> IO ())

Write a ByteString.

-> Backend 

An in-memory Backend.

Crypto provider

data CryptoProvider Source #

A cryptography provider for Rustls.

In particular, this contains the set of supported TLS cipher suites.

Instances

Instances details
Show CryptoProvider Source # 
Instance details

Defined in Rustls.Internal

getDefaultCryptoProvider :: MonadIO m => m CryptoProvider Source #

Get the process-wide default Rustls cryptography provider.

setCryptoProviderCipherSuites Source #

Arguments

:: MonadError RustlsException m 
=> [CipherSuite]

Must be a subset of cryptoProviderCipherSuites. Only the cipherSuiteID is used.

-> CryptoProvider 
-> m CryptoProvider 

Create a derived CryptoProvider by restricting the cipher suites to the ones in the given list.

cryptoProviderCipherSuites :: CryptoProvider -> [CipherSuite] Source #

Get the cipher suites supported by the given cryptography provider.

cryptoProviderTLSVersions :: CryptoProvider -> [TLSVersion] Source #

Get all TLS versions supported by at least one of the cipher suites supported by the given cryptography provider.

Types

newtype ALPNProtocol Source #

Constructors

ALPNProtocol 

Instances

Instances details
Generic ALPNProtocol Source # 
Instance details

Defined in Rustls.Internal

Associated Types

type Rep ALPNProtocol 
Instance details

Defined in Rustls.Internal

type Rep ALPNProtocol = D1 ('MetaData "ALPNProtocol" "Rustls.Internal" "rustls-0.2.0.0-inplace" 'True) (C1 ('MetaCons "ALPNProtocol" 'PrefixI 'True) (S1 ('MetaSel ('Just "unALPNProtocol") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ByteString)))
Show ALPNProtocol Source # 
Instance details

Defined in Rustls.Internal

Eq ALPNProtocol Source # 
Instance details

Defined in Rustls.Internal

Ord ALPNProtocol Source # 
Instance details

Defined in Rustls.Internal

type Rep ALPNProtocol Source # 
Instance details

Defined in Rustls.Internal

type Rep ALPNProtocol = D1 ('MetaData "ALPNProtocol" "Rustls.Internal" "rustls-0.2.0.0-inplace" 'True) (C1 ('MetaCons "ALPNProtocol" 'PrefixI 'True) (S1 ('MetaSel ('Just "unALPNProtocol") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ByteString)))

data PEMCertificates Source #

A source of PEM-encoded certificates.

Constructors

PEMCertificatesInMemory ByteString PEMCertificateParsing

In-memory PEM-encoded certificates.

PemCertificatesFromFile FilePath PEMCertificateParsing

Fetch PEM-encoded root certificates from a file.

Instances

Instances details
Generic PEMCertificates Source # 
Instance details

Defined in Rustls.Internal

Show PEMCertificates Source # 
Instance details

Defined in Rustls.Internal

type Rep PEMCertificates Source # 
Instance details

Defined in Rustls.Internal

data PEMCertificateParsing Source #

Parsing mode for PEM-encoded certificates.

Constructors

PEMCertificateParsingStrict

Fail if syntactically invalid.

PEMCertificateParsingLax

Ignore if syntactically invalid.

This may be useful on systems that have syntactically invalid root certificates.

Instances

Instances details
Bounded PEMCertificateParsing Source # 
Instance details

Defined in Rustls.Internal

Enum PEMCertificateParsing Source # 
Instance details

Defined in Rustls.Internal

Generic PEMCertificateParsing Source # 
Instance details

Defined in Rustls.Internal

Associated Types

type Rep PEMCertificateParsing 
Instance details

Defined in Rustls.Internal

type Rep PEMCertificateParsing = D1 ('MetaData "PEMCertificateParsing" "Rustls.Internal" "rustls-0.2.0.0-inplace" 'False) (C1 ('MetaCons "PEMCertificateParsingStrict" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "PEMCertificateParsingLax" 'PrefixI 'False) (U1 :: Type -> Type))
Show PEMCertificateParsing Source # 
Instance details

Defined in Rustls.Internal

Eq PEMCertificateParsing Source # 
Instance details

Defined in Rustls.Internal

Ord PEMCertificateParsing Source # 
Instance details

Defined in Rustls.Internal

type Rep PEMCertificateParsing Source # 
Instance details

Defined in Rustls.Internal

type Rep PEMCertificateParsing = D1 ('MetaData "PEMCertificateParsing" "Rustls.Internal" "rustls-0.2.0.0-inplace" 'False) (C1 ('MetaCons "PEMCertificateParsingStrict" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "PEMCertificateParsingLax" 'PrefixI 'False) (U1 :: Type -> Type))

data CertifiedKey Source #

A complete chain of certificates plus a private key for the leaf certificate.

Constructors

CertifiedKey 

Fields

Instances

Instances details
Generic CertifiedKey Source # 
Instance details

Defined in Rustls.Internal

Associated Types

type Rep CertifiedKey 
Instance details

Defined in Rustls.Internal

type Rep CertifiedKey = D1 ('MetaData "CertifiedKey" "Rustls.Internal" "rustls-0.2.0.0-inplace" 'False) (C1 ('MetaCons "CertifiedKey" 'PrefixI 'True) (S1 ('MetaSel ('Just "certificateChain") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 ByteString) :*: S1 ('MetaSel ('Just "privateKey") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 ByteString)))
Show CertifiedKey Source # 
Instance details

Defined in Rustls.Internal

type Rep CertifiedKey Source # 
Instance details

Defined in Rustls.Internal

type Rep CertifiedKey = D1 ('MetaData "CertifiedKey" "Rustls.Internal" "rustls-0.2.0.0-inplace" 'False) (C1 ('MetaCons "CertifiedKey" 'PrefixI 'True) (S1 ('MetaSel ('Just "certificateChain") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 ByteString) :*: S1 ('MetaSel ('Just "privateKey") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 ByteString)))

newtype DERCertificate Source #

A DER-encoded certificate.

Instances

Instances details
Generic DERCertificate Source # 
Instance details

Defined in Rustls

Associated Types

type Rep DERCertificate 
Instance details

Defined in Rustls

type Rep DERCertificate = D1 ('MetaData "DERCertificate" "Rustls" "rustls-0.2.0.0-inplace" 'True) (C1 ('MetaCons "DERCertificate" 'PrefixI 'True) (S1 ('MetaSel ('Just "unDERCertificate") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ByteString)))
Show DERCertificate Source # 
Instance details

Defined in Rustls

Eq DERCertificate Source # 
Instance details

Defined in Rustls

Ord DERCertificate Source # 
Instance details

Defined in Rustls

type Rep DERCertificate Source # 
Instance details

Defined in Rustls

type Rep DERCertificate = D1 ('MetaData "DERCertificate" "Rustls" "rustls-0.2.0.0-inplace" 'True) (C1 ('MetaCons "DERCertificate" 'PrefixI 'True) (S1 ('MetaSel ('Just "unDERCertificate") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ByteString)))

newtype CertificateRevocationList Source #

One or more PEM-encoded certificate revocation lists (CRL).

Instances

Instances details
Generic CertificateRevocationList Source # 
Instance details

Defined in Rustls.Internal

Associated Types

type Rep CertificateRevocationList 
Instance details

Defined in Rustls.Internal

type Rep CertificateRevocationList = D1 ('MetaData "CertificateRevocationList" "Rustls.Internal" "rustls-0.2.0.0-inplace" 'True) (C1 ('MetaCons "CertificateRevocationList" 'PrefixI 'True) (S1 ('MetaSel ('Just "unCertificateRevocationList") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ByteString)))
Show CertificateRevocationList Source # 
Instance details

Defined in Rustls.Internal

type Rep CertificateRevocationList Source # 
Instance details

Defined in Rustls.Internal

type Rep CertificateRevocationList = D1 ('MetaData "CertificateRevocationList" "Rustls.Internal" "rustls-0.2.0.0-inplace" 'True) (C1 ('MetaCons "CertificateRevocationList" 'PrefixI 'True) (S1 ('MetaSel ('Just "unCertificateRevocationList") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ByteString)))

data TLSVersion where Source #

A TLS protocol version supported by Rustls.

Bundled Patterns

pattern TLS12 :: TLSVersion 
pattern TLS13 :: TLSVersion 

data CipherSuite Source #

A TLS cipher suite supported by a Rustls cryptography provider.

Constructors

CipherSuite 

Fields

Instances

Instances details
Generic CipherSuite Source # 
Instance details

Defined in Rustls.Internal

Associated Types

type Rep CipherSuite 
Instance details

Defined in Rustls.Internal

type Rep CipherSuite = D1 ('MetaData "CipherSuite" "Rustls.Internal" "rustls-0.2.0.0-inplace" 'False) (C1 ('MetaCons "CipherSuite" 'PrefixI 'True) (S1 ('MetaSel ('Just "cipherSuiteID") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Word16) :*: (S1 ('MetaSel ('Just "cipherSuiteName") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Text) :*: S1 ('MetaSel ('Just "cipherSuiteTLSVersion") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 TLSVersion))))
Show CipherSuite Source # 
Instance details

Defined in Rustls.Internal

Eq CipherSuite Source # 
Instance details

Defined in Rustls.Internal

Ord CipherSuite Source # 
Instance details

Defined in Rustls.Internal

type Rep CipherSuite Source # 
Instance details

Defined in Rustls.Internal

type Rep CipherSuite = D1 ('MetaData "CipherSuite" "Rustls.Internal" "rustls-0.2.0.0-inplace" 'False) (C1 ('MetaCons "CipherSuite" 'PrefixI 'True) (S1 ('MetaSel ('Just "cipherSuiteID") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Word16) :*: (S1 ('MetaSel ('Just "cipherSuiteName") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Text) :*: S1 ('MetaSel ('Just "cipherSuiteTLSVersion") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 TLSVersion))))

data NegotiatedCipherSuite Source #

A negotiated TLS cipher suite. Subset of CipherSuite.

Constructors

NegotiatedCipherSuite 

Fields

Instances

Instances details
Generic NegotiatedCipherSuite Source # 
Instance details

Defined in Rustls.Internal

Associated Types

type Rep NegotiatedCipherSuite 
Instance details

Defined in Rustls.Internal

type Rep NegotiatedCipherSuite = D1 ('MetaData "NegotiatedCipherSuite" "Rustls.Internal" "rustls-0.2.0.0-inplace" 'False) (C1 ('MetaCons "NegotiatedCipherSuite" 'PrefixI 'True) (S1 ('MetaSel ('Just "negotiatedCipherSuiteID") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Word16) :*: S1 ('MetaSel ('Just "negotiatedCipherSuiteName") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Text)))
Show NegotiatedCipherSuite Source # 
Instance details

Defined in Rustls.Internal

Eq NegotiatedCipherSuite Source # 
Instance details

Defined in Rustls.Internal

Ord NegotiatedCipherSuite Source # 
Instance details

Defined in Rustls.Internal

type Rep NegotiatedCipherSuite Source # 
Instance details

Defined in Rustls.Internal

type Rep NegotiatedCipherSuite = D1 ('MetaData "NegotiatedCipherSuite" "Rustls.Internal" "rustls-0.2.0.0-inplace" 'False) (C1 ('MetaCons "NegotiatedCipherSuite" 'PrefixI 'True) (S1 ('MetaSel ('Just "negotiatedCipherSuiteID") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Word16) :*: S1 ('MetaSel ('Just "negotiatedCipherSuiteName") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Text)))

Exceptions

data RustlsException Source #

TLS exception thrown by Rustls.

Use displayException for a human-friendly representation.

isCertError :: RustlsException -> Bool Source #

Checks if the given RustlsException represents a certificate error.