Safe Haskell | None |
---|---|
Language | GHC2021 |
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
- data ClientConfigBuilder = ClientConfigBuilder {}
- defaultClientConfigBuilder :: MonadIO m => m ClientConfigBuilder
- data ServerCertVerifier
- data ClientConfig
- clientConfigLogCallback :: ClientConfig -> Maybe LogCallback
- buildClientConfig :: MonadIO m => ClientConfigBuilder -> m ClientConfig
- newClientConnection :: Backend -> ClientConfig -> Text -> Acquire (Connection 'Client)
- data ServerConfigBuilder = ServerConfigBuilder {}
- defaultServerConfigBuilder :: MonadIO m => NonEmpty CertifiedKey -> m ServerConfigBuilder
- data ClientCertVerifier = ClientCertVerifier {}
- data ClientCertVerifierPolicy
- data ServerConfig
- serverConfigLogCallback :: ServerConfig -> Maybe LogCallback
- buildServerConfig :: MonadIO m => ServerConfigBuilder -> m ServerConfig
- newServerConnection :: Backend -> ServerConfig -> Acquire (Connection 'Server)
- data Connection (side :: Side)
- data Side
- readBS :: forall m (side :: Side). MonadIO m => Connection side -> Int -> m ByteString
- writeBS :: forall m (side :: Side). MonadIO m => Connection side -> ByteString -> m ()
- handshake :: forall m (side :: Side) a. MonadIO m => Connection side -> HandshakeQuery side a -> m a
- data HandshakeQuery (side :: Side) a
- getALPNProtocol :: forall (side :: Side). HandshakeQuery side (Maybe ALPNProtocol)
- getTLSVersion :: forall (side :: Side). HandshakeQuery side TLSVersion
- getNegotiatedCipherSuite :: forall (side :: Side). HandshakeQuery side NegotiatedCipherSuite
- getSNIHostname :: HandshakeQuery 'Server (Maybe Text)
- getPeerCertificate :: forall (side :: Side). CSize -> HandshakeQuery side (Maybe DERCertificate)
- sendCloseNotify :: forall m (side :: Side). MonadIO m => Connection side -> m ()
- data LogCallback
- newLogCallback :: (LogLevel -> Text -> IO ()) -> Acquire LogCallback
- data LogLevel
- readPtr :: forall m (side :: Side). MonadIO m => Connection side -> Ptr Word8 -> CSize -> m CSize
- writePtr :: forall m (side :: Side). MonadIO m => Connection side -> Ptr Word8 -> CSize -> m CSize
- version :: Text
- data Backend = Backend {}
- mkSocketBackend :: Socket -> Backend
- mkByteStringBackend :: (Int -> IO ByteString) -> (ByteString -> IO ()) -> Backend
- data CryptoProvider
- getDefaultCryptoProvider :: MonadIO m => m CryptoProvider
- setCryptoProviderCipherSuites :: MonadError RustlsException m => [CipherSuite] -> CryptoProvider -> m CryptoProvider
- cryptoProviderCipherSuites :: CryptoProvider -> [CipherSuite]
- cryptoProviderTLSVersions :: CryptoProvider -> [TLSVersion]
- newtype ALPNProtocol = ALPNProtocol {}
- data PEMCertificates
- data PEMCertificateParsing
- data CertifiedKey = CertifiedKey {}
- newtype DERCertificate = DERCertificate {}
- newtype CertificateRevocationList = CertificateRevocationList {}
- data TLSVersion where
- pattern TLS12 :: TLSVersion
- pattern TLS13 :: TLSVersion
- data CipherSuite = CipherSuite {}
- data NegotiatedCipherSuite = NegotiatedCipherSuite {}
- data RustlsException
- isCertError :: RustlsException -> Bool
- newtype RustlsLogException = RustlsLogException SomeException
Client
Builder
data ClientConfigBuilder Source #
Rustls client config builder.
Constructors
ClientConfigBuilder | |
Fields
|
Instances
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
Generic ServerCertVerifier Source # | |||||
Defined in Rustls.Internal Associated Types
Methods from :: ServerCertVerifier -> Rep ServerCertVerifier x # to :: Rep ServerCertVerifier x -> ServerCertVerifier # | |||||
Show ServerCertVerifier Source # | |||||
Defined in Rustls.Internal Methods showsPrec :: Int -> ServerCertVerifier -> ShowS # show :: ServerCertVerifier -> String # showList :: [ServerCertVerifier] -> ShowS # | |||||
type Rep ServerCertVerifier Source # | |||||
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 Connection
s.
Open a connection
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
Generic ServerConfigBuilder Source # | |||||
Defined in Rustls.Internal Associated Types
Methods from :: ServerConfigBuilder -> Rep ServerConfigBuilder x # to :: Rep ServerConfigBuilder x -> ServerConfigBuilder # | |||||
Show ServerConfigBuilder Source # | |||||
Defined in Rustls.Internal Methods showsPrec :: Int -> ServerConfigBuilder -> ShowS # show :: ServerConfigBuilder -> String # showList :: [ServerConfigBuilder] -> ShowS # | |||||
type Rep ServerConfigBuilder Source # | |||||
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)))))) |
defaultServerConfigBuilder :: MonadIO m => NonEmpty CertifiedKey -> m ServerConfigBuilder Source #
A ServerConfigBuilder
with good defaults.
data ClientCertVerifier Source #
How to verify TLS client certificates.
Constructors
ClientCertVerifier | |
Fields
|
Instances
Generic ClientCertVerifier Source # | |||||
Defined in Rustls.Internal Associated Types
Methods from :: ClientCertVerifier -> Rep ClientCertVerifier x # to :: Rep ClientCertVerifier x -> ClientCertVerifier # | |||||
Show ClientCertVerifier Source # | |||||
Defined in Rustls.Internal Methods showsPrec :: Int -> ClientCertVerifier -> ShowS # show :: ClientCertVerifier -> String # showList :: [ClientCertVerifier] -> ShowS # | |||||
type Rep ClientCertVerifier Source # | |||||
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
Bounded ClientCertVerifierPolicy Source # | |||||
Defined in Rustls.Internal | |||||
Enum ClientCertVerifierPolicy Source # | |||||
Defined in Rustls.Internal Methods succ :: ClientCertVerifierPolicy -> ClientCertVerifierPolicy # pred :: ClientCertVerifierPolicy -> ClientCertVerifierPolicy # toEnum :: Int -> ClientCertVerifierPolicy # fromEnum :: ClientCertVerifierPolicy -> Int # enumFrom :: ClientCertVerifierPolicy -> [ClientCertVerifierPolicy] # enumFromThen :: ClientCertVerifierPolicy -> ClientCertVerifierPolicy -> [ClientCertVerifierPolicy] # enumFromTo :: ClientCertVerifierPolicy -> ClientCertVerifierPolicy -> [ClientCertVerifierPolicy] # enumFromThenTo :: ClientCertVerifierPolicy -> ClientCertVerifierPolicy -> ClientCertVerifierPolicy -> [ClientCertVerifierPolicy] # | |||||
Generic ClientCertVerifierPolicy Source # | |||||
Defined in Rustls.Internal Associated Types
Methods from :: ClientCertVerifierPolicy -> Rep ClientCertVerifierPolicy x # to :: Rep ClientCertVerifierPolicy x -> ClientCertVerifierPolicy # | |||||
Show ClientCertVerifierPolicy Source # | |||||
Defined in Rustls.Internal Methods showsPrec :: Int -> ClientCertVerifierPolicy -> ShowS # show :: ClientCertVerifierPolicy -> String # showList :: [ClientCertVerifierPolicy] -> ShowS # | |||||
Eq ClientCertVerifierPolicy Source # | |||||
Defined in Rustls.Internal Methods (==) :: ClientCertVerifierPolicy -> ClientCertVerifierPolicy -> Bool # (/=) :: ClientCertVerifierPolicy -> ClientCertVerifierPolicy -> Bool # | |||||
Ord ClientCertVerifierPolicy Source # | |||||
Defined in Rustls.Internal Methods compare :: ClientCertVerifierPolicy -> ClientCertVerifierPolicy -> Ordering # (<) :: ClientCertVerifierPolicy -> ClientCertVerifierPolicy -> Bool # (<=) :: ClientCertVerifierPolicy -> ClientCertVerifierPolicy -> Bool # (>) :: ClientCertVerifierPolicy -> ClientCertVerifierPolicy -> Bool # (>=) :: ClientCertVerifierPolicy -> ClientCertVerifierPolicy -> Bool # max :: ClientCertVerifierPolicy -> ClientCertVerifierPolicy -> ClientCertVerifierPolicy # min :: ClientCertVerifierPolicy -> ClientCertVerifierPolicy -> ClientCertVerifierPolicy # | |||||
type Rep ClientCertVerifierPolicy Source # | |||||
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 Connection
s.
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.
Type-level indicator whether a Connection
is client- or server-side.
Read and write
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 #
Instances
Applicative (HandshakeQuery side) Source # | |
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 # | |
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 # | |
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 Connection
s which you
configured to use it.
Rustls log level.
Constructors
LogLevelError | |
LogLevelWarn | |
LogLevelInfo | |
LogLevelDebug | |
LogLevelTrace |
Instances
Bounded LogLevel Source # | |||||
Enum LogLevel Source # | |||||
Generic LogLevel Source # | |||||
Defined in Rustls.Internal Associated Types
| |||||
Show LogLevel Source # | |||||
Eq LogLevel Source # | |||||
Ord LogLevel Source # | |||||
Defined in Rustls.Internal | |||||
type Rep LogLevel Source # | |||||
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
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
Underlying data source for Rustls.
mkSocketBackend :: Socket -> Backend Source #
Arguments
:: (Int -> IO ByteString) | Read a This will silently truncate |
-> (ByteString -> IO ()) | Write a |
-> 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
Show CryptoProvider Source # | |
Defined in Rustls.Internal Methods showsPrec :: Int -> CryptoProvider -> ShowS # show :: CryptoProvider -> String # showList :: [CryptoProvider] -> ShowS # |
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 |
-> 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 #
An ALPN protocol ID. See https://www.iana.org/assignments/tls-extensiontype-values/tls-extensiontype-values.xhtml#alpn-protocol-ids for a list of registered IDs.
Constructors
ALPNProtocol | |
Fields |
Instances
Generic ALPNProtocol Source # | |||||
Defined in Rustls.Internal Associated Types
| |||||
Show ALPNProtocol Source # | |||||
Defined in Rustls.Internal Methods showsPrec :: Int -> ALPNProtocol -> ShowS # show :: ALPNProtocol -> String # showList :: [ALPNProtocol] -> ShowS # | |||||
Eq ALPNProtocol Source # | |||||
Defined in Rustls.Internal | |||||
Ord ALPNProtocol Source # | |||||
Defined in Rustls.Internal Methods compare :: ALPNProtocol -> ALPNProtocol -> Ordering # (<) :: ALPNProtocol -> ALPNProtocol -> Bool # (<=) :: ALPNProtocol -> ALPNProtocol -> Bool # (>) :: ALPNProtocol -> ALPNProtocol -> Bool # (>=) :: ALPNProtocol -> ALPNProtocol -> Bool # max :: ALPNProtocol -> ALPNProtocol -> ALPNProtocol # min :: ALPNProtocol -> ALPNProtocol -> ALPNProtocol # | |||||
type Rep ALPNProtocol Source # | |||||
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
Generic PEMCertificates Source # | |||||
Defined in Rustls.Internal Associated Types
Methods from :: PEMCertificates -> Rep PEMCertificates x # to :: Rep PEMCertificates x -> PEMCertificates # | |||||
Show PEMCertificates Source # | |||||
Defined in Rustls.Internal Methods showsPrec :: Int -> PEMCertificates -> ShowS # show :: PEMCertificates -> String # showList :: [PEMCertificates] -> ShowS # | |||||
type Rep PEMCertificates Source # | |||||
Defined in Rustls.Internal type Rep PEMCertificates = D1 ('MetaData "PEMCertificates" "Rustls.Internal" "rustls-0.2.0.0-inplace" 'False) (C1 ('MetaCons "PEMCertificatesInMemory" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 ByteString) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 PEMCertificateParsing)) :+: C1 ('MetaCons "PemCertificatesFromFile" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 FilePath) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 PEMCertificateParsing))) |
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
Bounded PEMCertificateParsing Source # | |||||
Defined in Rustls.Internal | |||||
Enum PEMCertificateParsing Source # | |||||
Defined in Rustls.Internal Methods succ :: PEMCertificateParsing -> PEMCertificateParsing # pred :: PEMCertificateParsing -> PEMCertificateParsing # toEnum :: Int -> PEMCertificateParsing # fromEnum :: PEMCertificateParsing -> Int # enumFrom :: PEMCertificateParsing -> [PEMCertificateParsing] # enumFromThen :: PEMCertificateParsing -> PEMCertificateParsing -> [PEMCertificateParsing] # enumFromTo :: PEMCertificateParsing -> PEMCertificateParsing -> [PEMCertificateParsing] # enumFromThenTo :: PEMCertificateParsing -> PEMCertificateParsing -> PEMCertificateParsing -> [PEMCertificateParsing] # | |||||
Generic PEMCertificateParsing Source # | |||||
Defined in Rustls.Internal Associated Types
Methods from :: PEMCertificateParsing -> Rep PEMCertificateParsing x # to :: Rep PEMCertificateParsing x -> PEMCertificateParsing # | |||||
Show PEMCertificateParsing Source # | |||||
Defined in Rustls.Internal Methods showsPrec :: Int -> PEMCertificateParsing -> ShowS # show :: PEMCertificateParsing -> String # showList :: [PEMCertificateParsing] -> ShowS # | |||||
Eq PEMCertificateParsing Source # | |||||
Defined in Rustls.Internal Methods (==) :: PEMCertificateParsing -> PEMCertificateParsing -> Bool # (/=) :: PEMCertificateParsing -> PEMCertificateParsing -> Bool # | |||||
Ord PEMCertificateParsing Source # | |||||
Defined in Rustls.Internal Methods compare :: PEMCertificateParsing -> PEMCertificateParsing -> Ordering # (<) :: PEMCertificateParsing -> PEMCertificateParsing -> Bool # (<=) :: PEMCertificateParsing -> PEMCertificateParsing -> Bool # (>) :: PEMCertificateParsing -> PEMCertificateParsing -> Bool # (>=) :: PEMCertificateParsing -> PEMCertificateParsing -> Bool # max :: PEMCertificateParsing -> PEMCertificateParsing -> PEMCertificateParsing # min :: PEMCertificateParsing -> PEMCertificateParsing -> PEMCertificateParsing # | |||||
type Rep PEMCertificateParsing Source # | |||||
Defined in Rustls.Internal |
data CertifiedKey Source #
A complete chain of certificates plus a private key for the leaf certificate.
Constructors
CertifiedKey | |
Fields
|
Instances
Generic CertifiedKey Source # | |||||
Defined in Rustls.Internal Associated Types
| |||||
Show CertifiedKey Source # | |||||
Defined in Rustls.Internal Methods showsPrec :: Int -> CertifiedKey -> ShowS # show :: CertifiedKey -> String # showList :: [CertifiedKey] -> ShowS # | |||||
type Rep CertifiedKey Source # | |||||
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.
Constructors
DERCertificate | |
Fields |
Instances
Generic DERCertificate Source # | |||||
Defined in Rustls Associated Types
Methods from :: DERCertificate -> Rep DERCertificate x # to :: Rep DERCertificate x -> DERCertificate # | |||||
Show DERCertificate Source # | |||||
Defined in Rustls Methods showsPrec :: Int -> DERCertificate -> ShowS # show :: DERCertificate -> String # showList :: [DERCertificate] -> ShowS # | |||||
Eq DERCertificate Source # | |||||
Defined in Rustls Methods (==) :: DERCertificate -> DERCertificate -> Bool # (/=) :: DERCertificate -> DERCertificate -> Bool # | |||||
Ord DERCertificate Source # | |||||
Defined in Rustls Methods compare :: DERCertificate -> DERCertificate -> Ordering # (<) :: DERCertificate -> DERCertificate -> Bool # (<=) :: DERCertificate -> DERCertificate -> Bool # (>) :: DERCertificate -> DERCertificate -> Bool # (>=) :: DERCertificate -> DERCertificate -> Bool # max :: DERCertificate -> DERCertificate -> DERCertificate # min :: DERCertificate -> DERCertificate -> DERCertificate # | |||||
type Rep DERCertificate Source # | |||||
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).
Constructors
CertificateRevocationList | |
Fields |
Instances
Generic CertificateRevocationList Source # | |||||
Defined in Rustls.Internal Associated Types
Methods from :: CertificateRevocationList -> Rep CertificateRevocationList x # to :: Rep CertificateRevocationList x -> CertificateRevocationList # | |||||
Show CertificateRevocationList Source # | |||||
Defined in Rustls.Internal Methods showsPrec :: Int -> CertificateRevocationList -> ShowS # show :: CertificateRevocationList -> String # showList :: [CertificateRevocationList] -> ShowS # | |||||
type Rep CertificateRevocationList Source # | |||||
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 |
Instances
Storable TLSVersion Source # | |
Defined in Rustls.Internal.FFI Methods sizeOf :: TLSVersion -> Int # alignment :: TLSVersion -> Int # peekElemOff :: Ptr TLSVersion -> Int -> IO TLSVersion # pokeElemOff :: Ptr TLSVersion -> Int -> TLSVersion -> IO () # peekByteOff :: Ptr b -> Int -> IO TLSVersion # pokeByteOff :: Ptr b -> Int -> TLSVersion -> IO () # peek :: Ptr TLSVersion -> IO TLSVersion # poke :: Ptr TLSVersion -> TLSVersion -> IO () # | |
Show TLSVersion Source # | |
Defined in Rustls.Internal.FFI Methods showsPrec :: Int -> TLSVersion -> ShowS # show :: TLSVersion -> String # showList :: [TLSVersion] -> ShowS # | |
Eq TLSVersion Source # | |
Defined in Rustls.Internal.FFI | |
Ord TLSVersion Source # | |
Defined in Rustls.Internal.FFI Methods compare :: TLSVersion -> TLSVersion -> Ordering # (<) :: TLSVersion -> TLSVersion -> Bool # (<=) :: TLSVersion -> TLSVersion -> Bool # (>) :: TLSVersion -> TLSVersion -> Bool # (>=) :: TLSVersion -> TLSVersion -> Bool # max :: TLSVersion -> TLSVersion -> TLSVersion # min :: TLSVersion -> TLSVersion -> TLSVersion # |
data CipherSuite Source #
A TLS cipher suite supported by a Rustls cryptography provider.
Constructors
CipherSuite | |
Fields
|
Instances
Generic CipherSuite Source # | |||||
Defined in Rustls.Internal Associated Types
| |||||
Show CipherSuite Source # | |||||
Defined in Rustls.Internal Methods showsPrec :: Int -> CipherSuite -> ShowS # show :: CipherSuite -> String # showList :: [CipherSuite] -> ShowS # | |||||
Eq CipherSuite Source # | |||||
Defined in Rustls.Internal | |||||
Ord CipherSuite Source # | |||||
Defined in Rustls.Internal Methods compare :: CipherSuite -> CipherSuite -> Ordering # (<) :: CipherSuite -> CipherSuite -> Bool # (<=) :: CipherSuite -> CipherSuite -> Bool # (>) :: CipherSuite -> CipherSuite -> Bool # (>=) :: CipherSuite -> CipherSuite -> Bool # max :: CipherSuite -> CipherSuite -> CipherSuite # min :: CipherSuite -> CipherSuite -> CipherSuite # | |||||
type Rep CipherSuite Source # | |||||
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
Generic NegotiatedCipherSuite Source # | |||||
Defined in Rustls.Internal Associated Types
Methods from :: NegotiatedCipherSuite -> Rep NegotiatedCipherSuite x # to :: Rep NegotiatedCipherSuite x -> NegotiatedCipherSuite # | |||||
Show NegotiatedCipherSuite Source # | |||||
Defined in Rustls.Internal Methods showsPrec :: Int -> NegotiatedCipherSuite -> ShowS # show :: NegotiatedCipherSuite -> String # showList :: [NegotiatedCipherSuite] -> ShowS # | |||||
Eq NegotiatedCipherSuite Source # | |||||
Defined in Rustls.Internal Methods (==) :: NegotiatedCipherSuite -> NegotiatedCipherSuite -> Bool # (/=) :: NegotiatedCipherSuite -> NegotiatedCipherSuite -> Bool # | |||||
Ord NegotiatedCipherSuite Source # | |||||
Defined in Rustls.Internal Methods compare :: NegotiatedCipherSuite -> NegotiatedCipherSuite -> Ordering # (<) :: NegotiatedCipherSuite -> NegotiatedCipherSuite -> Bool # (<=) :: NegotiatedCipherSuite -> NegotiatedCipherSuite -> Bool # (>) :: NegotiatedCipherSuite -> NegotiatedCipherSuite -> Bool # (>=) :: NegotiatedCipherSuite -> NegotiatedCipherSuite -> Bool # max :: NegotiatedCipherSuite -> NegotiatedCipherSuite -> NegotiatedCipherSuite # min :: NegotiatedCipherSuite -> NegotiatedCipherSuite -> NegotiatedCipherSuite # | |||||
type Rep NegotiatedCipherSuite Source # | |||||
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.
Instances
Exception RustlsException Source # | |
Defined in Rustls.Internal Methods toException :: RustlsException -> SomeException # fromException :: SomeException -> Maybe RustlsException # displayException :: RustlsException -> String # backtraceDesired :: RustlsException -> Bool # | |
Show RustlsException Source # | |
Defined in Rustls.Internal Methods showsPrec :: Int -> RustlsException -> ShowS # show :: RustlsException -> String # showList :: [RustlsException] -> ShowS # |
isCertError :: RustlsException -> Bool Source #
Checks if the given RustlsException
represents a certificate error.
newtype RustlsLogException Source #
Wrapper for exceptions thrown in a LogCallback
.
Constructors
RustlsLogException SomeException |
Instances
Exception RustlsLogException Source # | |
Defined in Rustls.Internal Methods toException :: RustlsLogException -> SomeException # fromException :: SomeException -> Maybe RustlsLogException # | |
Show RustlsLogException Source # | |
Defined in Rustls.Internal Methods showsPrec :: Int -> RustlsLogException -> ShowS # show :: RustlsLogException -> String # showList :: [RustlsLogException] -> ShowS # |