#if DERIVE_STORABLE_PLUGIN
{-# OPTIONS_GHC -fplugin=Foreign.Storable.Generic.Plugin #-}
#endif
module Rustls.Internal.FFI
(
ClientConfig,
ClientConfigBuilder,
clientConfigBuilderNewCustom,
clientConfigBuilderFree,
clientConfigBuilderBuild,
clientConfigFree,
clientConfigBuilderSetALPNProtocols,
clientConfigBuilderSetEnableSNI,
clientConfigBuilderSetCertifiedKey,
clientConfigBuilderLoadRootsFromFile,
clientConfigBuilderUseRoots,
clientConnectionNew,
serverConnectionNew,
ServerConfig,
ServerConfigBuilder,
serverConfigBuilderNewCustom,
serverConfigBuilderFree,
serverConfigBuilderBuild,
serverConfigFree,
serverConfigBuilderSetALPNProtocols,
serverConfigBuilderSetIgnoreClientOrder,
serverConfigBuilderSetCertifiedKeys,
ClientCertVerifier,
clientCertVerifierNew,
clientCertVerifierFree,
serverConfigBuilderSetClientVerifier,
ClientCertVerifierOptional,
clientCertVerifierOptionalNew,
clientCertVerifierOptionalFree,
serverConfigBuilderSetClientVerifierOptional,
CertifiedKey,
certifiedKeyBuild,
certifiedKeyFree,
Certificate,
certificateGetDER,
Connection,
connectionFree,
ReadWriteCallback,
mkReadWriteCallback,
connectionWantsRead,
connectionRead,
connectionReadTls,
connectionWantsWrite,
connectionWrite,
connectionWriteTls,
connectionProcessNewPackets,
connectionIsHandshaking,
connectionSendCloseNotify,
connectionSetBufferLimit,
connectionGetALPNProtocol,
connectionGetProtocolVersion,
connectionGetNegotiatedCipherSuite,
serverConnectionGetSNIHostname,
connectionGetPeerCertificate,
connectionSetLogCallback,
LogCallback,
mkLogCallback,
LogParams (..),
LogLevel (..),
Str (..),
SliceBytes (..),
hsVersion,
Userdata,
Result (..),
resultIsCertError,
errorMsg,
resultOk,
resultInsufficientSize,
IOResult (..),
ioResultOk,
ioResultErr,
SupportedCipherSuite,
allCipherSuites,
allCipherSuitesLen,
defaultCipherSuites,
defaultCipherSuitesLen,
supportedCipherSuiteGetSuite,
hsSupportedCipherSuiteGetName,
TLSVersion (..),
pattern TLS12,
pattern TLS13,
allVersions,
allVersionsLen,
defaultVersions,
defaultVersionsLen,
RootCertStore,
rootCertStoreNew,
rootCertStoreAddPEM,
rootCertStoreFree,
)
where
import Data.Word
import Foreign
import Foreign.C
import Foreign.Storable.Generic
import GHC.Generics (Generic)
data {-# CTYPE "rustls.h" "rustls_str" #-} Str = Str CString CSize
deriving stock ((forall x. Str -> Rep Str x)
-> (forall x. Rep Str x -> Str) -> Generic Str
forall x. Rep Str x -> Str
forall x. Str -> Rep Str x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Str x -> Str
$cfrom :: forall x. Str -> Rep Str x
Generic)
deriving anyclass (Str -> Int
(Str -> Int)
-> (Str -> Int)
-> (forall b. Ptr b -> Int -> IO Str)
-> (forall b. Ptr b -> Int -> Str -> IO ())
-> GStorable Str
forall b. Ptr b -> Int -> IO Str
forall b. Ptr b -> Int -> Str -> IO ()
forall a.
(a -> Int)
-> (a -> Int)
-> (forall b. Ptr b -> Int -> IO a)
-> (forall b. Ptr b -> Int -> a -> IO ())
-> GStorable a
gpokeByteOff :: Ptr b -> Int -> Str -> IO ()
$cgpokeByteOff :: forall b. Ptr b -> Int -> Str -> IO ()
gpeekByteOff :: Ptr b -> Int -> IO Str
$cgpeekByteOff :: forall b. Ptr b -> Int -> IO Str
galignment :: Str -> Int
$cgalignment :: Str -> Int
gsizeOf :: Str -> Int
$cgsizeOf :: Str -> Int
GStorable)
data {-# CTYPE "rustls.h" "rustls_slice_bytes" #-} SliceBytes = SliceBytes (Ptr Word8) CSize
deriving stock ((forall x. SliceBytes -> Rep SliceBytes x)
-> (forall x. Rep SliceBytes x -> SliceBytes) -> Generic SliceBytes
forall x. Rep SliceBytes x -> SliceBytes
forall x. SliceBytes -> Rep SliceBytes x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep SliceBytes x -> SliceBytes
$cfrom :: forall x. SliceBytes -> Rep SliceBytes x
Generic)
deriving anyclass (SliceBytes -> Int
(SliceBytes -> Int)
-> (SliceBytes -> Int)
-> (forall b. Ptr b -> Int -> IO SliceBytes)
-> (forall b. Ptr b -> Int -> SliceBytes -> IO ())
-> GStorable SliceBytes
forall b. Ptr b -> Int -> IO SliceBytes
forall b. Ptr b -> Int -> SliceBytes -> IO ()
forall a.
(a -> Int)
-> (a -> Int)
-> (forall b. Ptr b -> Int -> IO a)
-> (forall b. Ptr b -> Int -> a -> IO ())
-> GStorable a
gpokeByteOff :: Ptr b -> Int -> SliceBytes -> IO ()
$cgpokeByteOff :: forall b. Ptr b -> Int -> SliceBytes -> IO ()
gpeekByteOff :: Ptr b -> Int -> IO SliceBytes
$cgpeekByteOff :: forall b. Ptr b -> Int -> IO SliceBytes
galignment :: SliceBytes -> Int
$cgalignment :: SliceBytes -> Int
gsizeOf :: SliceBytes -> Int
$cgsizeOf :: SliceBytes -> Int
GStorable)
foreign import capi unsafe "hs_rustls.h hs_rustls_version"
hsVersion :: Ptr Str -> IO ()
newtype {-# CTYPE "rustls.h" "rustls_result" #-} Result = Result Word32
deriving stock (Int -> Result -> ShowS
[Result] -> ShowS
Result -> String
(Int -> Result -> ShowS)
-> (Result -> String) -> ([Result] -> ShowS) -> Show Result
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Result] -> ShowS
$cshowList :: [Result] -> ShowS
show :: Result -> String
$cshow :: Result -> String
showsPrec :: Int -> Result -> ShowS
$cshowsPrec :: Int -> Result -> ShowS
Show, Result -> Result -> Bool
(Result -> Result -> Bool)
-> (Result -> Result -> Bool) -> Eq Result
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Result -> Result -> Bool
$c/= :: Result -> Result -> Bool
== :: Result -> Result -> Bool
$c== :: Result -> Result -> Bool
Eq, Eq Result
Eq Result
-> (Result -> Result -> Ordering)
-> (Result -> Result -> Bool)
-> (Result -> Result -> Bool)
-> (Result -> Result -> Bool)
-> (Result -> Result -> Bool)
-> (Result -> Result -> Result)
-> (Result -> Result -> Result)
-> Ord Result
Result -> Result -> Bool
Result -> Result -> Ordering
Result -> Result -> Result
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: Result -> Result -> Result
$cmin :: Result -> Result -> Result
max :: Result -> Result -> Result
$cmax :: Result -> Result -> Result
>= :: Result -> Result -> Bool
$c>= :: Result -> Result -> Bool
> :: Result -> Result -> Bool
$c> :: Result -> Result -> Bool
<= :: Result -> Result -> Bool
$c<= :: Result -> Result -> Bool
< :: Result -> Result -> Bool
$c< :: Result -> Result -> Bool
compare :: Result -> Result -> Ordering
$ccompare :: Result -> Result -> Ordering
$cp1Ord :: Eq Result
Ord)
foreign import capi "rustls.h value RUSTLS_RESULT_OK"
resultOk :: Result
foreign import capi "rustls.h value RUSTLS_RESULT_INSUFFICIENT_SIZE"
resultInsufficientSize :: Result
foreign import capi unsafe "rustls.h rustls_result_is_cert_error"
resultIsCertError :: Result -> CBool
foreign import capi unsafe "rustls.h rustls_error"
errorMsg :: Result -> CString -> CSize -> Ptr CSize -> IO ()
newtype {-# CTYPE "rustls.h" "rustls_io_result" #-} IOResult = IOResult CInt
deriving stock (IOResult -> IOResult -> Bool
(IOResult -> IOResult -> Bool)
-> (IOResult -> IOResult -> Bool) -> Eq IOResult
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: IOResult -> IOResult -> Bool
$c/= :: IOResult -> IOResult -> Bool
== :: IOResult -> IOResult -> Bool
$c== :: IOResult -> IOResult -> Bool
Eq)
ioResultOk :: IOResult
ioResultOk :: IOResult
ioResultOk = CInt -> IOResult
IOResult CInt
0
ioResultErr :: IOResult
ioResultErr :: IOResult
ioResultErr = CInt -> IOResult
IOResult CInt
1
data Userdata
data {-# CTYPE "rustls.h" "rustls_client_config" #-} ClientConfig
data {-# CTYPE "rustls.h" "rustls_client_config_builder" #-} ClientConfigBuilder
foreign import capi unsafe "rustls.h rustls_client_config_builder_new_custom"
clientConfigBuilderNewCustom ::
Ptr (Ptr SupportedCipherSuite) ->
CSize ->
Ptr TLSVersion ->
CSize ->
Ptr (Ptr ClientConfigBuilder) ->
IO Result
foreign import capi unsafe "rustls.h rustls_client_config_builder_free"
clientConfigBuilderFree :: Ptr ClientConfigBuilder -> IO ()
foreign import capi unsafe "rustls.h rustls_client_config_builder_build"
clientConfigBuilderBuild :: Ptr ClientConfigBuilder -> IO (Ptr ClientConfig)
foreign import capi unsafe "rustls.h &rustls_client_config_free"
clientConfigFree :: FinalizerPtr ClientConfig
foreign import capi unsafe "rustls.h rustls_client_connection_new"
clientConnectionNew ::
Ptr ClientConfig ->
CString ->
Ptr (Ptr Connection) ->
IO Result
foreign import capi unsafe "rustls.h rustls_client_config_builder_load_roots_from_file"
clientConfigBuilderLoadRootsFromFile :: Ptr ClientConfigBuilder -> CString -> IO Result
data {-# CTYPE "rustls.h" "rustls_root_cert_store" #-} RootCertStore
foreign import capi unsafe "rustls.h rustls_root_cert_store_new"
rootCertStoreNew :: IO (Ptr RootCertStore)
foreign import capi unsafe "rustls.h rustls_root_cert_store_add_pem"
rootCertStoreAddPEM :: Ptr RootCertStore -> Ptr Word8 -> CSize -> CBool -> IO Result
foreign import capi unsafe "rustls.h rustls_root_cert_store_free"
rootCertStoreFree :: Ptr RootCertStore -> IO ()
foreign import capi unsafe "rustls.h rustls_client_config_builder_use_roots"
clientConfigBuilderUseRoots :: Ptr ClientConfigBuilder -> Ptr RootCertStore -> IO Result
foreign import capi unsafe "rustls.h rustls_client_config_builder_set_alpn_protocols"
clientConfigBuilderSetALPNProtocols :: Ptr ClientConfigBuilder -> Ptr SliceBytes -> CSize -> IO Result
foreign import capi unsafe "rustls.h rustls_client_config_builder_set_enable_sni"
clientConfigBuilderSetEnableSNI :: Ptr ClientConfigBuilder -> CBool -> IO ()
foreign import capi unsafe "rustls.h rustls_client_config_builder_set_certified_key"
clientConfigBuilderSetCertifiedKey :: Ptr ClientConfigBuilder -> Ptr (Ptr CertifiedKey) -> CSize -> IO Result
data {-# CTYPE "rustls.h" "rustls_server_config" #-} ServerConfig
data {-# CTYPE "rustls.h" "rustls_server_config_builder" #-} ServerConfigBuilder
foreign import capi unsafe "rustls.h rustls_server_config_builder_new_custom"
serverConfigBuilderNewCustom ::
Ptr (Ptr SupportedCipherSuite) ->
CSize ->
Ptr TLSVersion ->
CSize ->
Ptr (Ptr ServerConfigBuilder) ->
IO Result
foreign import capi unsafe "rustls.h rustls_server_config_builder_free"
serverConfigBuilderFree :: Ptr ServerConfigBuilder -> IO ()
foreign import capi unsafe "rustls.h rustls_server_config_builder_build"
serverConfigBuilderBuild :: Ptr ServerConfigBuilder -> IO (Ptr ServerConfig)
foreign import capi unsafe "rustls.h &rustls_server_config_free"
serverConfigFree :: FinalizerPtr ServerConfig
foreign import capi unsafe "rustls.h rustls_server_connection_new"
serverConnectionNew :: Ptr ServerConfig -> Ptr (Ptr Connection) -> IO Result
foreign import capi unsafe "rustls.h rustls_server_config_builder_set_alpn_protocols"
serverConfigBuilderSetALPNProtocols :: Ptr ServerConfigBuilder -> Ptr SliceBytes -> CSize -> IO Result
foreign import capi unsafe "rustls.h rustls_server_config_builder_set_ignore_client_order"
serverConfigBuilderSetIgnoreClientOrder :: Ptr ServerConfigBuilder -> CBool -> IO Result
foreign import capi unsafe "rustls.h rustls_server_config_builder_set_certified_keys"
serverConfigBuilderSetCertifiedKeys :: Ptr ServerConfigBuilder -> Ptr (Ptr CertifiedKey) -> CSize -> IO Result
data {-# CTYPE "rustls.h" "rustls_client_cert_verifier" #-} ClientCertVerifier
foreign import capi unsafe "rustls.h rustls_client_cert_verifier_new"
clientCertVerifierNew :: Ptr RootCertStore -> IO (Ptr ClientCertVerifier)
foreign import capi unsafe "rustls.h rustls_client_cert_verifier_free"
clientCertVerifierFree :: Ptr ClientCertVerifier -> IO ()
foreign import capi unsafe "rustls.h rustls_server_config_builder_set_client_verifier"
serverConfigBuilderSetClientVerifier :: Ptr ServerConfigBuilder -> Ptr ClientCertVerifier -> IO ()
data {-# CTYPE "rustls.h" "rustls_client_cert_verifier_optional" #-} ClientCertVerifierOptional
foreign import capi unsafe "rustls.h rustls_client_cert_verifier_optional_new"
clientCertVerifierOptionalNew :: Ptr RootCertStore -> IO (Ptr ClientCertVerifierOptional)
foreign import capi unsafe "rustls.h rustls_client_cert_verifier_optional_free"
clientCertVerifierOptionalFree :: Ptr ClientCertVerifierOptional -> IO ()
foreign import capi unsafe "rustls.h rustls_server_config_builder_set_client_verifier_optional"
serverConfigBuilderSetClientVerifierOptional :: Ptr ServerConfigBuilder -> Ptr ClientCertVerifierOptional -> IO ()
data {-# CTYPE "rustls.h" "rustls_connection" #-} Connection
foreign import capi unsafe "rustls.h rustls_connection_free"
connectionFree :: Ptr Connection -> IO ()
type LogCallback = Ptr Userdata -> Ptr LogParams -> IO ()
foreign import ccall "wrapper"
mkLogCallback :: LogCallback -> IO (FunPtr LogCallback)
newtype LogLevel = LogLevel CSize
deriving stock (LogLevel -> LogLevel -> Bool
(LogLevel -> LogLevel -> Bool)
-> (LogLevel -> LogLevel -> Bool) -> Eq LogLevel
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: LogLevel -> LogLevel -> Bool
$c/= :: LogLevel -> LogLevel -> Bool
== :: LogLevel -> LogLevel -> Bool
$c== :: LogLevel -> LogLevel -> Bool
Eq)
deriving newtype (Ptr b -> Int -> IO LogLevel
Ptr b -> Int -> LogLevel -> IO ()
Ptr LogLevel -> IO LogLevel
Ptr LogLevel -> Int -> IO LogLevel
Ptr LogLevel -> Int -> LogLevel -> IO ()
Ptr LogLevel -> LogLevel -> IO ()
LogLevel -> Int
(LogLevel -> Int)
-> (LogLevel -> Int)
-> (Ptr LogLevel -> Int -> IO LogLevel)
-> (Ptr LogLevel -> Int -> LogLevel -> IO ())
-> (forall b. Ptr b -> Int -> IO LogLevel)
-> (forall b. Ptr b -> Int -> LogLevel -> IO ())
-> (Ptr LogLevel -> IO LogLevel)
-> (Ptr LogLevel -> LogLevel -> IO ())
-> Storable LogLevel
forall b. Ptr b -> Int -> IO LogLevel
forall b. Ptr b -> Int -> LogLevel -> IO ()
forall a.
(a -> Int)
-> (a -> Int)
-> (Ptr a -> Int -> IO a)
-> (Ptr a -> Int -> a -> IO ())
-> (forall b. Ptr b -> Int -> IO a)
-> (forall b. Ptr b -> Int -> a -> IO ())
-> (Ptr a -> IO a)
-> (Ptr a -> a -> IO ())
-> Storable a
poke :: Ptr LogLevel -> LogLevel -> IO ()
$cpoke :: Ptr LogLevel -> LogLevel -> IO ()
peek :: Ptr LogLevel -> IO LogLevel
$cpeek :: Ptr LogLevel -> IO LogLevel
pokeByteOff :: Ptr b -> Int -> LogLevel -> IO ()
$cpokeByteOff :: forall b. Ptr b -> Int -> LogLevel -> IO ()
peekByteOff :: Ptr b -> Int -> IO LogLevel
$cpeekByteOff :: forall b. Ptr b -> Int -> IO LogLevel
pokeElemOff :: Ptr LogLevel -> Int -> LogLevel -> IO ()
$cpokeElemOff :: Ptr LogLevel -> Int -> LogLevel -> IO ()
peekElemOff :: Ptr LogLevel -> Int -> IO LogLevel
$cpeekElemOff :: Ptr LogLevel -> Int -> IO LogLevel
alignment :: LogLevel -> Int
$calignment :: LogLevel -> Int
sizeOf :: LogLevel -> Int
$csizeOf :: LogLevel -> Int
Storable)
data LogParams = LogParams
{ LogParams -> LogLevel
rustlsLogParamsLevel :: LogLevel,
LogParams -> Str
rustlsLogParamsMessage :: Str
}
deriving stock ((forall x. LogParams -> Rep LogParams x)
-> (forall x. Rep LogParams x -> LogParams) -> Generic LogParams
forall x. Rep LogParams x -> LogParams
forall x. LogParams -> Rep LogParams x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep LogParams x -> LogParams
$cfrom :: forall x. LogParams -> Rep LogParams x
Generic)
deriving anyclass (LogParams -> Int
(LogParams -> Int)
-> (LogParams -> Int)
-> (forall b. Ptr b -> Int -> IO LogParams)
-> (forall b. Ptr b -> Int -> LogParams -> IO ())
-> GStorable LogParams
forall b. Ptr b -> Int -> IO LogParams
forall b. Ptr b -> Int -> LogParams -> IO ()
forall a.
(a -> Int)
-> (a -> Int)
-> (forall b. Ptr b -> Int -> IO a)
-> (forall b. Ptr b -> Int -> a -> IO ())
-> GStorable a
gpokeByteOff :: Ptr b -> Int -> LogParams -> IO ()
$cgpokeByteOff :: forall b. Ptr b -> Int -> LogParams -> IO ()
gpeekByteOff :: Ptr b -> Int -> IO LogParams
$cgpeekByteOff :: forall b. Ptr b -> Int -> IO LogParams
galignment :: LogParams -> Int
$cgalignment :: LogParams -> Int
gsizeOf :: LogParams -> Int
$cgsizeOf :: LogParams -> Int
GStorable)
foreign import capi unsafe "rustls.h rustls_connection_set_log_callback"
connectionSetLogCallback :: Ptr Connection -> FunPtr LogCallback -> IO ()
foreign import capi unsafe "rustls.h rustls_connection_is_handshaking"
connectionIsHandshaking :: Ptr Connection -> IO CBool
foreign import capi unsafe "rustls.h rustls_connection_get_alpn_protocol"
connectionGetALPNProtocol :: Ptr Connection -> Ptr (Ptr Word8) -> Ptr CSize -> IO ()
foreign import capi unsafe "rustls.h rustls_connection_get_protocol_version"
connectionGetProtocolVersion :: Ptr Connection -> IO TLSVersion
foreign import capi unsafe "rustls.h rustls_connection_get_negotiated_ciphersuite"
connectionGetNegotiatedCipherSuite :: Ptr Connection -> IO (Ptr SupportedCipherSuite)
foreign import capi unsafe "rustls.h rustls_server_connection_get_sni_hostname"
serverConnectionGetSNIHostname :: Ptr Connection -> Ptr Word8 -> CSize -> Ptr CSize -> IO Result
foreign import capi unsafe "rustls.h rustls_connection_get_peer_certificate"
connectionGetPeerCertificate :: Ptr Connection -> CSize -> IO (Ptr Certificate)
type ReadWriteCallback = Ptr Userdata -> Ptr Word8 -> CSize -> Ptr CSize -> IO IOResult
foreign import ccall "wrapper"
mkReadWriteCallback :: ReadWriteCallback -> IO (FunPtr ReadWriteCallback)
foreign import capi "rustls.h rustls_connection_read_tls"
connectionReadTls ::
Ptr Connection -> FunPtr ReadWriteCallback -> Ptr Userdata -> Ptr CSize -> IO IOResult
foreign import capi "rustls.h rustls_connection_read"
connectionRead :: Ptr Connection -> Ptr Word8 -> CSize -> Ptr CSize -> IO Result
foreign import capi unsafe "rustls.h rustls_connection_wants_read"
connectionWantsRead :: Ptr Connection -> IO CBool
foreign import capi "rustls.h rustls_connection_write_tls"
connectionWriteTls ::
Ptr Connection -> FunPtr ReadWriteCallback -> Ptr Userdata -> Ptr CSize -> IO IOResult
foreign import capi "rustls.h rustls_connection_write"
connectionWrite :: Ptr Connection -> Ptr Word8 -> CSize -> Ptr CSize -> IO Result
foreign import capi unsafe "rustls.h rustls_connection_wants_write"
connectionWantsWrite :: Ptr Connection -> IO CBool
foreign import capi "rustls.h rustls_connection_process_new_packets"
connectionProcessNewPackets :: Ptr Connection -> IO Result
foreign import capi "rustls.h rustls_connection_send_close_notify"
connectionSendCloseNotify :: Ptr Connection -> IO ()
foreign import capi unsafe "rustls.h rustls_connection_set_buffer_limit"
connectionSetBufferLimit :: Ptr Connection -> CSize -> IO ()
data {-# CTYPE "rustls.h" "rustls_certified_key" #-} CertifiedKey
foreign import capi unsafe "rustls.h rustls_certified_key_build"
certifiedKeyBuild :: Ptr Word8 -> CSize -> Ptr Word8 -> CSize -> Ptr (Ptr CertifiedKey) -> IO Result
foreign import capi unsafe "rustls.h rustls_certified_key_free"
certifiedKeyFree :: Ptr CertifiedKey -> IO ()
data {-# CTYPE "rustls.h" "rustls_certificate" #-} Certificate
foreign import capi unsafe "rustls.h rustls_certificate_get_der"
certificateGetDER :: Ptr Certificate -> Ptr (Ptr Word8) -> Ptr CSize -> IO Result
data {-# CTYPE "rustls.h" "rustls_supported_ciphersuite" #-} SupportedCipherSuite
foreign import capi "rustls.h value RUSTLS_ALL_CIPHER_SUITES"
allCipherSuites :: Ptr (Ptr SupportedCipherSuite)
foreign import capi "rustls.h value RUSTLS_ALL_CIPHER_SUITES_LEN"
allCipherSuitesLen :: CSize
foreign import capi "rustls.h value RUSTLS_DEFAULT_CIPHER_SUITES"
defaultCipherSuites :: Ptr (Ptr SupportedCipherSuite)
foreign import capi "rustls.h value RUSTLS_DEFAULT_CIPHER_SUITES_LEN"
defaultCipherSuitesLen :: CSize
foreign import capi unsafe "rustls.h rustls_supported_ciphersuite_get_suite"
supportedCipherSuiteGetSuite :: Ptr SupportedCipherSuite -> Word16
foreign import capi unsafe "hs_rustls.h hs_rustls_supported_ciphersuite_get_name"
hsSupportedCipherSuiteGetName :: Ptr SupportedCipherSuite -> Ptr Str -> IO ()
newtype {-# CTYPE "stdint.h" "uint16_t" #-} TLSVersion = TLSVersion
{ TLSVersion -> Word16
unTLSVersion :: Word16
}
deriving stock (Int -> TLSVersion -> ShowS
[TLSVersion] -> ShowS
TLSVersion -> String
(Int -> TLSVersion -> ShowS)
-> (TLSVersion -> String)
-> ([TLSVersion] -> ShowS)
-> Show TLSVersion
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [TLSVersion] -> ShowS
$cshowList :: [TLSVersion] -> ShowS
show :: TLSVersion -> String
$cshow :: TLSVersion -> String
showsPrec :: Int -> TLSVersion -> ShowS
$cshowsPrec :: Int -> TLSVersion -> ShowS
Show, TLSVersion -> TLSVersion -> Bool
(TLSVersion -> TLSVersion -> Bool)
-> (TLSVersion -> TLSVersion -> Bool) -> Eq TLSVersion
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: TLSVersion -> TLSVersion -> Bool
$c/= :: TLSVersion -> TLSVersion -> Bool
== :: TLSVersion -> TLSVersion -> Bool
$c== :: TLSVersion -> TLSVersion -> Bool
Eq, Eq TLSVersion
Eq TLSVersion
-> (TLSVersion -> TLSVersion -> Ordering)
-> (TLSVersion -> TLSVersion -> Bool)
-> (TLSVersion -> TLSVersion -> Bool)
-> (TLSVersion -> TLSVersion -> Bool)
-> (TLSVersion -> TLSVersion -> Bool)
-> (TLSVersion -> TLSVersion -> TLSVersion)
-> (TLSVersion -> TLSVersion -> TLSVersion)
-> Ord TLSVersion
TLSVersion -> TLSVersion -> Bool
TLSVersion -> TLSVersion -> Ordering
TLSVersion -> TLSVersion -> TLSVersion
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: TLSVersion -> TLSVersion -> TLSVersion
$cmin :: TLSVersion -> TLSVersion -> TLSVersion
max :: TLSVersion -> TLSVersion -> TLSVersion
$cmax :: TLSVersion -> TLSVersion -> TLSVersion
>= :: TLSVersion -> TLSVersion -> Bool
$c>= :: TLSVersion -> TLSVersion -> Bool
> :: TLSVersion -> TLSVersion -> Bool
$c> :: TLSVersion -> TLSVersion -> Bool
<= :: TLSVersion -> TLSVersion -> Bool
$c<= :: TLSVersion -> TLSVersion -> Bool
< :: TLSVersion -> TLSVersion -> Bool
$c< :: TLSVersion -> TLSVersion -> Bool
compare :: TLSVersion -> TLSVersion -> Ordering
$ccompare :: TLSVersion -> TLSVersion -> Ordering
$cp1Ord :: Eq TLSVersion
Ord)
deriving newtype (Ptr b -> Int -> IO TLSVersion
Ptr b -> Int -> TLSVersion -> IO ()
Ptr TLSVersion -> IO TLSVersion
Ptr TLSVersion -> Int -> IO TLSVersion
Ptr TLSVersion -> Int -> TLSVersion -> IO ()
Ptr TLSVersion -> TLSVersion -> IO ()
TLSVersion -> Int
(TLSVersion -> Int)
-> (TLSVersion -> Int)
-> (Ptr TLSVersion -> Int -> IO TLSVersion)
-> (Ptr TLSVersion -> Int -> TLSVersion -> IO ())
-> (forall b. Ptr b -> Int -> IO TLSVersion)
-> (forall b. Ptr b -> Int -> TLSVersion -> IO ())
-> (Ptr TLSVersion -> IO TLSVersion)
-> (Ptr TLSVersion -> TLSVersion -> IO ())
-> Storable TLSVersion
forall b. Ptr b -> Int -> IO TLSVersion
forall b. Ptr b -> Int -> TLSVersion -> IO ()
forall a.
(a -> Int)
-> (a -> Int)
-> (Ptr a -> Int -> IO a)
-> (Ptr a -> Int -> a -> IO ())
-> (forall b. Ptr b -> Int -> IO a)
-> (forall b. Ptr b -> Int -> a -> IO ())
-> (Ptr a -> IO a)
-> (Ptr a -> a -> IO ())
-> Storable a
poke :: Ptr TLSVersion -> TLSVersion -> IO ()
$cpoke :: Ptr TLSVersion -> TLSVersion -> IO ()
peek :: Ptr TLSVersion -> IO TLSVersion
$cpeek :: Ptr TLSVersion -> IO TLSVersion
pokeByteOff :: Ptr b -> Int -> TLSVersion -> IO ()
$cpokeByteOff :: forall b. Ptr b -> Int -> TLSVersion -> IO ()
peekByteOff :: Ptr b -> Int -> IO TLSVersion
$cpeekByteOff :: forall b. Ptr b -> Int -> IO TLSVersion
pokeElemOff :: Ptr TLSVersion -> Int -> TLSVersion -> IO ()
$cpokeElemOff :: Ptr TLSVersion -> Int -> TLSVersion -> IO ()
peekElemOff :: Ptr TLSVersion -> Int -> IO TLSVersion
$cpeekElemOff :: Ptr TLSVersion -> Int -> IO TLSVersion
alignment :: TLSVersion -> Int
$calignment :: TLSVersion -> Int
sizeOf :: TLSVersion -> Int
$csizeOf :: TLSVersion -> Int
Storable)
pattern TLS12, TLS13 :: TLSVersion
pattern $bTLS12 :: TLSVersion
$mTLS12 :: forall r. TLSVersion -> (Void# -> r) -> (Void# -> r) -> r
TLS12 = TLSVersion 0x0303
pattern $bTLS13 :: TLSVersion
$mTLS13 :: forall r. TLSVersion -> (Void# -> r) -> (Void# -> r) -> r
TLS13 = TLSVersion 0x0304
foreign import capi "rustls.h value RUSTLS_ALL_VERSIONS"
allVersions :: Ptr TLSVersion
foreign import capi "rustls.h value RUSTLS_ALL_VERSIONS_LEN"
allVersionsLen :: CSize
foreign import capi "rustls.h value RUSTLS_DEFAULT_VERSIONS"
defaultVersions :: Ptr TLSVersion
foreign import capi "rustls.h value RUSTLS_DEFAULT_VERSIONS_LEN"
defaultVersionsLen :: CSize