License | BSD-style |
---|---|
Maintainer | Vincent Hanquez <vincent@snarc.org> |
Stability | experimental |
Portability | unknown |
Safe Haskell | None |
Language | Haskell98 |
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
- clientEarlyData :: Maybe ByteString
- defaultParamsClient :: HostName -> ByteString -> ClientParams
- data ServerParams = ServerParams {}
- data Supported = Supported {
- supportedVersions :: [Version]
- supportedCiphers :: [Cipher]
- supportedCompressions :: [Compression]
- supportedHashSignatures :: [HashAndSignatureAlgorithm]
- supportedSecureRenegotiation :: Bool
- supportedClientInitiatedRenegotiation :: Bool
- supportedSession :: Bool
- supportedFallbackScsv :: Bool
- supportedEmptyPacket :: Bool
- supportedGroups :: [Group]
- data Shared = Shared {}
- data DebugParams = DebugParams {
- debugSeed :: Maybe Seed
- debugPrintSeed :: Seed -> IO ()
- debugVersionForced :: Maybe Version
- debugKeyLogger :: String -> IO ()
- 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)
- 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
- type SessionID = ByteString
- data SessionData = SessionData {}
- data SessionManager = SessionManager {
- sessionResume :: SessionID -> IO (Maybe SessionData)
- sessionResumeOnlyOnce :: SessionID -> IO (Maybe SessionData)
- sessionEstablish :: SessionID -> SessionData -> IO ()
- sessionInvalidate :: SessionID -> IO ()
- noSessionManager :: SessionManager
- data TLS13TicketInfo
- data Hooks = Hooks {
- hookRecvHandshake :: Handshake -> IO Handshake
- hookRecvHandshake13 :: Handshake13 -> IO Handshake13
- hookRecvCertificates :: CertificateChain -> IO ()
- hookLogging :: Logging
- data Handshake
- data Logging = Logging {
- loggingPacketSent :: String -> IO ()
- loggingPacketRecv :: String -> IO ()
- loggingIOSent :: ByteString -> IO ()
- loggingIORecv :: Header -> ByteString -> IO ()
- contextHookSetHandshakeRecv :: Context -> (Handshake -> IO Handshake) -> IO ()
- contextHookSetHandshake13Recv :: Context -> (Handshake13 -> IO Handshake13) -> IO ()
- contextHookSetCertificateRecv :: Context -> (CertificateChain -> IO ()) -> IO ()
- contextHookSetLogging :: Context -> Logging -> IO ()
- contextModifyHooks :: Context -> (Hooks -> Hooks) -> IO ()
- type HostName = String
- type DHParams = Params
- type DHPublic = PublicNumber
- data Measurement = Measurement {
- nbHandshakes :: !Word32
- bytesReceived :: !Word32
- bytesSent :: !Word32
- data GroupUsage
- data CertificateUsage
- data CertificateRejectReason
- data MaxFragmentEnum
- type HashAndSignatureAlgorithm = (HashAlgorithm, SignatureAlgorithm)
- data HashAlgorithm
- data SignatureAlgorithm
- data CertificateType
- = CertificateType_RSA_Sign
- | CertificateType_DSS_Sign
- | CertificateType_ECDSA_Sign
- | CertificateType_Ed25519_Sign
- | CertificateType_Ed448_Sign
- | CertificateType_RSA_Fixed_DH
- | CertificateType_DSS_Fixed_DH
- | CertificateType_RSA_Ephemeral_DH
- | CertificateType_DSS_Ephemeral_DH
- | CertificateType_fortezza_dms
- | CertificateType_RSA_Fixed_ECDH
- | CertificateType_ECDSA_Fixed_ECDH
- | CertificateType_Unknown Word8
- data ValidationChecks = ValidationChecks {}
- data ValidationHooks = ValidationHooks {
- hookMatchSubjectIssuer :: DistinguishedName -> Certificate -> Bool
- hookValidateTime :: DateTime -> Certificate -> [FailedReason]
- hookValidateName :: HostName -> Certificate -> [FailedReason]
- hookFilterReason :: [FailedReason] -> [FailedReason]
- data ValidationCache = ValidationCache {}
- data ValidationCacheResult
- exceptionValidationCache :: [(ServiceID, Fingerprint)] -> ValidationCache
- ctxConnection :: Context -> Backend
- contextFlush :: Context -> IO ()
- contextClose :: Context -> IO ()
- data Information = Information {}
- contextGetInformation :: Context -> IO (Maybe Information)
- data ClientRandom
- data ServerRandom
- unClientRandom :: ClientRandom -> ByteString
- unServerRandom :: ServerRandom -> ByteString
- getNegotiatedProtocol :: MonadIO m => Context -> m (Maybe ByteString)
- getClientSNI :: MonadIO m => Context -> m (Maybe HostName)
- updateKey :: MonadIO m => Context -> KeyUpdateRequest -> m Bool
- data KeyUpdateRequest
- requestCertificate :: MonadIO m => Context -> m Bool
- data ProtocolType
- data Header = Header ProtocolType Version Word16
- data Version
- data Compression = CompressionC a => Compression a
- class CompressionC a where
- compressionCID :: a -> CompressionID
- compressionCDeflate :: a -> ByteString -> (a, ByteString)
- compressionCInflate :: a -> ByteString -> (a, ByteString)
- nullCompression :: Compression
- type CompressionID = Word8
- 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
- data Hash
- data Cipher = Cipher {}
- 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
- data PubKey
- data PrivKey
- data Group
- data HandshakeMode13
- data TLSError
- data KxError
- data AlertDescription
- = CloseNotify
- | UnexpectedMessage
- | BadRecordMac
- | DecryptionFailed
- | RecordOverflow
- | DecompressionFailure
- | HandshakeFailure
- | BadCertificate
- | UnsupportedCertificate
- | CertificateRevoked
- | CertificateExpired
- | CertificateUnknown
- | IllegalParameter
- | UnknownCa
- | AccessDenied
- | DecodeError
- | DecryptError
- | ExportRestriction
- | ProtocolVersion
- | InsufficientSecurity
- | InternalError
- | InappropriateFallback
- | UserCanceled
- | NoRenegotiation
- | MissingExtension
- | UnsupportedExtension
- | CertificateUnobtainable
- | UnrecognizedName
- | BadCertificateStatusResponse
- | BadCertificateHashValue
- | UnknownPskIdentity
- | CertificateRequired
- | NoApplicationProtocol
- data TLSException
- recvData' :: MonadIO m => Context -> m ByteString
- contextNewOnHandle :: (MonadIO m, TLSParams params) => Handle -> params -> m Context
- contextNewOnSocket :: (MonadIO m, TLSParams params) => Socket -> params -> m Context
- type Bytes = ByteString
Basic APIs
:: (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 () Source #
Handshake for a new TLS connection This is to be called at the beginning of a connection, and during renegotiation
sendData :: MonadIO m => Context -> ByteString -> m () Source #
sendData sends a bunch of data. It will automatically chunk data to acceptable packet size
recvData :: MonadIO m => Context -> m ByteString Source #
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 () Source #
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
Backend abstraction
class HasBackend a where Source #
initializeBackend :: a -> IO () Source #
getBackend :: a -> Backend Source #
Instances
HasBackend Handle Source # | |
Defined in Network.TLS.Backend initializeBackend :: Handle -> IO () Source # getBackend :: Handle -> Backend Source # | |
HasBackend Socket Source # | |
Defined in Network.TLS.Backend initializeBackend :: Socket -> IO () Source # getBackend :: Socket -> Backend Source # | |
HasBackend Backend Source # | |
Defined in Network.TLS.Backend initializeBackend :: Backend -> IO () Source # getBackend :: Backend -> Backend Source # |
Connection IO backend
Backend | |
|
Instances
HasBackend Backend Source # | |
Defined in Network.TLS.Backend initializeBackend :: Backend -> IO () Source # getBackend :: Backend -> Backend Source # |
Context configuration
Parameters
getTLSCommonParams, getTLSRole, doHandshake, doHandshakeWith, doRequestCertificate, doPostHandshakeAuthWith
Instances
TLSParams ServerParams Source # | |
Defined in Network.TLS.Context 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 () | |
TLSParams ClientParams Source # | |
Defined in Network.TLS.Context 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 () |
data ClientParams Source #
ClientParams | |
|
Instances
Show ClientParams Source # | |
Defined in Network.TLS.Parameters showsPrec :: Int -> ClientParams -> ShowS # show :: ClientParams -> String # showList :: [ClientParams] -> ShowS # | |
TLSParams ClientParams Source # | |
Defined in Network.TLS.Context 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 Source #
data ServerParams Source #
ServerParams | |
|
Instances
Show ServerParams Source # | |
Defined in Network.TLS.Parameters showsPrec :: Int -> ServerParams -> ShowS # show :: ServerParams -> String # showList :: [ServerParams] -> ShowS # | |
Default ServerParams Source # | |
Defined in Network.TLS.Parameters def :: ServerParams # | |
TLSParams ServerParams Source # | |
Defined in Network.TLS.Context 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 () |
Supported
List all the supported algorithms, versions, ciphers, etc supported.
Supported | |
|
Shared
Parameters that are common to clients and servers.
Shared | |
|
Debug parameters
data DebugParams Source #
All settings should not be used in production
DebugParams | |
|
Instances
Show DebugParams Source # | |
Defined in Network.TLS.Parameters showsPrec :: Int -> DebugParams -> ShowS # show :: DebugParams -> String # showList :: [DebugParams] -> ShowS # | |
Default DebugParams Source # | |
Defined in Network.TLS.Parameters def :: DebugParams # |
Client Server Hooks
data ClientHooks Source #
A set of callbacks run by the clients for various corners of TLS establishment
ClientHooks | |
|
Instances
Show ClientHooks Source # | |
Defined in Network.TLS.Parameters showsPrec :: Int -> ClientHooks -> ShowS # show :: ClientHooks -> String # showList :: [ClientHooks] -> ShowS # | |
Default ClientHooks Source # | |
Defined in Network.TLS.Parameters def :: ClientHooks # |
type OnCertificateRequest = ([CertificateType], Maybe [HashAndSignatureAlgorithm], [DistinguishedName]) -> IO (Maybe (CertificateChain, PrivKey)) Source #
Type for onCertificateRequest
. This type synonym is to make
document readable.
type OnServerCertificate = CertificateStore -> ValidationCache -> ServiceID -> CertificateChain -> IO [FailedReason] Source #
Type for onServerCertificate
. This type synonym is to make
document readable.
data ServerHooks Source #
A set of callbacks run by the server for various corners of the TLS establishment
ServerHooks | |
|
Instances
Show ServerHooks Source # | |
Defined in Network.TLS.Parameters showsPrec :: Int -> ServerHooks -> ShowS # show :: ServerHooks -> String # showList :: [ServerHooks] -> ShowS # | |
Default ServerHooks Source # | |
Defined in Network.TLS.Parameters def :: ServerHooks # |
Credentials
newtype Credentials Source #
Instances
Semigroup Credentials Source # | |
Defined in Network.TLS.Credentials (<>) :: Credentials -> Credentials -> Credentials # sconcat :: NonEmpty Credentials -> Credentials # stimes :: Integral b => b -> Credentials -> Credentials # | |
Monoid Credentials Source # | |
Defined in Network.TLS.Credentials mempty :: Credentials # mappend :: Credentials -> Credentials -> Credentials # mconcat :: [Credentials] -> Credentials # |
type Credential = (CertificateChain, PrivKey) Source #
:: 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 Source #
similar to credentialLoadX509
but take the certificate
and private key from memory instead of from the filesystem.
credentialLoadX509Chain Source #
:: 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 Source #
similar to credentialLoadX509FromMemory
but also allow
specifying chain certificates.
Session
type SessionID = ByteString Source #
A session ID
data SessionData Source #
Session data to resume
Instances
Eq SessionData Source # | |
Defined in Network.TLS.Types (==) :: SessionData -> SessionData -> Bool # (/=) :: SessionData -> SessionData -> Bool # | |
Show SessionData Source # | |
Defined in Network.TLS.Types showsPrec :: Int -> SessionData -> ShowS # show :: SessionData -> String # showList :: [SessionData] -> ShowS # |
data SessionManager Source #
A session manager
SessionManager | |
|
data TLS13TicketInfo Source #
Instances
Eq TLS13TicketInfo Source # | |
Defined in Network.TLS.Types (==) :: TLS13TicketInfo -> TLS13TicketInfo -> Bool # (/=) :: TLS13TicketInfo -> TLS13TicketInfo -> Bool # | |
Show TLS13TicketInfo Source # | |
Defined in Network.TLS.Types showsPrec :: Int -> TLS13TicketInfo -> ShowS # show :: TLS13TicketInfo -> String # showList :: [TLS13TicketInfo] -> ShowS # |
Hooks
A collection of hooks actions.
Hooks | |
|
Hooks for logging
This is called when sending and receiving packets and IO
Logging | |
|
contextHookSetCertificateRecv :: Context -> (CertificateChain -> IO ()) -> IO () Source #
Misc
type DHPublic = PublicNumber Source #
data Measurement Source #
record some data about this connection.
Measurement | |
|
Instances
Eq Measurement Source # | |
Defined in Network.TLS.Measurement (==) :: Measurement -> Measurement -> Bool # (/=) :: Measurement -> Measurement -> Bool # | |
Show Measurement Source # | |
Defined in Network.TLS.Measurement showsPrec :: Int -> Measurement -> ShowS # show :: Measurement -> String # showList :: [Measurement] -> ShowS # |
data GroupUsage Source #
Group usage callback possible return values.
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
Eq GroupUsage Source # | |
Defined in Network.TLS.Parameters (==) :: GroupUsage -> GroupUsage -> Bool # (/=) :: GroupUsage -> GroupUsage -> Bool # | |
Show GroupUsage Source # | |
Defined in Network.TLS.Parameters showsPrec :: Int -> GroupUsage -> ShowS # show :: GroupUsage -> String # showList :: [GroupUsage] -> ShowS # |
data CertificateUsage Source #
Certificate Usage callback possible returns values.
CertificateUsageAccept | usage of certificate accepted |
CertificateUsageReject CertificateRejectReason | usage of certificate rejected |
Instances
Eq CertificateUsage Source # | |
Defined in Network.TLS.X509 (==) :: CertificateUsage -> CertificateUsage -> Bool # (/=) :: CertificateUsage -> CertificateUsage -> Bool # | |
Show CertificateUsage Source # | |
Defined in Network.TLS.X509 showsPrec :: Int -> CertificateUsage -> ShowS # show :: CertificateUsage -> String # showList :: [CertificateUsage] -> ShowS # |
data CertificateRejectReason Source #
Certificate and Chain rejection reason
CertificateRejectExpired | |
CertificateRejectRevoked | |
CertificateRejectUnknownCA | |
CertificateRejectAbsent | |
CertificateRejectOther String |
Instances
Eq CertificateRejectReason Source # | |
Defined in Network.TLS.X509 | |
Show CertificateRejectReason Source # | |
Defined in Network.TLS.X509 showsPrec :: Int -> CertificateRejectReason -> ShowS # show :: CertificateRejectReason -> String # showList :: [CertificateRejectReason] -> ShowS # |
data MaxFragmentEnum Source #
Instances
Eq MaxFragmentEnum Source # | |
Defined in Network.TLS.Extension (==) :: MaxFragmentEnum -> MaxFragmentEnum -> Bool # (/=) :: MaxFragmentEnum -> MaxFragmentEnum -> Bool # | |
Show MaxFragmentEnum Source # | |
Defined in Network.TLS.Extension showsPrec :: Int -> MaxFragmentEnum -> ShowS # show :: MaxFragmentEnum -> String # showList :: [MaxFragmentEnum] -> ShowS # |
data HashAlgorithm Source #
Instances
Eq HashAlgorithm Source # | |
Defined in Network.TLS.Struct (==) :: HashAlgorithm -> HashAlgorithm -> Bool # (/=) :: HashAlgorithm -> HashAlgorithm -> Bool # | |
Show HashAlgorithm Source # | |
Defined in Network.TLS.Struct showsPrec :: Int -> HashAlgorithm -> ShowS # show :: HashAlgorithm -> String # showList :: [HashAlgorithm] -> ShowS # |
data SignatureAlgorithm Source #
Instances
Eq SignatureAlgorithm Source # | |
Defined in Network.TLS.Struct (==) :: SignatureAlgorithm -> SignatureAlgorithm -> Bool # (/=) :: SignatureAlgorithm -> SignatureAlgorithm -> Bool # | |
Show SignatureAlgorithm Source # | |
Defined in Network.TLS.Struct showsPrec :: Int -> SignatureAlgorithm -> ShowS # show :: SignatureAlgorithm -> String # showList :: [SignatureAlgorithm] -> ShowS # |
data CertificateType Source #
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.
CertificateType_RSA_Sign | TLS10 and up, RFC5246 |
CertificateType_DSS_Sign | TLS10 and up, RFC5246 |
CertificateType_ECDSA_Sign | TLS10 and up, RFC8422 |
CertificateType_Ed25519_Sign | TLS13 and up, synthetic |
CertificateType_Ed448_Sign | TLS13 and up, synthetic | None of the below will ever be presented to the callback. Any future public key algorithms valid for client certificates go above this line. |
CertificateType_RSA_Fixed_DH | |
CertificateType_DSS_Fixed_DH | |
CertificateType_RSA_Ephemeral_DH | |
CertificateType_DSS_Ephemeral_DH | |
CertificateType_fortezza_dms | |
CertificateType_RSA_Fixed_ECDH | |
CertificateType_ECDSA_Fixed_ECDH | |
CertificateType_Unknown Word8 |
Instances
Eq CertificateType Source # | |
Defined in Network.TLS.Struct (==) :: CertificateType -> CertificateType -> Bool # (/=) :: CertificateType -> CertificateType -> Bool # | |
Ord CertificateType Source # | |
Defined in Network.TLS.Struct compare :: CertificateType -> CertificateType -> Ordering # (<) :: CertificateType -> CertificateType -> Bool # (<=) :: CertificateType -> CertificateType -> Bool # (>) :: CertificateType -> CertificateType -> Bool # (>=) :: CertificateType -> CertificateType -> Bool # max :: CertificateType -> CertificateType -> CertificateType # min :: CertificateType -> CertificateType -> CertificateType # | |
Show CertificateType Source # | |
Defined in Network.TLS.Struct showsPrec :: Int -> CertificateType -> ShowS # show :: CertificateType -> String # showList :: [CertificateType] -> ShowS # |
X509
X509 Validation
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.
ValidationChecks | |
|
Instances
Eq ValidationChecks | |
Defined in Data.X509.Validation (==) :: ValidationChecks -> ValidationChecks -> Bool # (/=) :: ValidationChecks -> ValidationChecks -> Bool # | |
Show ValidationChecks | |
Defined in Data.X509.Validation showsPrec :: Int -> ValidationChecks -> ShowS # show :: ValidationChecks -> String # showList :: [ValidationChecks] -> ShowS # | |
Default ValidationChecks | |
Defined in Data.X509.Validation def :: ValidationChecks # |
data ValidationHooks #
A set of hooks to manipulate the way the verification works.
BEWARE, it's easy to change behavior leading to compromised security.
ValidationHooks | |
|
Instances
Default ValidationHooks | |
Defined in Data.X509.Validation def :: ValidationHooks # |
X509 Validation Cache
data ValidationCache #
All the callbacks needed for querying and adding to the cache.
ValidationCache | |
|
Instances
Default ValidationCache | |
Defined in Data.X509.Validation.Cache def :: ValidationCache # |
data ValidationCacheResult #
The result of a cache query
ValidationCachePass | cache allow this fingerprint to go through |
ValidationCacheDenied String | cache denied this fingerprint for further validation |
ValidationCacheUnknown | unknown fingerprint in cache |
Instances
Eq ValidationCacheResult | |
Defined in Data.X509.Validation.Cache (==) :: ValidationCacheResult -> ValidationCacheResult -> Bool # (/=) :: ValidationCacheResult -> ValidationCacheResult -> Bool # | |
Show ValidationCacheResult | |
Defined in Data.X509.Validation.Cache showsPrec :: Int -> ValidationCacheResult -> ShowS # show :: ValidationCacheResult -> String # showList :: [ValidationCacheResult] -> ShowS # |
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.
APIs
Backend
ctxConnection :: Context -> Backend Source #
return the backend object associated with this context
contextFlush :: Context -> IO () Source #
A shortcut for 'backendFlush . ctxConnection'.
contextClose :: Context -> IO () Source #
A shortcut for 'backendClose . ctxConnection'.
Information gathering
data Information Source #
Information related to a running context, e.g. current cipher
Instances
Eq Information Source # | |
Defined in Network.TLS.Context.Internal (==) :: Information -> Information -> Bool # (/=) :: Information -> Information -> Bool # | |
Show Information Source # | |
Defined in Network.TLS.Context.Internal showsPrec :: Int -> Information -> ShowS # show :: Information -> String # showList :: [Information] -> ShowS # |
contextGetInformation :: Context -> IO (Maybe Information) Source #
Information about the current context
data ClientRandom Source #
Instances
Eq ClientRandom Source # | |
Defined in Network.TLS.Struct (==) :: ClientRandom -> ClientRandom -> Bool # (/=) :: ClientRandom -> ClientRandom -> Bool # | |
Show ClientRandom Source # | |
Defined in Network.TLS.Struct showsPrec :: Int -> ClientRandom -> ShowS # show :: ClientRandom -> String # showList :: [ClientRandom] -> ShowS # |
data ServerRandom Source #
Instances
Eq ServerRandom Source # | |
Defined in Network.TLS.Struct (==) :: ServerRandom -> ServerRandom -> Bool # (/=) :: ServerRandom -> ServerRandom -> Bool # | |
Show ServerRandom Source # | |
Defined in Network.TLS.Struct showsPrec :: Int -> ServerRandom -> ShowS # show :: ServerRandom -> String # showList :: [ServerRandom] -> ShowS # |
Negotiated
getNegotiatedProtocol :: MonadIO m => Context -> m (Maybe ByteString) Source #
If the ALPN extensions have been used, this will return get the protocol agreed upon.
getClientSNI :: MonadIO m => Context -> m (Maybe HostName) Source #
If the Server Name Indication extension has been used, return the hostname specified by the client.
Post-handshake actions
data KeyUpdateRequest Source #
How to update keys in TLS 1.3
Instances
Eq KeyUpdateRequest Source # | |
Defined in Network.TLS.Core (==) :: KeyUpdateRequest -> KeyUpdateRequest -> Bool # (/=) :: KeyUpdateRequest -> KeyUpdateRequest -> Bool # | |
Show KeyUpdateRequest Source # | |
Defined in Network.TLS.Core showsPrec :: Int -> KeyUpdateRequest -> ShowS # show :: KeyUpdateRequest -> String # showList :: [KeyUpdateRequest] -> ShowS # |
requestCertificate :: MonadIO m => Context -> m Bool Source #
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.
Raw types
data ProtocolType Source #
ProtocolType_ChangeCipherSpec | |
ProtocolType_Alert | |
ProtocolType_Handshake | |
ProtocolType_AppData | |
ProtocolType_DeprecatedHandshake |
Instances
Eq ProtocolType Source # | |
Defined in Network.TLS.Struct (==) :: ProtocolType -> ProtocolType -> Bool # (/=) :: ProtocolType -> ProtocolType -> Bool # | |
Show ProtocolType Source # | |
Defined in Network.TLS.Struct showsPrec :: Int -> ProtocolType -> ShowS # show :: ProtocolType -> String # showList :: [ProtocolType] -> ShowS # |
Versions known to TLS
SSL2 is just defined, but this version is and will not be supported.
Compressions & Predefined compressions
data Compression Source #
every compression need to be wrapped in this, to fit in structure
CompressionC a => Compression a |
Instances
Eq Compression Source # | |
Defined in Network.TLS.Compression (==) :: Compression -> Compression -> Bool # (/=) :: Compression -> Compression -> Bool # | |
Show Compression Source # | |
Defined in Network.TLS.Compression showsPrec :: Int -> Compression -> ShowS # show :: Compression -> String # showList :: [Compression] -> ShowS # |
class CompressionC a where Source #
supported compression algorithms need to be part of this class
compressionCID :: a -> CompressionID Source #
compressionCDeflate :: a -> ByteString -> (a, ByteString) Source #
compressionCInflate :: a -> ByteString -> (a, ByteString) Source #
nullCompression :: Compression Source #
default null compression
type CompressionID = Word8 Source #
Compression identification
Ciphers & Predefined ciphers
data CipherKeyExchangeType Source #
Instances
Eq CipherKeyExchangeType Source # | |
Defined in Network.TLS.Cipher (==) :: CipherKeyExchangeType -> CipherKeyExchangeType -> Bool # (/=) :: CipherKeyExchangeType -> CipherKeyExchangeType -> Bool # | |
Show CipherKeyExchangeType Source # | |
Defined in Network.TLS.Cipher showsPrec :: Int -> CipherKeyExchangeType -> ShowS # show :: CipherKeyExchangeType -> String # showList :: [CipherKeyExchangeType] -> ShowS # |
Bulk | |
|
data BulkFunctions Source #
BulkBlockF (BulkDirection -> BulkKey -> BulkBlock) | |
BulkStreamF (BulkDirection -> BulkKey -> BulkStream) | |
BulkAeadF (BulkDirection -> BulkKey -> BulkAEAD) |
data BulkDirection Source #
Instances
Eq BulkDirection Source # | |
Defined in Network.TLS.Cipher (==) :: BulkDirection -> BulkDirection -> Bool # (/=) :: BulkDirection -> BulkDirection -> Bool # | |
Show BulkDirection Source # | |
Defined in Network.TLS.Cipher showsPrec :: Int -> BulkDirection -> ShowS # show :: BulkDirection -> String # showList :: [BulkDirection] -> ShowS # |
newtype BulkStream Source #
BulkStream (ByteString -> (ByteString, BulkStream)) |
type BulkBlock = BulkIV -> ByteString -> (ByteString, BulkIV) Source #
type BulkAEAD = BulkNonce -> ByteString -> BulkAdditionalData -> (ByteString, AuthTag) Source #
Cipher algorithm
cipherKeyBlockSize :: Cipher -> Int Source #
type BulkKey = ByteString Source #
type BulkIV = ByteString Source #
type BulkNonce = ByteString Source #
type BulkAdditionalData = ByteString Source #
cipherAllowedForVersion :: Version -> Cipher -> Bool Source #
Check if a specific Cipher
is allowed to be used
with the version specified
hasMAC :: BulkFunctions -> Bool Source #
hasRecordIV :: BulkFunctions -> Bool Source #
Crypto Key
Public key types known and used in X.509
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
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 |
TLS 1.3
data HandshakeMode13 Source #
Type to show which handshake mode is used in TLS 1.3.
FullHandshake | Full handshake is used. |
HelloRetryRequest | Full handshake is used with hello retry reuest. |
PreSharedKey | Server authentication is skipped. |
RTT0 | Server authentication is skipped and early data is sent. |
Instances
Eq HandshakeMode13 Source # | |
Defined in Network.TLS.Handshake.State (==) :: HandshakeMode13 -> HandshakeMode13 -> Bool # (/=) :: HandshakeMode13 -> HandshakeMode13 -> Bool # | |
Show HandshakeMode13 Source # | |
Defined in Network.TLS.Handshake.State showsPrec :: Int -> HandshakeMode13 -> ShowS # show :: HandshakeMode13 -> String # showList :: [HandshakeMode13] -> ShowS # |
Errors and exceptions
Errors
TLSError that might be returned through the TLS stack
Error_Misc String | mainly for instance of Error |
Error_Protocol (String, Bool, AlertDescription) | |
Error_Certificate String | |
Error_HandshakePolicy String | handshake policy failed. |
Error_EOF | |
Error_Packet String | |
Error_Packet_unexpected String String | |
Error_Packet_Parsing String |
Instances
Eq TLSError Source # | |
Show TLSError Source # | |
Exception TLSError Source # | |
Defined in Network.TLS.Struct toException :: TLSError -> SomeException # fromException :: SomeException -> Maybe TLSError # displayException :: TLSError -> String # |
data AlertDescription Source #
Instances
Eq AlertDescription Source # | |
Defined in Network.TLS.Struct (==) :: AlertDescription -> AlertDescription -> Bool # (/=) :: AlertDescription -> AlertDescription -> Bool # | |
Show AlertDescription Source # | |
Defined in Network.TLS.Struct showsPrec :: Int -> AlertDescription -> ShowS # show :: AlertDescription -> String # showList :: [AlertDescription] -> ShowS # |
Exceptions
data TLSException Source #
TLS Exceptions related to bad user usage or asynchronous errors
Terminated Bool String TLSError | Early termination exception with the reason and the error associated |
HandshakeFailed TLSError | Handshake failed for the reason attached |
ConnectionNotEstablished | Usage error when the connection has not been established and the user is trying to send or receive data |
Instances
Eq TLSException Source # | |
Defined in Network.TLS.Struct (==) :: TLSException -> TLSException -> Bool # (/=) :: TLSException -> TLSException -> Bool # | |
Show TLSException Source # | |
Defined in Network.TLS.Struct showsPrec :: Int -> TLSException -> ShowS # show :: TLSException -> String # showList :: [TLSException] -> ShowS # | |
Exception TLSException Source # | |
Defined in Network.TLS.Struct |
Deprecated
recvData' :: MonadIO m => Context -> m ByteString Source #
Deprecated: use recvData that returns strict bytestring
same as recvData but returns a lazy bytestring.
:: (MonadIO m, TLSParams params) | |
=> Handle | Handle of the connection. |
-> params | Parameters of the context. |
-> m Context |
Deprecated: use contextNew
create a new context on an handle.
:: (MonadIO m, TLSParams params) | |
=> Socket | Socket of the connection. |
-> params | Parameters of the context. |
-> m Context |
Deprecated: use contextNew
create a new context on a socket.
type Bytes = ByteString Source #
Deprecated: Use Data.ByteString.Bytestring instead of Bytes.