License | BSD-style |
---|---|
Maintainer | Vincent Hanquez <vincent@snarc.org> |
Stability | experimental |
Portability | unknown |
Safe Haskell | None |
Language | Haskell98 |
Network.TLS
Contents
- Context configuration
- raw types
- Session
- Backend abstraction
- Context object
- Creating a context
- Information gathering
- Credentials
- Initialisation and Termination of context
- Application Layer Protocol Negotiation
- Server Name Indication
- High level API
- Crypto Key
- Compressions & Predefined compressions
- Ciphers & Predefined ciphers
- Versions
- Errors
- Exceptions
- X509 Validation
- X509 Validation Cache
- Key exchange group
Description
Synopsis
- data ClientParams = ClientParams {
- clientUseMaxFragmentLength :: Maybe MaxFragmentEnum
- clientServerIdentification :: (HostName, ByteString)
- clientUseServerNameIndication :: Bool
- clientWantSessionResume :: Maybe (SessionID, SessionData)
- clientShared :: Shared
- clientHooks :: ClientHooks
- clientSupported :: Supported
- clientDebug :: DebugParams
- type HostName = String
- type Bytes = ByteString
- data ServerParams = ServerParams {
- serverWantClientCert :: Bool
- serverCACertificates :: [SignedCertificate]
- serverDHEParams :: Maybe DHParams
- serverShared :: Shared
- serverHooks :: ServerHooks
- serverSupported :: Supported
- serverDebug :: DebugParams
- data DebugParams = DebugParams {
- debugSeed :: Maybe Seed
- debugPrintSeed :: Seed -> IO ()
- type DHParams = Params
- type DHPublic = PublicNumber
- data ClientHooks = ClientHooks {
- onCertificateRequest :: ([CertificateType], Maybe [HashAndSignatureAlgorithm], [DistinguishedName]) -> IO (Maybe (CertificateChain, PrivKey))
- onServerCertificate :: CertificateStore -> ValidationCache -> ServiceID -> CertificateChain -> IO [FailedReason]
- onSuggestALPN :: IO (Maybe [ByteString])
- onCustomFFDHEGroup :: DHParams -> DHPublic -> IO GroupUsage
- 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)
- 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 {
- sharedCredentials :: Credentials
- sharedSessionManager :: SessionManager
- sharedCAStore :: CertificateStore
- sharedValidationCache :: ValidationCache
- data Hooks = Hooks {
- hookRecvHandshake :: Handshake -> IO Handshake
- hookRecvCertificates :: CertificateChain -> IO ()
- hookLogging :: Logging
- data Handshake
- data Logging = Logging {
- loggingPacketSent :: String -> IO ()
- loggingPacketRecv :: String -> IO ()
- loggingIOSent :: ByteString -> IO ()
- loggingIORecv :: Header -> ByteString -> IO ()
- data Measurement = Measurement {
- nbHandshakes :: !Word32
- bytesReceived :: !Word32
- bytesSent :: !Word32
- data GroupUsage
- data CertificateUsage
- data CertificateRejectReason
- defaultParamsClient :: HostName -> ByteString -> ClientParams
- data MaxFragmentEnum
- type HashAndSignatureAlgorithm = (HashAlgorithm, SignatureAlgorithm)
- data HashAlgorithm
- = HashNone
- | HashMD5
- | HashSHA1
- | HashSHA224
- | HashSHA256
- | HashSHA384
- | HashSHA512
- | HashIntrinsic
- | HashOther Word8
- data SignatureAlgorithm
- data CertificateType
- data ProtocolType
- data Header = Header ProtocolType Version Word16
- type SessionID = ByteString
- data SessionData = SessionData {
- sessionVersion :: Version
- sessionCipher :: CipherID
- sessionCompression :: CompressionID
- sessionClientSNI :: Maybe HostName
- sessionSecret :: ByteString
- data SessionManager = SessionManager {
- sessionResume :: SessionID -> IO (Maybe SessionData)
- sessionEstablish :: SessionID -> SessionData -> IO ()
- sessionInvalidate :: SessionID -> IO ()
- noSessionManager :: SessionManager
- data Backend = Backend {
- backendFlush :: IO ()
- backendClose :: IO ()
- backendSend :: ByteString -> IO ()
- backendRecv :: Int -> IO ByteString
- data Context
- ctxConnection :: Context -> Backend
- class TLSParams a
- class HasBackend a where
- initializeBackend :: a -> IO ()
- getBackend :: a -> Backend
- contextNew :: (MonadIO m, HasBackend backend, TLSParams params) => backend -> params -> m Context
- contextNewOnHandle :: (MonadIO m, TLSParams params) => Handle -> params -> m Context
- contextNewOnSocket :: (MonadIO m, TLSParams params) => Socket -> params -> m Context
- contextFlush :: Context -> IO ()
- contextClose :: Context -> IO ()
- contextHookSetHandshakeRecv :: Context -> (Handshake -> IO Handshake) -> IO ()
- contextHookSetCertificateRecv :: Context -> (CertificateChain -> IO ()) -> IO ()
- contextHookSetLogging :: Context -> Logging -> IO ()
- contextModifyHooks :: Context -> (Hooks -> Hooks) -> IO ()
- data Information = Information {
- infoVersion :: Version
- infoCipher :: Cipher
- infoCompression :: Compression
- infoMasterSecret :: Maybe ByteString
- infoClientRandom :: Maybe ClientRandom
- infoServerRandom :: Maybe ServerRandom
- data ClientRandom
- data ServerRandom
- unClientRandom :: ClientRandom -> ByteString
- unServerRandom :: ServerRandom -> ByteString
- contextGetInformation :: Context -> IO (Maybe Information)
- 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
- bye :: MonadIO m => Context -> m ()
- handshake :: MonadIO m => Context -> m ()
- getNegotiatedProtocol :: MonadIO m => Context -> m (Maybe ByteString)
- getClientSNI :: MonadIO m => Context -> m (Maybe HostName)
- sendData :: MonadIO m => Context -> ByteString -> m ()
- recvData :: MonadIO m => Context -> m ByteString
- recvData' :: MonadIO m => Context -> m ByteString
- 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 Compression = CompressionC a => Compression a
- class CompressionC a where
- compressionCID :: a -> CompressionID
- compressionCDeflate :: a -> ByteString -> (a, ByteString)
- compressionCInflate :: a -> ByteString -> (a, ByteString)
- nullCompression :: Compression
- 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
- cipherExchangeNeedMoreData :: CipherKeyExchangeType -> Bool
- hasMAC :: BulkFunctions -> Bool
- hasRecordIV :: BulkFunctions -> Bool
- data Version
- 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
- | UnsupportedExtension
- | CertificateUnobtainable
- | UnrecognizedName
- | BadCertificateStatusResponse
- | BadCertificateHashValue
- data TLSException
- = Terminated Bool String TLSError
- | HandshakeFailed TLSError
- | ConnectionNotEstablished
- 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]
- data ValidationCache = ValidationCache {
- cacheQuery :: ValidationCacheQueryCallback
- cacheAdd :: ValidationCacheAddCallback
- data ValidationCacheResult
- exceptionValidationCache :: [(ServiceID, Fingerprint)] -> ValidationCache
- data Group
Context configuration
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 () |
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 () |
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 |
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 |
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 |
List all the supported algorithms, versions, ciphers, etc supported.
Constructors
Supported | |
Fields
|
Constructors
Shared | |
Fields
|
A collection of hooks actions.
Constructors
Hooks | |
Fields
|
Hooks for logging
This is called when sending and receiving packets and IO
Constructors
Logging | |
Fields
|
data Measurement Source #
record some data about this connection.
Constructors
Measurement | |
Fields
|
Instances
Eq Measurement Source # | |
Defined in Network.TLS.Measurement | |
Show Measurement Source # | |
Defined in Network.TLS.Measurement Methods showsPrec :: Int -> Measurement -> ShowS show :: Measurement -> String showList :: [Measurement] -> ShowS |
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
Eq GroupUsage Source # | |
Defined in Network.TLS.Parameters | |
Show GroupUsage Source # | |
Defined in Network.TLS.Parameters Methods showsPrec :: Int -> GroupUsage -> ShowS show :: GroupUsage -> String showList :: [GroupUsage] -> ShowS |
data CertificateUsage Source #
Certificate Usage callback possible returns values.
Constructors
CertificateUsageAccept | usage of certificate accepted |
CertificateUsageReject CertificateRejectReason | usage of certificate rejected |
Instances
Eq CertificateUsage Source # | |
Defined in Network.TLS.X509 Methods (==) :: CertificateUsage -> CertificateUsage -> Bool (/=) :: CertificateUsage -> CertificateUsage -> Bool | |
Show CertificateUsage Source # | |
Defined in Network.TLS.X509 Methods showsPrec :: Int -> CertificateUsage -> ShowS show :: CertificateUsage -> String showList :: [CertificateUsage] -> ShowS |
data CertificateRejectReason Source #
Certificate and Chain rejection reason
Constructors
CertificateRejectExpired | |
CertificateRejectRevoked | |
CertificateRejectUnknownCA | |
CertificateRejectOther String |
Instances
Eq CertificateRejectReason Source # | |
Defined in Network.TLS.X509 Methods (==) :: CertificateRejectReason -> CertificateRejectReason -> Bool (/=) :: CertificateRejectReason -> CertificateRejectReason -> Bool | |
Show CertificateRejectReason Source # | |
Defined in Network.TLS.X509 Methods showsPrec :: Int -> CertificateRejectReason -> ShowS show :: CertificateRejectReason -> String showList :: [CertificateRejectReason] -> ShowS |
defaultParamsClient :: HostName -> ByteString -> ClientParams Source #
data MaxFragmentEnum Source #
Constructors
MaxFragment512 | |
MaxFragment1024 | |
MaxFragment2048 | |
MaxFragment4096 |
Instances
Eq MaxFragmentEnum Source # | |
Defined in Network.TLS.Extension Methods (==) :: MaxFragmentEnum -> MaxFragmentEnum -> Bool (/=) :: MaxFragmentEnum -> MaxFragmentEnum -> Bool | |
Show MaxFragmentEnum Source # | |
Defined in Network.TLS.Extension Methods showsPrec :: Int -> MaxFragmentEnum -> ShowS show :: MaxFragmentEnum -> String showList :: [MaxFragmentEnum] -> ShowS |
data HashAlgorithm Source #
Constructors
HashNone | |
HashMD5 | |
HashSHA1 | |
HashSHA224 | |
HashSHA256 | |
HashSHA384 | |
HashSHA512 | |
HashIntrinsic | |
HashOther Word8 |
Instances
Eq HashAlgorithm Source # | |
Defined in Network.TLS.Struct | |
Show HashAlgorithm Source # | |
Defined in Network.TLS.Struct Methods showsPrec :: Int -> HashAlgorithm -> ShowS show :: HashAlgorithm -> String showList :: [HashAlgorithm] -> ShowS |
data SignatureAlgorithm Source #
Constructors
SignatureAnonymous | |
SignatureRSA | |
SignatureDSS | |
SignatureECDSA | |
SignatureRSApssSHA256 | |
SignatureRSApssSHA384 | |
SignatureRSApssSHA512 | |
SignatureEd25519 | |
SignatureEd448 | |
SignatureOther Word8 |
Instances
Eq SignatureAlgorithm Source # | |
Defined in Network.TLS.Struct Methods (==) :: SignatureAlgorithm -> SignatureAlgorithm -> Bool (/=) :: SignatureAlgorithm -> SignatureAlgorithm -> Bool | |
Show SignatureAlgorithm Source # | |
Defined in Network.TLS.Struct Methods showsPrec :: Int -> SignatureAlgorithm -> ShowS show :: SignatureAlgorithm -> String showList :: [SignatureAlgorithm] -> ShowS |
data CertificateType Source #
Constructors
Instances
Eq CertificateType Source # | |
Defined in Network.TLS.Struct Methods (==) :: CertificateType -> CertificateType -> Bool (/=) :: CertificateType -> CertificateType -> Bool | |
Show CertificateType Source # | |
Defined in Network.TLS.Struct Methods showsPrec :: Int -> CertificateType -> ShowS show :: CertificateType -> String showList :: [CertificateType] -> ShowS |
raw types
data ProtocolType Source #
Constructors
ProtocolType_ChangeCipherSpec | |
ProtocolType_Alert | |
ProtocolType_Handshake | |
ProtocolType_AppData | |
ProtocolType_DeprecatedHandshake |
Instances
Eq ProtocolType Source # | |
Defined in Network.TLS.Struct | |
Show ProtocolType Source # | |
Defined in Network.TLS.Struct Methods showsPrec :: Int -> ProtocolType -> ShowS show :: ProtocolType -> String showList :: [ProtocolType] -> ShowS |
Constructors
Header ProtocolType Version Word16 |
Session
data SessionData Source #
Session data to resume
Constructors
SessionData | |
Fields
|
Instances
Eq SessionData Source # | |
Defined in Network.TLS.Types | |
Show SessionData Source # | |
Defined in Network.TLS.Types Methods showsPrec :: Int -> SessionData -> ShowS show :: SessionData -> String showList :: [SessionData] -> ShowS |
data SessionManager Source #
A session manager
Constructors
SessionManager | |
Fields
|
Backend abstraction
Connection IO backend
Constructors
Backend | |
Fields
|
Instances
HasBackend Backend Source # | |
Defined in Network.TLS.Backend |
Context object
ctxConnection :: Context -> Backend Source #
return the backend object associated with this context
Minimal complete definition
getTLSCommonParams, getTLSRole, doHandshake, doHandshakeWith
Instances
TLSParams ServerParams Source # | |
Defined in Network.TLS.Context Methods getTLSCommonParams :: ServerParams -> CommonParams getTLSRole :: ServerParams -> Role doHandshake :: ServerParams -> Context -> IO () doHandshakeWith :: ServerParams -> Context -> Handshake -> IO () | |
TLSParams ClientParams Source # | |
Defined in Network.TLS.Context Methods getTLSCommonParams :: ClientParams -> CommonParams getTLSRole :: ClientParams -> Role doHandshake :: ClientParams -> Context -> IO () doHandshakeWith :: ClientParams -> Context -> Handshake -> IO () |
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 |
Creating a context
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.
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.
contextFlush :: Context -> IO () Source #
contextClose :: Context -> IO () Source #
contextHookSetCertificateRecv :: Context -> (CertificateChain -> IO ()) -> IO () Source #
contextHookSetLogging :: Context -> Logging -> IO () Source #
Information gathering
data Information Source #
Information related to a running context, e.g. current cipher
Constructors
Information | |
Fields
|
Instances
Eq Information Source # | |
Defined in Network.TLS.Context.Internal | |
Show Information Source # | |
Defined in Network.TLS.Context.Internal Methods showsPrec :: Int -> Information -> ShowS show :: Information -> String showList :: [Information] -> ShowS |
data ClientRandom Source #
Instances
Eq ClientRandom Source # | |
Defined in Network.TLS.Struct | |
Show ClientRandom Source # | |
Defined in Network.TLS.Struct Methods showsPrec :: Int -> ClientRandom -> ShowS show :: ClientRandom -> String showList :: [ClientRandom] -> ShowS |
data ServerRandom Source #
Instances
Eq ServerRandom Source # | |
Defined in Network.TLS.Struct | |
Show ServerRandom Source # | |
Defined in Network.TLS.Struct Methods showsPrec :: Int -> ServerRandom -> ShowS show :: ServerRandom -> String showList :: [ServerRandom] -> ShowS |
unClientRandom :: ClientRandom -> ByteString Source #
unServerRandom :: ServerRandom -> ByteString Source #
contextGetInformation :: Context -> IO (Maybe Information) Source #
Information about the current context
Credentials
newtype Credentials Source #
Constructors
Credentials [Credential] |
Instances
Semigroup Credentials Source # | |
Defined in Network.TLS.Credentials Methods (<>) :: Credentials -> Credentials -> Credentials sconcat :: NonEmpty Credentials -> Credentials stimes :: Integral b => b -> Credentials -> Credentials | |
Monoid Credentials Source # | |
Defined in Network.TLS.Credentials |
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.
Initialisation and Termination of context
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
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
Application Layer Protocol Negotiation
getNegotiatedProtocol :: MonadIO m => Context -> m (Maybe ByteString) Source #
If the ALPN extensions have been used, this will return get the protocol agreed upon.
Server Name Indication
getClientSNI :: MonadIO m => Context -> m (Maybe HostName) Source #
If the Server Name Indication extension has been used, return the hostname specified by the client.
High level API
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 #
recvData get data out of Data packet, and automatically renegotiate if a Handshake ClientHello is received
recvData' :: MonadIO m => Context -> m ByteString Source #
Deprecated: use recvData that returns strict bytestring
same as recvData but returns a lazy bytestring.
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
Eq PubKey | |
Show PubKey | |
ASN1Object PubKey | |
Defined in Data.X509.PublicKey |
Constructors
PrivKeyRSA PrivateKey | |
PrivKeyDSA PrivateKey | |
PrivKeyEC PrivKeyEC | |
PrivKeyX25519 SecretKey | |
PrivKeyX448 SecretKey | |
PrivKeyEd25519 SecretKey | |
PrivKeyEd448 SecretKey |
Instances
Eq PrivKey | |
Show PrivKey | |
ASN1Object PrivKey | |
Defined in Data.X509.PrivateKey |
Compressions & Predefined compressions
data Compression Source #
every compression need to be wrapped in this, to fit in structure
Constructors
CompressionC a => Compression a |
Instances
Eq Compression Source # | |
Defined in Network.TLS.Compression | |
Show Compression Source # | |
Defined in Network.TLS.Compression Methods 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
Methods
compressionCID :: a -> CompressionID Source #
compressionCDeflate :: a -> ByteString -> (a, ByteString) Source #
compressionCInflate :: a -> ByteString -> (a, ByteString) Source #
nullCompression :: Compression Source #
default null compression
Ciphers & Predefined ciphers
data CipherKeyExchangeType Source #
Constructors
Instances
Eq CipherKeyExchangeType Source # | |
Defined in Network.TLS.Cipher Methods (==) :: CipherKeyExchangeType -> CipherKeyExchangeType -> Bool (/=) :: CipherKeyExchangeType -> CipherKeyExchangeType -> Bool | |
Show CipherKeyExchangeType Source # | |
Defined in Network.TLS.Cipher Methods showsPrec :: Int -> CipherKeyExchangeType -> ShowS show :: CipherKeyExchangeType -> String showList :: [CipherKeyExchangeType] -> ShowS |
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
Eq BulkDirection Source # | |
Defined in Network.TLS.Cipher | |
Show BulkDirection Source # | |
Defined in Network.TLS.Cipher Methods showsPrec :: Int -> BulkDirection -> ShowS show :: BulkDirection -> String showList :: [BulkDirection] -> ShowS |
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
cipherExchangeNeedMoreData :: CipherKeyExchangeType -> Bool Source #
hasMAC :: BulkFunctions -> Bool Source #
hasRecordIV :: BulkFunctions -> Bool Source #
Versions
Versions known to TLS
SSL2 is just defined, but this version is and will not be supported.
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
Eq TLSError Source # | |
Show TLSError Source # | |
Exception TLSError Source # | |
Defined in Network.TLS.Struct Methods toException :: TLSError -> SomeException fromException :: SomeException -> Maybe TLSError displayException :: TLSError -> String |
Constructors
RSAError Error | |
KxUnsupported |
data AlertDescription Source #
Constructors
Instances
Eq AlertDescription Source # | |
Defined in Network.TLS.Struct Methods (==) :: AlertDescription -> AlertDescription -> Bool (/=) :: AlertDescription -> AlertDescription -> Bool | |
Show AlertDescription Source # | |
Defined in Network.TLS.Struct Methods showsPrec :: Int -> AlertDescription -> ShowS show :: AlertDescription -> String showList :: [AlertDescription] -> ShowS |
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
Eq TLSException Source # | |
Defined in Network.TLS.Struct | |
Show TLSException Source # | |
Defined in Network.TLS.Struct Methods showsPrec :: Int -> TLSException -> ShowS show :: TLSException -> String showList :: [TLSException] -> ShowS | |
Exception TLSException Source # | |
Defined in Network.TLS.Struct Methods toException :: TLSException -> SomeException fromException :: SomeException -> Maybe TLSException displayException :: TLSException -> String |
X509 Validation
data ValidationChecks #
Constructors
ValidationChecks | |
Fields
|
Instances
Eq ValidationChecks | |
Defined in Data.X509.Validation Methods (==) :: ValidationChecks -> ValidationChecks -> Bool (/=) :: ValidationChecks -> ValidationChecks -> Bool | |
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 |
data ValidationHooks #
Constructors
ValidationHooks | |
Fields
|
Instances
Default ValidationHooks | |
Defined in Data.X509.Validation Methods |
X509 Validation Cache
data ValidationCache #
Constructors
ValidationCache | |
Fields
|
Instances
Default ValidationCache | |
Defined in Data.X509.Validation.Cache Methods |
data ValidationCacheResult #
Constructors
ValidationCachePass | |
ValidationCacheDenied String | |
ValidationCacheUnknown |
Instances
Eq ValidationCacheResult | |
Defined in Data.X509.Validation.Cache Methods (==) :: ValidationCacheResult -> ValidationCacheResult -> Bool (/=) :: ValidationCacheResult -> ValidationCacheResult -> Bool | |
Show ValidationCacheResult | |
Defined in Data.X509.Validation.Cache Methods showsPrec :: Int -> ValidationCacheResult -> ShowS show :: ValidationCacheResult -> String showList :: [ValidationCacheResult] -> ShowS |
exceptionValidationCache :: [(ServiceID, Fingerprint)] -> ValidationCache #