License | BSD-style |
---|---|
Maintainer | Vincent Hanquez <vincent@snarc.org> |
Stability | experimental |
Portability | unknown |
Safe Haskell | Safe-Inferred |
Language | Haskell2010 |
Network.TLS
Description
Native Haskell TLS and SSL protocol implementation for server and client.
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 SSL3.0, TLS1.0, TLS1.1, TLS1.2 and TLS 1.3 protocol, and support RSA and Ephemeral (Elliptic curve and regular) Diffie Hellman key exchanges, and many extensions.
Some debug tools linked with tls, are available through the http://hackage.haskell.org/package/tls-debug/.
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 {
- serverWantClientCert :: Bool
- serverCACertificates :: [SignedCertificate]
- serverDHEParams :: Maybe DHParams
- serverHooks :: ServerHooks
- serverShared :: Shared
- serverSupported :: Supported
- serverDebug :: DebugParams
- serverEarlyDataSize :: Int
- serverTicketLifetime :: Int
- data Shared = Shared {
- sharedCredentials :: Credentials
- sharedSessionManager :: SessionManager
- sharedCAStore :: CertificateStore
- sharedValidationCache :: ValidationCache
- sharedHelloExtensions :: [ExtensionRaw]
- data ClientHooks = ClientHooks {
- onCertificateRequest :: OnCertificateRequest
- onServerCertificate :: OnServerCertificate
- onSuggestALPN :: IO (Maybe [ByteString])
- onCustomFFDHEGroup :: DHParams -> DHPublic -> IO GroupUsage
- 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 {
- nbHandshakes :: !Word32
- bytesReceived :: !Word32
- bytesSent :: !Word32
- data Supported = Supported {
- supportedVersions :: [Version]
- supportedCiphers :: [Cipher]
- supportedCompressions :: [Compression]
- supportedHashSignatures :: [HashAndSignatureAlgorithm]
- supportedSecureRenegotiation :: Bool
- supportedClientInitiatedRenegotiation :: Bool
- supportedExtendedMasterSec :: 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 :: SessionID -> IO (Maybe SessionData)
- sessionResumeOnlyOnce :: SessionID -> IO (Maybe SessionData)
- sessionEstablish :: SessionID -> SessionData -> IO ()
- sessionInvalidate :: SessionID -> IO ()
- noSessionManager :: SessionManager
- type SessionID = 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
- data Version
- data Compression = forall a.CompressionC a => Compression a
- nullCompression :: Compression
- type HashAndSignatureAlgorithm = (HashAlgorithm, SignatureAlgorithm)
- data HashAlgorithm
- = HashNone
- | HashMD5
- | HashSHA1
- | HashSHA224
- | HashSHA256
- | HashSHA384
- | HashSHA512
- | HashIntrinsic
- | HashOther Word8
- data SignatureAlgorithm
- data Group
- data EMSMode
- = NoEMS
- | AllowEMS
- | RequireEMS
- type DHParams = Params
- type DHPublic = PublicNumber
- data GroupUsage
- data CertificateUsage
- data CertificateRejectReason
- 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
- type HostName = String
- data MaxFragmentEnum
- ctxConnection :: Context -> Backend
- contextFlush :: Context -> IO ()
- contextClose :: Context -> IO ()
- data Information = Information {
- infoVersion :: Version
- infoCipher :: Cipher
- infoCompression :: Compression
- infoMasterSecret :: Maybe ByteString
- infoExtendedMasterSec :: Bool
- infoClientRandom :: Maybe ClientRandom
- infoServerRandom :: Maybe ServerRandom
- infoNegotiatedGroup :: Maybe Group
- 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 :: MonadIO m => Context -> m Bool
- getFinished :: Context -> IO (Maybe FinishedData)
- getPeerFinished :: Context -> IO (Maybe FinishedData)
- data Hooks = Hooks {
- hookRecvHandshake :: Handshake -> IO Handshake
- hookRecvHandshake13 :: Handshake13 -> IO Handshake13
- hookRecvCertificates :: CertificateChain -> IO ()
- hookLogging :: Logging
- 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
- data ProtocolType
- contextHookSetLogging :: Context -> Logging -> IO ()
- data TLSError
- = Error_Misc String
- | Error_Protocol (String, Bool, AlertDescription)
- | Error_Certificate String
- | Error_HandshakePolicy String
- | Error_EOF
- | Error_Packet String
- | Error_Packet_unexpected String String
- | Error_Packet_Parsing String
- data KxError
- = RSAError Error
- | KxUnsupported
- 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
- = Terminated Bool String TLSError
- | HandshakeFailed TLSError
- | ConnectionNotEstablished
- class CompressionC a where
- compressionCID :: a -> CompressionID
- compressionCDeflate :: a -> ByteString -> (a, ByteString)
- compressionCInflate :: a -> ByteString -> (a, ByteString)
- type CompressionID = Word8
- data PubKey
- = PubKeyRSA PublicKey
- | PubKeyDSA PublicKey
- | PubKeyDH (Integer, Integer, Integer, Maybe Integer, ([Word8], Integer))
- | PubKeyEC PubKeyEC
- | PubKeyX25519 PublicKey
- | PubKeyX448 PublicKey
- | PubKeyEd25519 PublicKey
- | PubKeyEd448 PublicKey
- | PubKeyUnknown OID ByteString
- data PrivKey
- = PrivKeyRSA PrivateKey
- | PrivKeyDSA PrivateKey
- | PrivKeyEC PrivKeyEC
- | PrivKeyX25519 SecretKey
- | PrivKeyX448 SecretKey
- | PrivKeyEd25519 SecretKey
- | PrivKeyEd448 SecretKey
- 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 {
- cipherID :: CipherID
- cipherName :: String
- cipherHash :: Hash
- cipherBulk :: Bulk
- cipherKeyExchange :: CipherKeyExchangeType
- cipherMinVer :: Maybe Version
- cipherPRFHash :: Maybe Hash
- 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
- contextNewOnHandle :: (MonadIO m, TLSParams params) => Handle -> params -> m Context
- contextNewOnSocket :: (MonadIO m, TLSParams params) => Socket -> params -> m Context
- type Bytes = ByteString
- data ValidationChecks = ValidationChecks {
- checkTimeValidity :: Bool
- checkAtTime :: Maybe DateTime
- checkStrictOrdering :: Bool
- checkCAConstraints :: Bool
- checkExhaustive :: Bool
- checkLeafV3 :: Bool
- checkLeafKeyUsage :: [ExtKeyUsageFlag]
- checkLeafKeyPurpose :: [ExtKeyUsagePurpose]
- checkFQHN :: Bool
- 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 () 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 #
Instances
HasBackend Handle Source # | |
Defined in Network.TLS.Backend | |
HasBackend Socket Source # | |
Defined in Network.TLS.Backend | |
HasBackend Backend Source # | |
Defined in Network.TLS.Backend |
Connection IO backend
Constructors
Backend | |
Fields
|
Instances
HasBackend Backend Source # | |
Defined in Network.TLS.Backend |
Parameters
Minimal complete definition
getTLSCommonParams, getTLSRole, doHandshake, doHandshakeWith, doRequestCertificate, doPostHandshakeAuthWith
Instances
TLSParams ClientParams Source # | |
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 Source # | |
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 Source #
Constructors
ClientParams | |
Fields
|
Instances
Show ClientParams Source # | |
Defined in Network.TLS.Parameters Methods showsPrec :: Int -> ClientParams -> ShowS show :: ClientParams -> String showList :: [ClientParams] -> ShowS | |
TLSParams ClientParams Source # | |
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 Source #
data ServerParams Source #
Constructors
ServerParams | |
Fields
|
Instances
Show ServerParams Source # | |
Defined in Network.TLS.Parameters Methods showsPrec :: Int -> ServerParams -> ShowS show :: ServerParams -> String showList :: [ServerParams] -> ShowS | |
Default ServerParams Source # | |
Defined in Network.TLS.Parameters Methods def :: ServerParams | |
TLSParams ServerParams Source # | |
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 Source #
A set of callbacks run by the clients for various corners of TLS establishment
Constructors
ClientHooks | |
Fields
|
Instances
Show ClientHooks Source # | |
Defined in Network.TLS.Parameters Methods showsPrec :: Int -> ClientHooks -> ShowS show :: ClientHooks -> String showList :: [ClientHooks] -> ShowS | |
Default ClientHooks Source # | |
Defined in Network.TLS.Parameters Methods 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
Constructors
ServerHooks | |
Fields
|
Instances
Show ServerHooks Source # | |
Defined in Network.TLS.Parameters Methods showsPrec :: Int -> ServerHooks -> ShowS show :: ServerHooks -> String showList :: [ServerHooks] -> ShowS | |
Default ServerHooks Source # | |
Defined in Network.TLS.Parameters Methods def :: ServerHooks |
data Measurement Source #
record some data about this connection.
Constructors
Measurement | |
Fields
|
Instances
Show Measurement Source # | |
Defined in Network.TLS.Measurement Methods showsPrec :: Int -> Measurement -> ShowS show :: Measurement -> String showList :: [Measurement] -> ShowS | |
Eq Measurement Source # | |
Defined in Network.TLS.Measurement |
Supported
List all the supported algorithms, versions, ciphers, etc supported.
Constructors
Supported | |
Fields
|
Debug parameters
data DebugParams Source #
All settings should not be used in production
Constructors
DebugParams | |
Fields
|
Instances
Show DebugParams Source # | |
Defined in Network.TLS.Parameters Methods showsPrec :: Int -> DebugParams -> ShowS show :: DebugParams -> String showList :: [DebugParams] -> ShowS | |
Default DebugParams Source # | |
Defined in Network.TLS.Parameters Methods def :: DebugParams |
Shared parameters
Credentials
newtype Credentials Source #
Constructors
Credentials [Credential] |
Instances
Monoid Credentials Source # | |
Defined in Network.TLS.Credentials | |
Semigroup Credentials Source # | |
Defined in Network.TLS.Credentials Methods (<>) :: Credentials -> Credentials -> Credentials sconcat :: NonEmpty Credentials -> Credentials stimes :: Integral b => b -> Credentials -> Credentials | |
Show Credentials Source # | |
Defined in Network.TLS.Credentials Methods showsPrec :: Int -> Credentials -> ShowS show :: Credentials -> String showList :: [Credentials] -> ShowS |
type Credential = (CertificateChain, PrivKey) Source #
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 Source #
similar to credentialLoadX509
but take the certificate
and private key from memory instead of from the filesystem.
credentialLoadX509Chain Source #
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 Source #
similar to credentialLoadX509FromMemory
but also allow
specifying chain certificates.
Session manager
data SessionManager Source #
A session manager
Constructors
SessionManager | |
Fields
|
noSessionManager :: SessionManager Source #
The session manager to do nothing.
data SessionData Source #
Session data to resume
Constructors
SessionData | |
Fields
|
Instances
Show SessionData Source # | |
Defined in Network.TLS.Types Methods showsPrec :: Int -> SessionData -> ShowS show :: SessionData -> String showList :: [SessionData] -> ShowS | |
Eq SessionData Source # | |
Defined in Network.TLS.Types |
data SessionFlag Source #
Some session flags
Constructors
SessionEMS | Session created with Extended Master Secret |
Instances
Enum SessionFlag Source # | |
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] | |
Show SessionFlag Source # | |
Defined in Network.TLS.Types Methods showsPrec :: Int -> SessionFlag -> ShowS show :: SessionFlag -> String showList :: [SessionFlag] -> ShowS | |
Eq SessionFlag Source # | |
Defined in Network.TLS.Types |
data TLS13TicketInfo Source #
Instances
Show TLS13TicketInfo Source # | |
Defined in Network.TLS.Types Methods showsPrec :: Int -> TLS13TicketInfo -> ShowS show :: TLS13TicketInfo -> String showList :: [TLS13TicketInfo] -> ShowS | |
Eq TLS13TicketInfo Source # | |
Defined in Network.TLS.Types Methods (==) :: TLS13TicketInfo -> TLS13TicketInfo -> Bool (/=) :: TLS13TicketInfo -> TLS13TicketInfo -> Bool |
Validation Cache
data ValidationCache #
Constructors
ValidationCache | |
Instances
Default ValidationCache | |
Defined in Data.X509.Validation.Cache Methods |
type ValidationCacheQueryCallback = ServiceID -> Fingerprint -> Certificate -> IO ValidationCacheResult #
type ValidationCacheAddCallback = ServiceID -> Fingerprint -> Certificate -> IO () #
data ValidationCacheResult #
Constructors
ValidationCachePass | |
ValidationCacheDenied String | |
ValidationCacheUnknown |
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 #
Types
For Supported
Versions known to TLS
SSL2 is just defined, but this version is and will not be supported.
data Compression Source #
every compression need to be wrapped in this, to fit in structure
Constructors
forall a.CompressionC a => Compression a |
Instances
Show Compression Source # | |
Defined in Network.TLS.Compression Methods showsPrec :: Int -> Compression -> ShowS show :: Compression -> String showList :: [Compression] -> ShowS | |
Eq Compression Source # | |
Defined in Network.TLS.Compression |
nullCompression :: Compression Source #
default null compression
data HashAlgorithm Source #
Constructors
HashNone | |
HashMD5 | |
HashSHA1 | |
HashSHA224 | |
HashSHA256 | |
HashSHA384 | |
HashSHA512 | |
HashIntrinsic | |
HashOther Word8 |
Instances
Show HashAlgorithm Source # | |
Defined in Network.TLS.Struct Methods showsPrec :: Int -> HashAlgorithm -> ShowS show :: HashAlgorithm -> String showList :: [HashAlgorithm] -> ShowS | |
Eq HashAlgorithm Source # | |
Defined in Network.TLS.Struct |
data SignatureAlgorithm Source #
Constructors
Instances
Show SignatureAlgorithm Source # | |
Defined in Network.TLS.Struct Methods showsPrec :: Int -> SignatureAlgorithm -> ShowS show :: SignatureAlgorithm -> String showList :: [SignatureAlgorithm] -> ShowS | |
Eq SignatureAlgorithm Source # | |
Defined in Network.TLS.Struct Methods (==) :: SignatureAlgorithm -> SignatureAlgorithm -> Bool (/=) :: SignatureAlgorithm -> SignatureAlgorithm -> Bool |
Client or server policy regarding Extended Master Secret
Constructors
NoEMS | Extended Master Secret is not used |
AllowEMS | Extended Master Secret is allowed |
RequireEMS | Extended Master Secret is required |
For parameters and hooks
data GroupUsage Source #
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 Source # | |
Defined in Network.TLS.Parameters Methods showsPrec :: Int -> GroupUsage -> ShowS show :: GroupUsage -> String showList :: [GroupUsage] -> ShowS | |
Eq GroupUsage Source # | |
Defined in Network.TLS.Parameters |
data CertificateUsage Source #
Certificate Usage callback possible returns values.
Constructors
CertificateUsageAccept | usage of certificate accepted |
CertificateUsageReject CertificateRejectReason | usage of certificate rejected |
Instances
Show CertificateUsage Source # | |
Defined in Network.TLS.X509 Methods showsPrec :: Int -> CertificateUsage -> ShowS show :: CertificateUsage -> String showList :: [CertificateUsage] -> ShowS | |
Eq CertificateUsage Source # | |
Defined in Network.TLS.X509 Methods (==) :: CertificateUsage -> CertificateUsage -> Bool (/=) :: CertificateUsage -> CertificateUsage -> Bool |
data CertificateRejectReason Source #
Certificate and Chain rejection reason
Constructors
CertificateRejectExpired | |
CertificateRejectRevoked | |
CertificateRejectUnknownCA | |
CertificateRejectAbsent | |
CertificateRejectOther String |
Instances
Show CertificateRejectReason Source # | |
Defined in Network.TLS.X509 Methods showsPrec :: Int -> CertificateRejectReason -> ShowS show :: CertificateRejectReason -> String showList :: [CertificateRejectReason] -> ShowS | |
Eq CertificateRejectReason Source # | |
Defined in Network.TLS.X509 Methods (==) :: CertificateRejectReason -> CertificateRejectReason -> Bool (/=) :: CertificateRejectReason -> CertificateRejectReason -> Bool |
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.
Constructors
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
Show CertificateType Source # | |
Defined in Network.TLS.Struct Methods showsPrec :: Int -> CertificateType -> ShowS show :: CertificateType -> String showList :: [CertificateType] -> ShowS | |
Eq CertificateType Source # | |
Defined in Network.TLS.Struct Methods (==) :: CertificateType -> CertificateType -> Bool (/=) :: CertificateType -> CertificateType -> Bool | |
Ord CertificateType Source # | |
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 |
data MaxFragmentEnum Source #
Constructors
MaxFragment512 | |
MaxFragment1024 | |
MaxFragment2048 | |
MaxFragment4096 |
Instances
Show MaxFragmentEnum Source # | |
Defined in Network.TLS.Extension Methods showsPrec :: Int -> MaxFragmentEnum -> ShowS show :: MaxFragmentEnum -> String showList :: [MaxFragmentEnum] -> ShowS | |
Eq MaxFragmentEnum Source # | |
Defined in Network.TLS.Extension Methods (==) :: MaxFragmentEnum -> MaxFragmentEnum -> Bool (/=) :: MaxFragmentEnum -> MaxFragmentEnum -> Bool |
Advanced 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
Constructors
Information | |
Fields
|
Instances
Show Information Source # | |
Defined in Network.TLS.Context.Internal Methods showsPrec :: Int -> Information -> ShowS show :: Information -> String showList :: [Information] -> ShowS | |
Eq Information Source # | |
Defined in Network.TLS.Context.Internal |
contextGetInformation :: Context -> IO (Maybe Information) Source #
Information about the current context
data ClientRandom Source #
Instances
Show ClientRandom Source # | |
Defined in Network.TLS.Struct Methods showsPrec :: Int -> ClientRandom -> ShowS show :: ClientRandom -> String showList :: [ClientRandom] -> ShowS | |
Eq ClientRandom Source # | |
Defined in Network.TLS.Struct |
data ServerRandom Source #
Instances
Show ServerRandom Source # | |
Defined in Network.TLS.Struct Methods showsPrec :: Int -> ServerRandom -> ShowS show :: ServerRandom -> String showList :: [ServerRandom] -> ShowS | |
Eq ServerRandom Source # | |
Defined in Network.TLS.Struct |
unClientRandom :: ClientRandom -> ByteString Source #
unServerRandom :: ServerRandom -> ByteString Source #
data HandshakeMode13 Source #
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 Source # | |
Defined in Network.TLS.Handshake.State Methods showsPrec :: Int -> HandshakeMode13 -> ShowS show :: HandshakeMode13 -> String showList :: [HandshakeMode13] -> ShowS | |
Eq HandshakeMode13 Source # | |
Defined in Network.TLS.Handshake.State Methods (==) :: HandshakeMode13 -> HandshakeMode13 -> Bool (/=) :: HandshakeMode13 -> HandshakeMode13 -> Bool |
getClientCertificateChain :: Context -> IO (Maybe CertificateChain) Source #
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) 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
updateKey :: MonadIO m => Context -> KeyUpdateRequest -> m Bool Source #
Updating appication traffic secrets for TLS 1.3.
If this API is called for TLS 1.3, True
is returned.
Otherwise, False
is returned.
data KeyUpdateRequest Source #
How to update keys in TLS 1.3
Instances
Show KeyUpdateRequest Source # | |
Defined in Network.TLS.Core Methods showsPrec :: Int -> KeyUpdateRequest -> ShowS show :: KeyUpdateRequest -> String showList :: [KeyUpdateRequest] -> ShowS | |
Eq KeyUpdateRequest Source # | |
Defined in Network.TLS.Core Methods (==) :: KeyUpdateRequest -> KeyUpdateRequest -> Bool (/=) :: KeyUpdateRequest -> KeyUpdateRequest -> Bool |
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.
getFinished :: Context -> IO (Maybe FinishedData) Source #
Get TLS Finished sent to peer
getPeerFinished :: Context -> IO (Maybe FinishedData) Source #
Get TLS Finished received from peer
Modifying hooks in context
A collection of hooks actions.
Constructors
Hooks | |
Fields
|
Instances
data Handshake13 Source #
Instances
Show Handshake13 Source # | |
Defined in Network.TLS.Struct13 Methods showsPrec :: Int -> Handshake13 -> ShowS show :: Handshake13 -> String showList :: [Handshake13] -> ShowS | |
Eq Handshake13 Source # | |
Defined in Network.TLS.Struct13 |
contextHookSetHandshake13Recv :: Context -> (Handshake13 -> IO Handshake13) -> IO () Source #
contextHookSetCertificateRecv :: Context -> (CertificateChain -> IO ()) -> IO () Source #
Hooks for logging
This is called when sending and receiving packets and IO
Constructors
Logging | |
Fields
|
Constructors
Header ProtocolType Version Word16 |
data ProtocolType Source #
Constructors
ProtocolType_ChangeCipherSpec | |
ProtocolType_Alert | |
ProtocolType_Handshake | |
ProtocolType_AppData | |
ProtocolType_DeprecatedHandshake |
Instances
Show ProtocolType Source # | |
Defined in Network.TLS.Struct Methods showsPrec :: Int -> ProtocolType -> ShowS show :: ProtocolType -> String showList :: [ProtocolType] -> ShowS | |
Eq ProtocolType Source # | |
Defined in Network.TLS.Struct |
contextHookSetLogging :: Context -> Logging -> IO () Source #
Errors and exceptions
Errors
TLSError that might be returned through the TLS stack
Constructors
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
Exception TLSError Source # | |
Defined in Network.TLS.Struct Methods toException :: TLSError -> SomeException fromException :: SomeException -> Maybe TLSError displayException :: TLSError -> String | |
Show TLSError Source # | |
Eq TLSError Source # | |
Constructors
RSAError Error | |
KxUnsupported |
data AlertDescription Source #
Constructors
Instances
Show AlertDescription Source # | |
Defined in Network.TLS.Struct Methods showsPrec :: Int -> AlertDescription -> ShowS show :: AlertDescription -> String showList :: [AlertDescription] -> ShowS | |
Eq AlertDescription Source # | |
Defined in Network.TLS.Struct Methods (==) :: AlertDescription -> AlertDescription -> Bool (/=) :: AlertDescription -> AlertDescription -> Bool |
Exceptions
data TLSException Source #
TLS Exceptions related to bad user usage or asynchronous errors
Constructors
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
Exception TLSException Source # | |
Defined in Network.TLS.Struct Methods toException :: TLSException -> SomeException fromException :: SomeException -> Maybe TLSException displayException :: TLSException -> String | |
Show TLSException Source # | |
Defined in Network.TLS.Struct Methods showsPrec :: Int -> TLSException -> ShowS show :: TLSException -> String showList :: [TLSException] -> ShowS | |
Eq TLSException Source # | |
Defined in Network.TLS.Struct |
Raw types
Compressions class
class CompressionC a where Source #
supported compression algorithms need to be part of this class
Methods
compressionCID :: a -> CompressionID Source #
compressionCDeflate :: a -> ByteString -> (a, ByteString) Source #
compressionCInflate :: a -> ByteString -> (a, ByteString) Source #
type CompressionID = Word8 Source #
Compression identification
Crypto Key
Constructors
PubKeyRSA PublicKey | |
PubKeyDSA PublicKey | |
PubKeyDH (Integer, Integer, Integer, Maybe Integer, ([Word8], Integer)) | |
PubKeyEC PubKeyEC | |
PubKeyX25519 PublicKey | |
PubKeyX448 PublicKey | |
PubKeyEd25519 PublicKey | |
PubKeyEd448 PublicKey | |
PubKeyUnknown OID ByteString |
Instances
ASN1Object PubKey | |
Defined in Data.X509.PublicKey | |
Show PubKey | |
Eq PubKey | |
Constructors
PrivKeyRSA PrivateKey | |
PrivKeyDSA PrivateKey | |
PrivKeyEC PrivKeyEC | |
PrivKeyX25519 SecretKey | |
PrivKeyX448 SecretKey | |
PrivKeyEd25519 SecretKey | |
PrivKeyEd448 SecretKey |
Instances
ASN1Object PrivKey | |
Defined in Data.X509.PrivateKey | |
Show PrivKey | |
Eq PrivKey | |
Ciphers & Predefined ciphers
data CipherKeyExchangeType Source #
Constructors
Instances
Show CipherKeyExchangeType Source # | |
Defined in Network.TLS.Cipher Methods showsPrec :: Int -> CipherKeyExchangeType -> ShowS show :: CipherKeyExchangeType -> String showList :: [CipherKeyExchangeType] -> ShowS | |
Eq CipherKeyExchangeType Source # | |
Defined in Network.TLS.Cipher Methods (==) :: CipherKeyExchangeType -> CipherKeyExchangeType -> Bool (/=) :: CipherKeyExchangeType -> CipherKeyExchangeType -> Bool |
Constructors
Bulk | |
Fields
|
data BulkFunctions Source #
Constructors
BulkBlockF (BulkDirection -> BulkKey -> BulkBlock) | |
BulkStreamF (BulkDirection -> BulkKey -> BulkStream) | |
BulkAeadF (BulkDirection -> BulkKey -> BulkAEAD) |
data BulkDirection Source #
Constructors
BulkEncrypt | |
BulkDecrypt |
Instances
Show BulkDirection Source # | |
Defined in Network.TLS.Cipher Methods showsPrec :: Int -> BulkDirection -> ShowS show :: BulkDirection -> String showList :: [BulkDirection] -> ShowS | |
Eq BulkDirection Source # | |
Defined in Network.TLS.Cipher |
newtype BulkStream Source #
Constructors
BulkStream (ByteString -> (ByteString, BulkStream)) |
type BulkAEAD = BulkNonce -> ByteString -> BulkAdditionalData -> (ByteString, AuthTag) Source #
Cipher algorithm
Constructors
Cipher | |
Fields
|
cipherKeyBlockSize :: Cipher -> Int 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 #
Deprecated
recvData' :: MonadIO m => Context -> m ByteString Source #
Deprecated: use recvData that returns strict bytestring
same as recvData but returns a lazy bytestring.
Arguments
:: (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.
Arguments
:: (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.
data ValidationChecks #
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 | |
Eq ValidationChecks | |
Defined in Data.X509.Validation Methods (==) :: ValidationChecks -> ValidationChecks -> Bool (/=) :: ValidationChecks -> ValidationChecks -> Bool |
data ValidationHooks #
Constructors
ValidationHooks | |
Fields
|
Instances
Default ValidationHooks | |
Defined in Data.X509.Validation Methods |