Safe Haskell | None |
---|---|
Language | Haskell2010 |
Network.TLS
Description
Native Haskell TLS protocol implementation for servers and clients.
This provides a high-level implementation of a sensitive security protocol, eliminating a common set of security issues through the use of the advanced type system, high level constructions and common Haskell features.
Currently implement the TLS1.2 and TLS 1.3 protocol, and support RSA and Ephemeral (Elliptic curve and regular) Diffie Hellman key exchanges, and many extensions.
Synopsis
- data Context
- contextNew :: (MonadIO m, HasBackend backend, TLSParams params) => backend -> params -> m Context
- handshake :: MonadIO m => Context -> m ()
- sendData :: MonadIO m => Context -> ByteString -> m ()
- recvData :: MonadIO m => Context -> m ByteString
- bye :: MonadIO m => Context -> m ()
- class HasBackend a where
- initializeBackend :: a -> IO ()
- getBackend :: a -> Backend
- data Backend = Backend {
- backendFlush :: IO ()
- backendClose :: IO ()
- backendSend :: ByteString -> IO ()
- backendRecv :: Int -> IO ByteString
- class TLSParams a
- data ClientParams = ClientParams {
- clientUseMaxFragmentLength :: Maybe MaxFragmentEnum
- clientServerIdentification :: (HostName, ByteString)
- clientUseServerNameIndication :: Bool
- clientWantSessionResume :: Maybe (SessionID, SessionData)
- clientShared :: Shared
- clientHooks :: ClientHooks
- clientSupported :: Supported
- clientDebug :: DebugParams
- clientUseEarlyData :: Bool
- defaultParamsClient :: HostName -> ByteString -> ClientParams
- data ServerParams = ServerParams {}
- data Shared = Shared {}
- data ClientHooks = ClientHooks {}
- type OnCertificateRequest = ([CertificateType], Maybe [HashAndSignatureAlgorithm], [DistinguishedName]) -> IO (Maybe (CertificateChain, PrivKey))
- type OnServerCertificate = CertificateStore -> ValidationCache -> ServiceID -> CertificateChain -> IO [FailedReason]
- data ServerHooks = ServerHooks {
- onClientCertificate :: CertificateChain -> IO CertificateUsage
- onUnverifiedClientCert :: IO Bool
- onCipherChoosing :: Version -> [Cipher] -> Cipher
- onServerNameIndication :: Maybe HostName -> IO Credentials
- onNewHandshake :: Measurement -> IO Bool
- onALPNClientSuggest :: Maybe ([ByteString] -> IO ByteString)
- onEncryptedExtensionsCreating :: [ExtensionRaw] -> IO [ExtensionRaw]
- data Measurement = Measurement {}
- data Supported = Supported {
- supportedVersions :: [Version]
- supportedCiphers :: [Cipher]
- supportedCompressions :: [Compression]
- supportedHashSignatures :: [HashAndSignatureAlgorithm]
- supportedSecureRenegotiation :: Bool
- supportedClientInitiatedRenegotiation :: Bool
- supportedExtendedMainSecret :: EMSMode
- supportedSession :: Bool
- supportedFallbackScsv :: Bool
- supportedEmptyPacket :: Bool
- supportedGroups :: [Group]
- data DebugParams = DebugParams {
- debugSeed :: Maybe Seed
- debugPrintSeed :: Seed -> IO ()
- debugVersionForced :: Maybe Version
- debugKeyLogger :: String -> IO ()
- newtype Credentials = Credentials [Credential]
- type Credential = (CertificateChain, PrivKey)
- credentialLoadX509 :: FilePath -> FilePath -> IO (Either String Credential)
- credentialLoadX509FromMemory :: ByteString -> ByteString -> Either String Credential
- credentialLoadX509Chain :: FilePath -> [FilePath] -> FilePath -> IO (Either String Credential)
- credentialLoadX509ChainFromMemory :: ByteString -> [ByteString] -> ByteString -> Either String Credential
- data SessionManager = SessionManager {
- sessionResume :: SessionIDorTicket -> IO (Maybe SessionData)
- sessionResumeOnlyOnce :: SessionIDorTicket -> IO (Maybe SessionData)
- sessionEstablish :: SessionID -> SessionData -> IO (Maybe Ticket)
- sessionInvalidate :: SessionID -> IO ()
- sessionUseTicket :: Bool
- noSessionManager :: SessionManager
- type SessionID = ByteString
- type SessionIDorTicket = ByteString
- type Ticket = ByteString
- data SessionData = SessionData {
- sessionVersion :: Version
- sessionCipher :: CipherID
- sessionCompression :: CompressionID
- sessionClientSNI :: Maybe HostName
- sessionSecret :: ByteString
- sessionGroup :: Maybe Group
- sessionTicketInfo :: Maybe TLS13TicketInfo
- sessionALPN :: Maybe ByteString
- sessionMaxEarlyDataSize :: Int
- sessionFlags :: [SessionFlag]
- data SessionFlag = SessionEMS
- data TLS13TicketInfo
- data ValidationCache = ValidationCache {}
- type ValidationCacheQueryCallback = ServiceID -> Fingerprint -> Certificate -> IO ValidationCacheResult
- type ValidationCacheAddCallback = ServiceID -> Fingerprint -> Certificate -> IO ()
- data ValidationCacheResult
- exceptionValidationCache :: [(ServiceID, Fingerprint)] -> ValidationCache
- newtype Version where
- data Compression = CompressionC a => Compression a
- nullCompression :: Compression
- type HashAndSignatureAlgorithm = (HashAlgorithm, SignatureAlgorithm)
- supportedSignatureSchemes :: [HashAndSignatureAlgorithm]
- newtype HashAlgorithm where
- HashAlgorithm { }
- pattern HashMD5 :: HashAlgorithm
- pattern HashSHA1 :: HashAlgorithm
- pattern HashSHA224 :: HashAlgorithm
- pattern HashSHA256 :: HashAlgorithm
- pattern HashSHA384 :: HashAlgorithm
- pattern HashSHA512 :: HashAlgorithm
- pattern HashNone :: HashAlgorithm
- pattern HashIntrinsic :: HashAlgorithm
- newtype SignatureAlgorithm where
- SignatureAlgorithm { }
- pattern SignatureAnonymous :: SignatureAlgorithm
- pattern SignatureRSA :: SignatureAlgorithm
- pattern SignatureDSA :: SignatureAlgorithm
- pattern SignatureECDSA :: SignatureAlgorithm
- pattern SignatureRSApssRSAeSHA256 :: SignatureAlgorithm
- pattern SignatureRSApssRSAeSHA384 :: SignatureAlgorithm
- pattern SignatureRSApssRSAeSHA512 :: SignatureAlgorithm
- pattern SignatureEd25519 :: SignatureAlgorithm
- pattern SignatureEd448 :: SignatureAlgorithm
- pattern SignatureRSApsspssSHA256 :: SignatureAlgorithm
- pattern SignatureRSApsspssSHA384 :: SignatureAlgorithm
- pattern SignatureRSApsspssSHA512 :: SignatureAlgorithm
- newtype Group where
- supportedNamedGroups :: [Group]
- data EMSMode
- = NoEMS
- | AllowEMS
- | RequireEMS
- type DHParams = Params
- type DHPublic = PublicNumber
- data GroupUsage
- data CertificateUsage
- data CertificateRejectReason
- newtype CertificateType where
- CertificateType { }
- pattern CertificateType_RSA_Sign :: CertificateType
- pattern CertificateType_DSA_Sign :: CertificateType
- pattern CertificateType_ECDSA_Sign :: CertificateType
- pattern CertificateType_Ed25519_Sign :: CertificateType
- pattern CertificateType_Ed448_Sign :: CertificateType
- type HostName = String
- data MaxFragmentEnum
- ctxBackend :: Context -> Backend
- contextFlush :: Context -> IO ()
- contextClose :: Context -> IO ()
- data Information = Information {
- infoVersion :: Version
- infoCipher :: Cipher
- infoCompression :: Compression
- infoMainSecret :: Maybe ByteString
- infoExtendedMainSecret :: Bool
- infoClientRandom :: Maybe ClientRandom
- infoServerRandom :: Maybe ServerRandom
- infoSupportedGroup :: Maybe Group
- infoTLS12Resumption :: Bool
- infoTLS13HandshakeMode :: Maybe HandshakeMode13
- infoIsEarlyDataAccepted :: Bool
- contextGetInformation :: Context -> IO (Maybe Information)
- data ClientRandom
- data ServerRandom
- unClientRandom :: ClientRandom -> ByteString
- unServerRandom :: ServerRandom -> ByteString
- data HandshakeMode13
- getClientCertificateChain :: Context -> IO (Maybe CertificateChain)
- getNegotiatedProtocol :: MonadIO m => Context -> m (Maybe ByteString)
- getClientSNI :: MonadIO m => Context -> m (Maybe HostName)
- updateKey :: MonadIO m => Context -> KeyUpdateRequest -> m Bool
- data KeyUpdateRequest
- requestCertificate :: Context -> IO Bool
- getTLSUnique :: Context -> IO (Maybe ByteString)
- getTLSExporter :: Context -> IO (Maybe ByteString)
- getTLSServerEndPoint :: Context -> IO (Maybe ByteString)
- getFinished :: Context -> IO (Maybe VerifyData)
- getPeerFinished :: Context -> IO (Maybe VerifyData)
- data Hooks = Hooks {}
- contextModifyHooks :: Context -> (Hooks -> Hooks) -> IO ()
- data Handshake
- contextHookSetHandshakeRecv :: Context -> (Handshake -> IO Handshake) -> IO ()
- data Handshake13
- contextHookSetHandshake13Recv :: Context -> (Handshake13 -> IO Handshake13) -> IO ()
- contextHookSetCertificateRecv :: Context -> (CertificateChain -> IO ()) -> IO ()
- data Logging = Logging {
- loggingPacketSent :: String -> IO ()
- loggingPacketRecv :: String -> IO ()
- loggingIOSent :: ByteString -> IO ()
- loggingIORecv :: Header -> ByteString -> IO ()
- data Header = Header ProtocolType Version Word16
- newtype ProtocolType where
- ProtocolType { }
- pattern ProtocolType_ChangeCipherSpec :: ProtocolType
- pattern ProtocolType_Alert :: ProtocolType
- pattern ProtocolType_Handshake :: ProtocolType
- pattern ProtocolType_AppData :: ProtocolType
- contextHookSetLogging :: Context -> Logging -> IO ()
- data TLSError
- data KxError
- newtype AlertDescription where
- AlertDescription { }
- pattern DecodeError :: AlertDescription
- pattern CloseNotify :: AlertDescription
- pattern UnexpectedMessage :: AlertDescription
- pattern BadRecordMac :: AlertDescription
- pattern DecryptionFailed :: AlertDescription
- pattern RecordOverflow :: AlertDescription
- pattern DecompressionFailure :: AlertDescription
- pattern HandshakeFailure :: AlertDescription
- pattern BadCertificate :: AlertDescription
- pattern UnsupportedCertificate :: AlertDescription
- pattern CertificateRevoked :: AlertDescription
- pattern CertificateExpired :: AlertDescription
- pattern CertificateUnknown :: AlertDescription
- pattern IllegalParameter :: AlertDescription
- pattern UnknownCa :: AlertDescription
- pattern AccessDenied :: AlertDescription
- pattern DecryptError :: AlertDescription
- pattern ExportRestriction :: AlertDescription
- pattern ProtocolVersion :: AlertDescription
- pattern InsufficientSecurity :: AlertDescription
- pattern InternalError :: AlertDescription
- pattern InappropriateFallback :: AlertDescription
- pattern UserCanceled :: AlertDescription
- pattern NoRenegotiation :: AlertDescription
- pattern MissingExtension :: AlertDescription
- pattern UnsupportedExtension :: AlertDescription
- pattern CertificateUnobtainable :: AlertDescription
- pattern UnrecognizedName :: AlertDescription
- pattern BadCertificateStatusResponse :: AlertDescription
- pattern BadCertificateHashValue :: AlertDescription
- pattern UnknownPskIdentity :: AlertDescription
- pattern CertificateRequired :: AlertDescription
- pattern NoApplicationProtocol :: AlertDescription
- data TLSException
- class CompressionC a where
- compressionCID :: a -> CompressionID
- compressionCDeflate :: a -> ByteString -> (a, ByteString)
- compressionCInflate :: a -> ByteString -> (a, ByteString)
- type CompressionID = Word8
- data PubKey
- data PrivKey
- data Cipher = Cipher {}
- data Hash
- data CipherKeyExchangeType
- data Bulk = Bulk {
- bulkName :: String
- bulkKeySize :: Int
- bulkIVSize :: Int
- bulkExplicitIV :: Int
- bulkAuthTagLen :: Int
- bulkBlockSize :: Int
- bulkF :: BulkFunctions
- data BulkFunctions
- = BulkBlockF (BulkDirection -> BulkKey -> BulkBlock)
- | BulkStreamF (BulkDirection -> BulkKey -> BulkStream)
- | BulkAeadF (BulkDirection -> BulkKey -> BulkAEAD)
- data BulkDirection
- data BulkState
- newtype BulkStream = BulkStream (ByteString -> (ByteString, BulkStream))
- type BulkBlock = BulkIV -> ByteString -> (ByteString, BulkIV)
- type BulkAEAD = BulkNonce -> ByteString -> BulkAdditionalData -> (ByteString, AuthTag)
- bulkInit :: Bulk -> BulkDirection -> BulkKey -> BulkState
- type CipherID = Word16
- cipherKeyBlockSize :: Cipher -> Int
- type BulkKey = ByteString
- type BulkIV = ByteString
- type BulkNonce = ByteString
- type BulkAdditionalData = ByteString
- cipherAllowedForVersion :: Version -> Cipher -> Bool
- hasMAC :: BulkFunctions -> Bool
- hasRecordIV :: BulkFunctions -> Bool
- recvData' :: MonadIO m => Context -> m ByteString
- type Bytes = ByteString
- data ValidationChecks = ValidationChecks {}
- data ValidationHooks = ValidationHooks {
- hookMatchSubjectIssuer :: DistinguishedName -> Certificate -> Bool
- hookValidateTime :: DateTime -> Certificate -> [FailedReason]
- hookValidateName :: HostName -> Certificate -> [FailedReason]
- hookFilterReason :: [FailedReason] -> [FailedReason]
Basic APIs
Arguments
:: (MonadIO m, HasBackend backend, TLSParams params) | |
=> backend | Backend abstraction with specific method to interact with the connection type. |
-> params | Parameters of the context. |
-> m Context |
create a new context using the backend and parameters specified.
handshake :: MonadIO m => Context -> m () #
Handshake for a new TLS connection
This is to be called at the beginning of a connection, and during renegotiation.
Don't use this function as the acquire resource of bracket
.
sendData :: MonadIO m => Context -> ByteString -> m () #
sendData sends a bunch of data. It will automatically chunk data to acceptable packet size
recvData :: MonadIO m => Context -> m ByteString #
Get data out of Data packet, and automatically renegotiate if a Handshake ClientHello is received. An empty result means EOF.
bye :: MonadIO m => Context -> m () #
notify the context that this side wants to close connection. this is important that it is called before closing the handle, otherwise the session might not be resumable (for version < TLS1.2).
this doesn't actually close the handle
Exceptions
Since 1.8.0, this library only throws exceptions of type TLSException
.
In the common case where the chosen backend is socket, IOException
may be thrown as well. This happens because the backend for sockets,
opaque to most modules in the tls
library, throws those exceptions.
Backend abstraction
class HasBackend a where #
Instances
HasBackend Handle # | |
Defined in Network.TLS.Backend | |
HasBackend Socket # | |
Defined in Network.TLS.Backend | |
HasBackend Backend # | |
Defined in Network.TLS.Backend |
Connection IO backend
Constructors
Backend | |
Fields
|
Instances
HasBackend Backend # | |
Defined in Network.TLS.Backend |
Parameters
Minimal complete definition
getTLSCommonParams, getTLSRole, doHandshake, doHandshakeWith, doRequestCertificate, doPostHandshakeAuthWith
Instances
TLSParams ClientParams # | |
Defined in Network.TLS.Context Methods getTLSCommonParams :: ClientParams -> CommonParams getTLSRole :: ClientParams -> Role doHandshake :: ClientParams -> Context -> IO () doHandshakeWith :: ClientParams -> Context -> Handshake -> IO () doRequestCertificate :: ClientParams -> Context -> IO Bool doPostHandshakeAuthWith :: ClientParams -> Context -> Handshake13 -> IO () | |
TLSParams ServerParams # | |
Defined in Network.TLS.Context Methods getTLSCommonParams :: ServerParams -> CommonParams getTLSRole :: ServerParams -> Role doHandshake :: ServerParams -> Context -> IO () doHandshakeWith :: ServerParams -> Context -> Handshake -> IO () doRequestCertificate :: ServerParams -> Context -> IO Bool doPostHandshakeAuthWith :: ServerParams -> Context -> Handshake13 -> IO () |
data ClientParams #
Constructors
ClientParams | |
Fields
|
Instances
Show ClientParams # | |
Defined in Network.TLS.Parameters Methods showsPrec :: Int -> ClientParams -> ShowS # show :: ClientParams -> String # showList :: [ClientParams] -> ShowS # | |
TLSParams ClientParams # | |
Defined in Network.TLS.Context Methods getTLSCommonParams :: ClientParams -> CommonParams getTLSRole :: ClientParams -> Role doHandshake :: ClientParams -> Context -> IO () doHandshakeWith :: ClientParams -> Context -> Handshake -> IO () doRequestCertificate :: ClientParams -> Context -> IO Bool doPostHandshakeAuthWith :: ClientParams -> Context -> Handshake13 -> IO () |
defaultParamsClient :: HostName -> ByteString -> ClientParams #
data ServerParams #
Constructors
ServerParams | |
Fields
|
Instances
Show ServerParams # | |
Defined in Network.TLS.Parameters Methods showsPrec :: Int -> ServerParams -> ShowS # show :: ServerParams -> String # showList :: [ServerParams] -> ShowS # | |
Default ServerParams # | |
Defined in Network.TLS.Parameters Methods def :: ServerParams # | |
TLSParams ServerParams # | |
Defined in Network.TLS.Context Methods getTLSCommonParams :: ServerParams -> CommonParams getTLSRole :: ServerParams -> Role doHandshake :: ServerParams -> Context -> IO () doHandshakeWith :: ServerParams -> Context -> Handshake -> IO () doRequestCertificate :: ServerParams -> Context -> IO Bool doPostHandshakeAuthWith :: ServerParams -> Context -> Handshake13 -> IO () |
Shared
Parameters that are common to clients and servers.
Constructors
Shared | |
Fields
|
Instances
Hooks
data ClientHooks #
A set of callbacks run by the clients for various corners of TLS establishment
Constructors
ClientHooks | |
Fields
|
Instances
Show ClientHooks # | |
Defined in Network.TLS.Parameters Methods showsPrec :: Int -> ClientHooks -> ShowS # show :: ClientHooks -> String # showList :: [ClientHooks] -> ShowS # | |
Default ClientHooks # | |
Defined in Network.TLS.Parameters Methods def :: ClientHooks # |
type OnCertificateRequest = ([CertificateType], Maybe [HashAndSignatureAlgorithm], [DistinguishedName]) -> IO (Maybe (CertificateChain, PrivKey)) #
Type for onCertificateRequest
. This type synonym is to make
document readable.
type OnServerCertificate = CertificateStore -> ValidationCache -> ServiceID -> CertificateChain -> IO [FailedReason] #
Type for onServerCertificate
. This type synonym is to make
document readable.
data ServerHooks #
A set of callbacks run by the server for various corners of the TLS establishment
Constructors
ServerHooks | |
Fields
|
Instances
Show ServerHooks # | |
Defined in Network.TLS.Parameters Methods showsPrec :: Int -> ServerHooks -> ShowS # show :: ServerHooks -> String # showList :: [ServerHooks] -> ShowS # | |
Default ServerHooks # | |
Defined in Network.TLS.Parameters Methods def :: ServerHooks # |
data Measurement #
record some data about this connection.
Constructors
Measurement | |
Fields
|
Instances
Show Measurement # | |
Defined in Network.TLS.Measurement Methods showsPrec :: Int -> Measurement -> ShowS # show :: Measurement -> String # showList :: [Measurement] -> ShowS # | |
Eq Measurement # | |
Defined in Network.TLS.Measurement |
Supported
List all the supported algorithms, versions, ciphers, etc supported.
Constructors
Supported | |
Fields
|
Debug parameters
data DebugParams #
All settings should not be used in production
Constructors
DebugParams | |
Fields
|
Instances
Show DebugParams # | |
Defined in Network.TLS.Parameters Methods showsPrec :: Int -> DebugParams -> ShowS # show :: DebugParams -> String # showList :: [DebugParams] -> ShowS # | |
Default DebugParams # | |
Defined in Network.TLS.Parameters Methods def :: DebugParams # |
Shared parameters
Credentials
newtype Credentials #
Constructors
Credentials [Credential] |
Instances
Monoid Credentials # | |
Defined in Network.TLS.Credentials Methods mempty :: Credentials # mappend :: Credentials -> Credentials -> Credentials # mconcat :: [Credentials] -> Credentials # | |
Semigroup Credentials # | |
Defined in Network.TLS.Credentials Methods (<>) :: Credentials -> Credentials -> Credentials # sconcat :: NonEmpty Credentials -> Credentials # stimes :: Integral b => b -> Credentials -> Credentials # | |
Show Credentials # | |
Defined in Network.TLS.Credentials Methods showsPrec :: Int -> Credentials -> ShowS # show :: Credentials -> String # showList :: [Credentials] -> ShowS # |
type Credential = (CertificateChain, PrivKey) #
Arguments
:: FilePath | public certificate (X.509 format) |
-> FilePath | private key associated |
-> IO (Either String Credential) |
try to create a new credential object from a public certificate and the associated private key that are stored on the filesystem in PEM format.
credentialLoadX509FromMemory :: ByteString -> ByteString -> Either String Credential #
similar to credentialLoadX509
but take the certificate
and private key from memory instead of from the filesystem.
Arguments
:: FilePath | public certificate (X.509 format) |
-> [FilePath] | chain certificates (X.509 format) |
-> FilePath | private key associated |
-> IO (Either String Credential) |
similar to credentialLoadX509
but also allow specifying chain
certificates.
credentialLoadX509ChainFromMemory :: ByteString -> [ByteString] -> ByteString -> Either String Credential #
similar to credentialLoadX509FromMemory
but also allow
specifying chain certificates.
Session manager
data SessionManager #
A session manager
Constructors
SessionManager | |
Fields
|
noSessionManager :: SessionManager #
The session manager to do nothing.
type SessionID = ByteString #
A session ID
type SessionIDorTicket = ByteString #
Identity
type Ticket = ByteString #
Encrypted session ticket (encrypt(encode SessionData
)).
data SessionData #
Session data to resume
Constructors
Instances
data SessionFlag #
Some session flags
Constructors
SessionEMS | Session created with Extended Main Secret |
Instances
Enum SessionFlag # | |||||
Defined in Network.TLS.Types Methods succ :: SessionFlag -> SessionFlag # pred :: SessionFlag -> SessionFlag # toEnum :: Int -> SessionFlag # fromEnum :: SessionFlag -> Int # enumFrom :: SessionFlag -> [SessionFlag] # enumFromThen :: SessionFlag -> SessionFlag -> [SessionFlag] # enumFromTo :: SessionFlag -> SessionFlag -> [SessionFlag] # enumFromThenTo :: SessionFlag -> SessionFlag -> SessionFlag -> [SessionFlag] # | |||||
Generic SessionFlag # | |||||
Defined in Network.TLS.Types Associated Types
| |||||
Show SessionFlag # | |||||
Defined in Network.TLS.Types Methods showsPrec :: Int -> SessionFlag -> ShowS # show :: SessionFlag -> String # showList :: [SessionFlag] -> ShowS # | |||||
Eq SessionFlag # | |||||
Defined in Network.TLS.Types | |||||
Serialise SessionFlag # | |||||
Defined in Network.TLS.Types Methods encode :: SessionFlag -> Encoding # decode :: Decoder s SessionFlag # encodeList :: [SessionFlag] -> Encoding # decodeList :: Decoder s [SessionFlag] # | |||||
type Rep SessionFlag # | |||||
data TLS13TicketInfo #
Instances
Generic TLS13TicketInfo # | |||||
Defined in Network.TLS.Types Associated Types
Methods from :: TLS13TicketInfo -> Rep TLS13TicketInfo x # to :: Rep TLS13TicketInfo x -> TLS13TicketInfo # | |||||
Show TLS13TicketInfo # | |||||
Defined in Network.TLS.Types Methods showsPrec :: Int -> TLS13TicketInfo -> ShowS # show :: TLS13TicketInfo -> String # showList :: [TLS13TicketInfo] -> ShowS # | |||||
Eq TLS13TicketInfo # | |||||
Defined in Network.TLS.Types Methods (==) :: TLS13TicketInfo -> TLS13TicketInfo -> Bool # (/=) :: TLS13TicketInfo -> TLS13TicketInfo -> Bool # | |||||
Serialise TLS13TicketInfo # | |||||
Defined in Network.TLS.Types Methods encode :: TLS13TicketInfo -> Encoding # decode :: Decoder s TLS13TicketInfo # encodeList :: [TLS13TicketInfo] -> Encoding # decodeList :: Decoder s [TLS13TicketInfo] # | |||||
type Rep TLS13TicketInfo # | |||||
Defined in Network.TLS.Types |
Validation Cache
data ValidationCache #
All the callbacks needed for querying and adding to the cache.
Constructors
ValidationCache | |
Fields
|
Instances
Default ValidationCache | |
Defined in Data.X509.Validation.Cache Methods def :: ValidationCache # |
type ValidationCacheQueryCallback #
Arguments
= ServiceID | connection's identification |
-> Fingerprint | fingerprint of the leaf certificate |
-> Certificate | leaf certificate |
-> IO ValidationCacheResult | return if the operation is succesful or not |
Validation cache query callback type
type ValidationCacheAddCallback #
Arguments
= ServiceID | connection's identification |
-> Fingerprint | fingerprint of the leaf certificate |
-> Certificate | leaf certificate |
-> IO () |
Validation cache callback type
data ValidationCacheResult #
The result of a cache query
Constructors
ValidationCachePass | cache allow this fingerprint to go through |
ValidationCacheDenied String | cache denied this fingerprint for further validation |
ValidationCacheUnknown | unknown fingerprint in cache |
Instances
Show ValidationCacheResult | |
Defined in Data.X509.Validation.Cache Methods showsPrec :: Int -> ValidationCacheResult -> ShowS # show :: ValidationCacheResult -> String # showList :: [ValidationCacheResult] -> ShowS # | |
Eq ValidationCacheResult | |
Defined in Data.X509.Validation.Cache Methods (==) :: ValidationCacheResult -> ValidationCacheResult -> Bool # (/=) :: ValidationCacheResult -> ValidationCacheResult -> Bool # |
exceptionValidationCache :: [(ServiceID, Fingerprint)] -> ValidationCache #
create a simple constant cache that list exceptions to the certification validation. Typically this is use to allow self-signed certificates for specific use, with out-of-bounds user checks.
No fingerprints will be added after the instance is created.
The underlying structure for the check is kept as a list, as usually the exception list will be short, but when the list go above a dozen exceptions it's recommended to use another cache mechanism with a faster lookup mechanism (hashtable, map, etc).
Note that only one fingerprint is allowed per ServiceID, for other use, another cache mechanism need to be use.
Types
For Supported
Versions known to TLS
Bundled Patterns
pattern TLS12 :: Version | |
pattern TLS13 :: Version | |
pattern SSL2 :: Version | |
pattern SSL3 :: Version | |
pattern TLS10 :: Version | |
pattern TLS11 :: Version |
data Compression #
every compression need to be wrapped in this, to fit in structure
Constructors
CompressionC a => Compression a |
Instances
Show Compression # | |
Defined in Network.TLS.Compression Methods showsPrec :: Int -> Compression -> ShowS # show :: Compression -> String # showList :: [Compression] -> ShowS # | |
Eq Compression # | |
Defined in Network.TLS.Compression |
nullCompression :: Compression #
default null compression
newtype HashAlgorithm #
Constructors
HashAlgorithm | |
Fields |
Bundled Patterns
pattern HashMD5 :: HashAlgorithm | |
pattern HashSHA1 :: HashAlgorithm | |
pattern HashSHA224 :: HashAlgorithm | |
pattern HashSHA256 :: HashAlgorithm | |
pattern HashSHA384 :: HashAlgorithm | |
pattern HashSHA512 :: HashAlgorithm | |
pattern HashNone :: HashAlgorithm | |
pattern HashIntrinsic :: HashAlgorithm |
Instances
Show HashAlgorithm # | |
Defined in Network.TLS.Struct Methods showsPrec :: Int -> HashAlgorithm -> ShowS # show :: HashAlgorithm -> String # showList :: [HashAlgorithm] -> ShowS # | |
Eq HashAlgorithm # | |
Defined in Network.TLS.Struct Methods (==) :: HashAlgorithm -> HashAlgorithm -> Bool # (/=) :: HashAlgorithm -> HashAlgorithm -> Bool # |
newtype SignatureAlgorithm #
Constructors
SignatureAlgorithm | |
Fields |
Bundled Patterns
pattern SignatureAnonymous :: SignatureAlgorithm | |
pattern SignatureRSA :: SignatureAlgorithm | |
pattern SignatureDSA :: SignatureAlgorithm | |
pattern SignatureECDSA :: SignatureAlgorithm | |
pattern SignatureRSApssRSAeSHA256 :: SignatureAlgorithm | |
pattern SignatureRSApssRSAeSHA384 :: SignatureAlgorithm | |
pattern SignatureRSApssRSAeSHA512 :: SignatureAlgorithm | |
pattern SignatureEd25519 :: SignatureAlgorithm | |
pattern SignatureEd448 :: SignatureAlgorithm | |
pattern SignatureRSApsspssSHA256 :: SignatureAlgorithm | |
pattern SignatureRSApsspssSHA384 :: SignatureAlgorithm | |
pattern SignatureRSApsspssSHA512 :: SignatureAlgorithm |
Instances
Show SignatureAlgorithm # | |
Defined in Network.TLS.Struct Methods showsPrec :: Int -> SignatureAlgorithm -> ShowS # show :: SignatureAlgorithm -> String # showList :: [SignatureAlgorithm] -> ShowS # | |
Eq SignatureAlgorithm # | |
Defined in Network.TLS.Struct Methods (==) :: SignatureAlgorithm -> SignatureAlgorithm -> Bool # (/=) :: SignatureAlgorithm -> SignatureAlgorithm -> Bool # |
Bundled Patterns
pattern P256 :: Group | |
pattern P384 :: Group | |
pattern P521 :: Group | |
pattern X25519 :: Group | |
pattern X448 :: Group | |
pattern FFDHE2048 :: Group | |
pattern FFDHE3072 :: Group | |
pattern FFDHE4096 :: Group | |
pattern FFDHE6144 :: Group | |
pattern FFDHE8192 :: Group |
supportedNamedGroups :: [Group] #
Client or server policy regarding Extended Main Secret
Constructors
NoEMS | Extended Main Secret is not used |
AllowEMS | Extended Main Secret is allowed |
RequireEMS | Extended Main Secret is required |
For parameters and hooks
type DHPublic = PublicNumber #
data GroupUsage #
Group usage callback possible return values.
Constructors
GroupUsageValid | usage of group accepted |
GroupUsageInsecure | usage of group provides insufficient security |
GroupUsageUnsupported String | usage of group rejected for other reason (specified as string) |
GroupUsageInvalidPublic | usage of group with an invalid public value |
Instances
Show GroupUsage # | |
Defined in Network.TLS.Parameters Methods showsPrec :: Int -> GroupUsage -> ShowS # show :: GroupUsage -> String # showList :: [GroupUsage] -> ShowS # | |
Eq GroupUsage # | |
Defined in Network.TLS.Parameters |
data CertificateUsage #
Certificate Usage callback possible returns values.
Constructors
CertificateUsageAccept | usage of certificate accepted |
CertificateUsageReject CertificateRejectReason | usage of certificate rejected |
Instances
Show CertificateUsage # | |
Defined in Network.TLS.X509 Methods showsPrec :: Int -> CertificateUsage -> ShowS # show :: CertificateUsage -> String # showList :: [CertificateUsage] -> ShowS # | |
Eq CertificateUsage # | |
Defined in Network.TLS.X509 Methods (==) :: CertificateUsage -> CertificateUsage -> Bool # (/=) :: CertificateUsage -> CertificateUsage -> Bool # |
data CertificateRejectReason #
Certificate and Chain rejection reason
Constructors
CertificateRejectExpired | |
CertificateRejectRevoked | |
CertificateRejectUnknownCA | |
CertificateRejectAbsent | |
CertificateRejectOther String |
Instances
Show CertificateRejectReason # | |
Defined in Network.TLS.X509 Methods showsPrec :: Int -> CertificateRejectReason -> ShowS # show :: CertificateRejectReason -> String # showList :: [CertificateRejectReason] -> ShowS # | |
Eq CertificateRejectReason # | |
Defined in Network.TLS.X509 Methods (==) :: CertificateRejectReason -> CertificateRejectReason -> Bool # (/=) :: CertificateRejectReason -> CertificateRejectReason -> Bool # |
newtype CertificateType #
Some of the IANA registered code points for CertificateType
are not
currently supported by the library. Nor should they be, they're are either
unwise, obsolete or both. There's no point in conveying these to the user
in the client certificate request callback. The request callback will be
filtered to exclude unsupported values. If the user cannot find a certificate
for a supported code point, we'll go ahead without a client certificate and
hope for the best, unless the user's callback decides to throw an exception.
Constructors
CertificateType | |
Fields |
Bundled Patterns
pattern CertificateType_RSA_Sign :: CertificateType | TLS10 and up, RFC5246 |
pattern CertificateType_DSA_Sign :: CertificateType | TLS10 and up, RFC5246 |
pattern CertificateType_ECDSA_Sign :: CertificateType | TLS10 and up, RFC8422 |
pattern CertificateType_Ed25519_Sign :: CertificateType | |
pattern CertificateType_Ed448_Sign :: CertificateType |
Instances
Show CertificateType # | |
Defined in Network.TLS.Struct Methods showsPrec :: Int -> CertificateType -> ShowS # show :: CertificateType -> String # showList :: [CertificateType] -> ShowS # | |
Eq CertificateType # | |
Defined in Network.TLS.Struct Methods (==) :: CertificateType -> CertificateType -> Bool # (/=) :: CertificateType -> CertificateType -> Bool # | |
Ord CertificateType # | |
Defined in Network.TLS.Struct Methods compare :: CertificateType -> CertificateType -> Ordering # (<) :: CertificateType -> CertificateType -> Bool # (<=) :: CertificateType -> CertificateType -> Bool # (>) :: CertificateType -> CertificateType -> Bool # (>=) :: CertificateType -> CertificateType -> Bool # max :: CertificateType -> CertificateType -> CertificateType # min :: CertificateType -> CertificateType -> CertificateType # |
Either a host name e.g., "haskell.org"
or a numeric host
address string consisting of a dotted decimal IPv4 address or an
IPv6 address e.g., "192.168.0.1"
.
data MaxFragmentEnum #
Constructors
MaxFragment512 | |
MaxFragment1024 | |
MaxFragment2048 | |
MaxFragment4096 |
Instances
Show MaxFragmentEnum # | |
Defined in Network.TLS.Extension Methods showsPrec :: Int -> MaxFragmentEnum -> ShowS # show :: MaxFragmentEnum -> String # showList :: [MaxFragmentEnum] -> ShowS # | |
Eq MaxFragmentEnum # | |
Defined in Network.TLS.Extension Methods (==) :: MaxFragmentEnum -> MaxFragmentEnum -> Bool # (/=) :: MaxFragmentEnum -> MaxFragmentEnum -> Bool # |
Advanced APIs
Backend
ctxBackend :: Context -> Backend #
return the backend object associated with this context
contextFlush :: Context -> IO () #
A shortcut for 'backendFlush . ctxBackend'.
contextClose :: Context -> IO () #
A shortcut for 'backendClose . ctxBackend'.
Information gathering
data Information #
Information related to a running context, e.g. current cipher
Constructors
Information | |
Fields
|
Instances
Show Information # | |
Defined in Network.TLS.Context.Internal Methods showsPrec :: Int -> Information -> ShowS # show :: Information -> String # showList :: [Information] -> ShowS # | |
Eq Information # | |
Defined in Network.TLS.Context.Internal |
contextGetInformation :: Context -> IO (Maybe Information) #
Information about the current context
data ClientRandom #
Instances
Show ClientRandom # | |
Defined in Network.TLS.Struct Methods showsPrec :: Int -> ClientRandom -> ShowS # show :: ClientRandom -> String # showList :: [ClientRandom] -> ShowS # | |
Eq ClientRandom # | |
Defined in Network.TLS.Struct |
data ServerRandom #
Instances
Show ServerRandom # | |
Defined in Network.TLS.Struct Methods showsPrec :: Int -> ServerRandom -> ShowS # show :: ServerRandom -> String # showList :: [ServerRandom] -> ShowS # | |
Eq ServerRandom # | |
Defined in Network.TLS.Struct |
data HandshakeMode13 #
Type to show which handshake mode is used in TLS 1.3.
Constructors
FullHandshake | Full handshake is used. |
HelloRetryRequest | Full handshake is used with hello retry request. |
PreSharedKey | Server authentication is skipped. |
RTT0 | Server authentication is skipped and early data is sent. |
Instances
Show HandshakeMode13 # | |
Defined in Network.TLS.Handshake.State Methods showsPrec :: Int -> HandshakeMode13 -> ShowS # show :: HandshakeMode13 -> String # showList :: [HandshakeMode13] -> ShowS # | |
Eq HandshakeMode13 # | |
Defined in Network.TLS.Handshake.State Methods (==) :: HandshakeMode13 -> HandshakeMode13 -> Bool # (/=) :: HandshakeMode13 -> HandshakeMode13 -> Bool # |
getClientCertificateChain :: Context -> IO (Maybe CertificateChain) #
Getting certificates from a client, if any. Note that the certificates are not sent by a client on resumption even if client authentication is required. So, this API would be replaced by the one which can treat both cases of full-negotiation and resumption.
Negotiated
getNegotiatedProtocol :: MonadIO m => Context -> m (Maybe ByteString) #
If the ALPN extensions have been used, this will return get the protocol agreed upon.
getClientSNI :: MonadIO m => Context -> m (Maybe HostName) #
If the Server Name Indication extension has been used, return the hostname specified by the client.
Post-handshake actions
data KeyUpdateRequest #
How to update keys in TLS 1.3
Instances
Show KeyUpdateRequest # | |
Defined in Network.TLS.Core Methods showsPrec :: Int -> KeyUpdateRequest -> ShowS # show :: KeyUpdateRequest -> String # showList :: [KeyUpdateRequest] -> ShowS # | |
Eq KeyUpdateRequest # | |
Defined in Network.TLS.Core Methods (==) :: KeyUpdateRequest -> KeyUpdateRequest -> Bool # (/=) :: KeyUpdateRequest -> KeyUpdateRequest -> Bool # |
requestCertificate :: Context -> IO Bool #
Post-handshake certificate request with TLS 1.3. Returns True
if the
request was possible, i.e. if TLS 1.3 is used and the remote client supports
post-handshake authentication.
getTLSUnique :: Context -> IO (Maybe ByteString) #
Getting the "tls-unique" channel binding for TLS 1.2 (RFC5929).
For TLS 1.3, Nothing
is returned.
supportedExtendedMainSecret
must be RequireEMS
But in general, it is highly recommended to upgrade to TLS 1.3
and use the "tls-exporter" channel binding via getTLSExporter
.
getTLSExporter :: Context -> IO (Maybe ByteString) #
Getting the "tls-exporter" channel binding for TLS 1.3 (RFC9266).
For TLS 1.2, Nothing
is returned.
getTLSServerEndPoint :: Context -> IO (Maybe ByteString) #
Getting the "tls-server-end-point" channel binding for TLS 1.2 (RFC5929). For 1.3, there is no specifications for how to create it. In this implementation, a certificate chain without extensions is hashed like TLS 1.2.
getFinished :: Context -> IO (Maybe VerifyData) #
Deprecated: Use getTLSUnique instead
Getting TLS Finished sent to peer.
getPeerFinished :: Context -> IO (Maybe VerifyData) #
Deprecated: Use getTLSUnique instead
Getting TLS Finished received from peer.
Modifying hooks in context
A collection of hooks actions.
Constructors
Hooks | |
Fields
|
Instances
data Handshake13 #
Instances
Show Handshake13 # | |
Defined in Network.TLS.Struct13 Methods showsPrec :: Int -> Handshake13 -> ShowS # show :: Handshake13 -> String # showList :: [Handshake13] -> ShowS # | |
Eq Handshake13 # | |
Defined in Network.TLS.Struct13 |
contextHookSetHandshake13Recv :: Context -> (Handshake13 -> IO Handshake13) -> IO () #
contextHookSetCertificateRecv :: Context -> (CertificateChain -> IO ()) -> IO () #
Hooks for logging
This is called when sending and receiving packets and IO
Constructors
Logging | |
Fields
|
Constructors
Header ProtocolType Version Word16 |
newtype ProtocolType #
Constructors
ProtocolType | |
Fields |
Bundled Patterns
pattern ProtocolType_ChangeCipherSpec :: ProtocolType | |
pattern ProtocolType_Alert :: ProtocolType | |
pattern ProtocolType_Handshake :: ProtocolType | |
pattern ProtocolType_AppData :: ProtocolType |
Instances
Show ProtocolType # | |
Defined in Network.TLS.Struct Methods showsPrec :: Int -> ProtocolType -> ShowS # show :: ProtocolType -> String # showList :: [ProtocolType] -> ShowS # | |
Eq ProtocolType # | |
Defined in Network.TLS.Struct |
contextHookSetLogging :: Context -> Logging -> IO () #
Errors and exceptions
Errors
TLSError that might be returned through the TLS stack.
Prior to version 1.8.0, this type had an Exception
instance.
In version 1.8.0, this instance was removed, and functions in
this library now only throw TLSException
.
Constructors
Error_Misc String | mainly for instance of Error |
Error_Protocol String AlertDescription | A fatal error condition was encountered at a low level. The elements of the tuple give (freeform text description, structured error description). |
Error_Protocol_Warning String AlertDescription | A non-fatal error condition was encountered at a low level at a low level. The elements of the tuple give (freeform text description, structured error description). |
Error_Certificate String | |
Error_HandshakePolicy String | handshake policy failed. |
Error_EOF | |
Error_Packet String | |
Error_Packet_unexpected String String | |
Error_Packet_Parsing String |
Constructors
RSAError Error | |
KxUnsupported |
newtype AlertDescription #
Constructors
AlertDescription | |
Fields |
Bundled Patterns
pattern DecodeError :: AlertDescription | |
pattern CloseNotify :: AlertDescription | |
pattern UnexpectedMessage :: AlertDescription | |
pattern BadRecordMac :: AlertDescription | |
pattern DecryptionFailed :: AlertDescription | |
pattern RecordOverflow :: AlertDescription | |
pattern DecompressionFailure :: AlertDescription | |
pattern HandshakeFailure :: AlertDescription | |
pattern BadCertificate :: AlertDescription | |
pattern UnsupportedCertificate :: AlertDescription | |
pattern CertificateRevoked :: AlertDescription | |
pattern CertificateExpired :: AlertDescription | |
pattern CertificateUnknown :: AlertDescription | |
pattern IllegalParameter :: AlertDescription | |
pattern UnknownCa :: AlertDescription | |
pattern AccessDenied :: AlertDescription | |
pattern DecryptError :: AlertDescription | |
pattern ExportRestriction :: AlertDescription | |
pattern ProtocolVersion :: AlertDescription | |
pattern InsufficientSecurity :: AlertDescription | |
pattern InternalError :: AlertDescription | |
pattern InappropriateFallback :: AlertDescription | |
pattern UserCanceled :: AlertDescription | |
pattern NoRenegotiation :: AlertDescription | |
pattern MissingExtension :: AlertDescription | |
pattern UnsupportedExtension :: AlertDescription | |
pattern CertificateUnobtainable :: AlertDescription | |
pattern UnrecognizedName :: AlertDescription | |
pattern BadCertificateStatusResponse :: AlertDescription | |
pattern BadCertificateHashValue :: AlertDescription | |
pattern UnknownPskIdentity :: AlertDescription | |
pattern CertificateRequired :: AlertDescription | |
pattern NoApplicationProtocol :: AlertDescription |
Instances
Show AlertDescription # | |
Defined in Network.TLS.Struct Methods showsPrec :: Int -> AlertDescription -> ShowS # show :: AlertDescription -> String # showList :: [AlertDescription] -> ShowS # | |
Eq AlertDescription # | |
Defined in Network.TLS.Struct Methods (==) :: AlertDescription -> AlertDescription -> Bool # (/=) :: AlertDescription -> AlertDescription -> Bool # |
Exceptions
data TLSException #
TLS Exceptions. Some of the data constructors indicate incorrect use of
the library, and the documentation for those data constructors calls
this out. The others wrap TLSError
with some kind of context to explain
when the exception occurred.
Constructors
Terminated Bool String TLSError | Early termination exception with the reason and the error associated |
HandshakeFailed TLSError | Handshake failed for the reason attached. |
PostHandshake TLSError | Failure occurred while sending or receiving data after the TLS handshake succeeded. |
Uncontextualized TLSError | Lifts a |
ConnectionNotEstablished | Usage error when the connection has not been established and the user is trying to send or receive data. Indicates that this library has been used incorrectly. |
MissingHandshake | Expected that a TLS handshake had already taken place, but no TLS handshake had occurred. Indicates that this library has been used incorrectly. |
Instances
Exception TLSException # | |
Defined in Network.TLS.Struct Methods toException :: TLSException -> SomeException # fromException :: SomeException -> Maybe TLSException # displayException :: TLSException -> String # | |
Show TLSException # | |
Defined in Network.TLS.Struct Methods showsPrec :: Int -> TLSException -> ShowS # show :: TLSException -> String # showList :: [TLSException] -> ShowS # | |
Eq TLSException # | |
Defined in Network.TLS.Struct |
Raw types
Compressions class
class CompressionC a where #
supported compression algorithms need to be part of this class
Methods
compressionCID :: a -> CompressionID #
compressionCDeflate :: a -> ByteString -> (a, ByteString) #
compressionCInflate :: a -> ByteString -> (a, ByteString) #
type CompressionID = Word8 #
Compression identification
Crypto Key
Public key types known and used in X.509
Constructors
PubKeyRSA PublicKey | RSA public key |
PubKeyDSA PublicKey | DSA public key |
PubKeyDH (Integer, Integer, Integer, Maybe Integer, ([Word8], Integer)) | DH format with (p,g,q,j,(seed,pgenCounter)) |
PubKeyEC PubKeyEC | EC public key |
PubKeyX25519 PublicKey | X25519 public key |
PubKeyX448 PublicKey | X448 public key |
PubKeyEd25519 PublicKey | Ed25519 public key |
PubKeyEd448 PublicKey | Ed448 public key |
PubKeyUnknown OID ByteString | unrecognized format |
Private key types known and used in X.509
Constructors
PrivKeyRSA PrivateKey | RSA private key |
PrivKeyDSA PrivateKey | DSA private key |
PrivKeyEC PrivKeyEC | EC private key |
PrivKeyX25519 SecretKey | X25519 private key |
PrivKeyX448 SecretKey | X448 private key |
PrivKeyEd25519 SecretKey | Ed25519 private key |
PrivKeyEd448 SecretKey | Ed448 private key |
Ciphers & Predefined ciphers
Cipher algorithm
Constructors
Cipher | |
Fields
|
data CipherKeyExchangeType #
Constructors
CipherKeyExchange_RSA | |
CipherKeyExchange_DH_Anon | |
CipherKeyExchange_DHE_RSA | |
CipherKeyExchange_ECDHE_RSA | |
CipherKeyExchange_DHE_DSA | |
CipherKeyExchange_DH_DSA | |
CipherKeyExchange_DH_RSA | |
CipherKeyExchange_ECDH_ECDSA | |
CipherKeyExchange_ECDH_RSA | |
CipherKeyExchange_ECDHE_ECDSA | |
CipherKeyExchange_TLS13 |
Instances
Show CipherKeyExchangeType # | |
Defined in Network.TLS.Cipher Methods showsPrec :: Int -> CipherKeyExchangeType -> ShowS # show :: CipherKeyExchangeType -> String # showList :: [CipherKeyExchangeType] -> ShowS # | |
Eq CipherKeyExchangeType # | |
Defined in Network.TLS.Cipher Methods (==) :: CipherKeyExchangeType -> CipherKeyExchangeType -> Bool # (/=) :: CipherKeyExchangeType -> CipherKeyExchangeType -> Bool # |
Constructors
Bulk | |
Fields
|
data BulkFunctions #
Constructors
BulkBlockF (BulkDirection -> BulkKey -> BulkBlock) | |
BulkStreamF (BulkDirection -> BulkKey -> BulkStream) | |
BulkAeadF (BulkDirection -> BulkKey -> BulkAEAD) |
data BulkDirection #
Constructors
BulkEncrypt | |
BulkDecrypt |
Instances
Show BulkDirection # | |
Defined in Network.TLS.Cipher Methods showsPrec :: Int -> BulkDirection -> ShowS # show :: BulkDirection -> String # showList :: [BulkDirection] -> ShowS # | |
Eq BulkDirection # | |
Defined in Network.TLS.Cipher Methods (==) :: BulkDirection -> BulkDirection -> Bool # (/=) :: BulkDirection -> BulkDirection -> Bool # |
newtype BulkStream #
Constructors
BulkStream (ByteString -> (ByteString, BulkStream)) |
type BulkBlock = BulkIV -> ByteString -> (ByteString, BulkIV) #
type BulkAEAD = BulkNonce -> ByteString -> BulkAdditionalData -> (ByteString, AuthTag) #
cipherKeyBlockSize :: Cipher -> Int #
type BulkKey = ByteString #
type BulkIV = ByteString #
type BulkNonce = ByteString #
type BulkAdditionalData = ByteString #
cipherAllowedForVersion :: Version -> Cipher -> Bool #
Check if a specific Cipher
is allowed to be used
with the version specified
hasMAC :: BulkFunctions -> Bool #
hasRecordIV :: BulkFunctions -> Bool #
Deprecated
recvData' :: MonadIO m => Context -> m ByteString #
Deprecated: use recvData that returns strict bytestring
same as recvData but returns a lazy bytestring.
type Bytes = ByteString #
Deprecated: Use Data.ByteString.Bytestring instead of Bytes.
data ValidationChecks #
A set of checks to activate or parametrize to perform on certificates.
It's recommended to use defaultChecks
to create the structure,
to better cope with future changes or expansion of the structure.
Constructors
ValidationChecks | |
Fields
|
Instances
Show ValidationChecks | |
Defined in Data.X509.Validation Methods showsPrec :: Int -> ValidationChecks -> ShowS # show :: ValidationChecks -> String # showList :: [ValidationChecks] -> ShowS # | |
Default ValidationChecks | |
Defined in Data.X509.Validation Methods def :: ValidationChecks # | |
Eq ValidationChecks | |
Defined in Data.X509.Validation Methods (==) :: ValidationChecks -> ValidationChecks -> Bool # (/=) :: ValidationChecks -> ValidationChecks -> Bool # |
data ValidationHooks #
A set of hooks to manipulate the way the verification works.
BEWARE, it's easy to change behavior leading to compromised security.
Constructors
ValidationHooks | |
Fields
|
Instances
Default ValidationHooks | |
Defined in Data.X509.Validation Methods def :: ValidationHooks # |