rustls-0.0.1.0: TLS bindings for Rustls
Safe HaskellSafe-Inferred
LanguageHaskell2010

Rustls.Internal

Description

Internal module, not subject to PVP.

Synopsis

Documentation

newtype ALPNProtocol Source #

Constructors

ALPNProtocol 

Instances

Instances details
Generic ALPNProtocol Source # 
Instance details

Defined in Rustls.Internal

Associated Types

type Rep ALPNProtocol :: Type -> Type #

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.0.1.0-inplace" 'True) (C1 ('MetaCons "ALPNProtocol" 'PrefixI 'True) (S1 ('MetaSel ('Just "unALPNProtocol") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ByteString)))

newtype CipherSuite Source #

A TLS cipher suite supported by Rustls.

cipherSuiteID :: CipherSuite -> Word16 Source #

Get the IANA value from a cipher suite. The bytes are interpreted in network order.

See https://www.iana.org/assignments/tls-parameters/tls-parameters.xhtml#tls-parameters-4 for a list.

showCipherSuite :: CipherSuite -> Text Source #

Get the text representation of a cipher suite.

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 :: Type -> Type #

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.0.1.0-inplace" 'False) (C1 ('MetaCons "ClientConfigBuilder" 'PrefixI 'True) ((S1 ('MetaSel ('Just "clientConfigRoots") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 ClientRoots) :*: (S1 ('MetaSel ('Just "clientConfigTLSVersions") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 [TLSVersion]) :*: S1 ('MetaSel ('Just "clientConfigCipherSuites") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 [CipherSuite]))) :*: (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])))))

data ClientRoots Source #

How to look up root certificates.

Constructors

ClientRootsFromFile FilePath

Fetch PEM-encoded root certificates from a file.

ClientRootsInMemory [PEMCertificates]

Use in-memory PEM-encoded certificates.

Instances

Instances details
Generic ClientRoots Source # 
Instance details

Defined in Rustls.Internal

Associated Types

type Rep ClientRoots :: Type -> Type #

Show ClientRoots Source # 
Instance details

Defined in Rustls.Internal

type Rep ClientRoots Source # 
Instance details

Defined in Rustls.Internal

type Rep ClientRoots = D1 ('MetaData "ClientRoots" "Rustls.Internal" "rustls-0.0.1.0-inplace" 'False) (C1 ('MetaCons "ClientRootsFromFile" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 FilePath)) :+: C1 ('MetaCons "ClientRootsInMemory" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 [PEMCertificates])))

data PEMCertificates Source #

In-memory PEM-encoded certificates.

Constructors

PEMCertificatesStrict ByteString

Syntactically valid PEM-encoded certificates.

PEMCertificatesLax ByteString

PEM-encoded certificates, ignored if syntactically invalid.

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

Instances

Instances details
Generic PEMCertificates Source # 
Instance details

Defined in Rustls.Internal

Associated Types

type Rep PEMCertificates :: Type -> Type #

Show PEMCertificates Source # 
Instance details

Defined in Rustls.Internal

type Rep PEMCertificates Source # 
Instance details

Defined in Rustls.Internal

type Rep PEMCertificates = D1 ('MetaData "PEMCertificates" "Rustls.Internal" "rustls-0.0.1.0-inplace" 'False) (C1 ('MetaCons "PEMCertificatesStrict" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 ByteString)) :+: C1 ('MetaCons "PEMCertificatesLax" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 ByteString)))

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 :: Type -> Type #

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.0.1.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)))

data ClientConfig Source #

Assembled configuration for a Rustls client connection.

Constructors

ClientConfig 

Fields

data ClientCertVerifier Source #

How to verify TLS client certificates.

Constructors

ClientCertVerifier [PEMCertificates]

Root certificates used to verify TLS client certificates.

ClientCertVerifierOptional [PEMCertificates]

Root certificates used to verify TLS client certificates if present, but does not reject clients which provide no certificate.

Instances

Instances details
Generic ClientCertVerifier Source # 
Instance details

Defined in Rustls.Internal

Associated Types

type Rep ClientCertVerifier :: Type -> Type #

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.0.1.0-inplace" 'False) (C1 ('MetaCons "ClientCertVerifier" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 [PEMCertificates])) :+: C1 ('MetaCons "ClientCertVerifierOptional" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 [PEMCertificates])))

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 :: Type -> Type #

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.0.1.0-inplace" 'False) (C1 ('MetaCons "ServerConfigBuilder" 'PrefixI 'True) ((S1 ('MetaSel ('Just "serverConfigCertifiedKeys") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (NonEmpty CertifiedKey)) :*: (S1 ('MetaSel ('Just "serverConfigTLSVersions") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 [TLSVersion]) :*: S1 ('MetaSel ('Just "serverConfigCipherSuites") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 [CipherSuite]))) :*: (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 ServerConfig Source #

Assembled configuration for a Rustls server connection.

Constructors

ServerConfig 

Fields

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 :: 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.0.1.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))))

newtype LogCallback Source #

A Rustls connection logging callback.

newtype 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 #

newtype RustlsException Source #

TLS exception thrown by Rustls.

Use displayException for a human-friendly representation.

Constructors

RustlsException 

isCertError :: RustlsException -> Bool Source #

Checks if the given RustlsException represents a certificate error.

class Backend b where Source #

Underlying data sources for Rustls.

Methods

backendRead Source #

Arguments

:: b 
-> Ptr Word8

Target buffer pointer.

-> CSize

Target buffer length.

-> IO CSize

Amount of bytes read.

Read data from the backend into the given buffer.

backendWrite Source #

Arguments

:: b 
-> Ptr Word8

Source buffer pointer.

-> CSize

Source buffer length.

-> IO CSize

Amount of bytes written.

Write data from the given buffer to the backend.

Instances

Instances details
Backend Socket Source # 
Instance details

Defined in Rustls.Internal

Backend ByteStringBackend Source #

This instance will silently truncate ByteStrings which are too long.

Instance details

Defined in Rustls.Internal

data ByteStringBackend Source #

An in-memory Backend.

Constructors

ByteStringBackend 

Fields

Instances

Instances details
Generic ByteStringBackend Source # 
Instance details

Defined in Rustls.Internal

Associated Types

type Rep ByteStringBackend :: Type -> Type #

Backend ByteStringBackend Source #

This instance will silently truncate ByteStrings which are too long.

Instance details

Defined in Rustls.Internal

type Rep ByteStringBackend Source # 
Instance details

Defined in Rustls.Internal

type Rep ByteStringBackend = D1 ('MetaData "ByteStringBackend" "Rustls.Internal" "rustls-0.0.1.0-inplace" 'False) (C1 ('MetaCons "ByteStringBackend" 'PrefixI 'True) (S1 ('MetaSel ('Just "bsbRead") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Int -> IO ByteString)) :*: S1 ('MetaSel ('Just "bsbWrite") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (ByteString -> IO ()))))

data Side Source #

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

Constructors

Client 
Server 

newtype Connection (side :: Side) Source #

A Rustls connection.

Constructors

Connection (MVar Connection') 

data ReadOrWrite Source #

Constructors

Read 
Write 

data IOMsgReq Source #

Messages sent to the background thread.

Constructors

Request ReadOrWrite

Request to start a read or a write FFI call from the background thread. It should respond with UsingBuffer.

Done IOResult

Notify the background thread that we are done interacting with the buffer.

data IOMsgRes Source #

Messages sent from the background thread.

Constructors

UsingBuffer (Ptr Word8) CSize (Ptr CSize)

Reply with a buffer, either containing the read data, or awaiting a write to this buffer.

DoneFFI

Notify that the FFI call finished.

data RunTLSMode Source #

Constructors

TLSHandshake 
TLSRead 
TLSWrite 

Instances

Instances details
Eq RunTLSMode Source # 
Instance details

Defined in Rustls.Internal