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 {}
- type HostName = String
- type Bytes = ByteString
- data ServerParams = ServerParams {}
- data DebugParams = DebugParams {}
- 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 {}
- 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
- 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 {}
- 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
- data PrivKey
- 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 {}
- 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
- 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
- | UnsupportedExtension
- | CertificateUnobtainable
- | UnrecognizedName
- | BadCertificateStatusResponse
- | BadCertificateHashValue
- data TLSException
- 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
- data Group
Context configuration
data ClientParams #
Constructors
ClientParams | |
Fields
|
Instances
Show ClientParams # | |
Defined in Network.TLS.Parameters Methods showsPrec :: Int -> ClientParams -> ShowS # show :: ClientParams -> String # showList :: [ClientParams] -> ShowS # | |
TLSParams ClientParams # | |
Defined in Network.TLS.Context Methods getTLSCommonParams :: ClientParams -> CommonParams getTLSRole :: ClientParams -> Role doHandshake :: ClientParams -> Context -> IO () doHandshakeWith :: ClientParams -> Context -> Handshake -> IO () |
type Bytes = ByteString #
Deprecated: Use Data.ByteString.Bytestring instead of Bytes.
data ServerParams #
Constructors
ServerParams | |
Fields
|
Instances
Show ServerParams # | |
Defined in Network.TLS.Parameters Methods showsPrec :: Int -> ServerParams -> ShowS # show :: ServerParams -> String # showList :: [ServerParams] -> ShowS # | |
Default ServerParams # | |
Defined in Network.TLS.Parameters Methods def :: ServerParams # | |
TLSParams ServerParams # | |
Defined in Network.TLS.Context Methods getTLSCommonParams :: ServerParams -> CommonParams getTLSRole :: ServerParams -> Role doHandshake :: ServerParams -> Context -> IO () doHandshakeWith :: ServerParams -> Context -> Handshake -> IO () |
data DebugParams #
All settings should not be used in production
Constructors
DebugParams | |
Fields
|
Instances
Show DebugParams # | |
Defined in Network.TLS.Parameters Methods showsPrec :: Int -> DebugParams -> ShowS # show :: DebugParams -> String # showList :: [DebugParams] -> ShowS # | |
Default DebugParams # | |
Defined in Network.TLS.Parameters Methods def :: DebugParams # |
type DHPublic = PublicNumber #
data ClientHooks #
A set of callbacks run by the clients for various corners of TLS establishment
Constructors
ClientHooks | |
Fields
|
Instances
Show ClientHooks # | |
Defined in Network.TLS.Parameters Methods showsPrec :: Int -> ClientHooks -> ShowS # show :: ClientHooks -> String # showList :: [ClientHooks] -> ShowS # | |
Default ClientHooks # | |
Defined in Network.TLS.Parameters Methods def :: ClientHooks # |
data ServerHooks #
A set of callbacks run by the server for various corners of the TLS establishment
Constructors
ServerHooks | |
Fields
|
Instances
Show ServerHooks # | |
Defined in Network.TLS.Parameters Methods showsPrec :: Int -> ServerHooks -> ShowS # show :: ServerHooks -> String # showList :: [ServerHooks] -> ShowS # | |
Default ServerHooks # | |
Defined in Network.TLS.Parameters Methods def :: ServerHooks # |
List all the supported algorithms, versions, ciphers, etc supported.
Constructors
Supported | |
Fields
|
Constructors
Shared | |
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 #
record some data about this connection.
Constructors
Measurement | |
Fields
|
Instances
Eq Measurement # | |
Defined in Network.TLS.Measurement | |
Show Measurement # | |
Defined in Network.TLS.Measurement Methods showsPrec :: Int -> Measurement -> ShowS # show :: Measurement -> String # showList :: [Measurement] -> ShowS # |
data GroupUsage #
Group usage callback possible return values.
Constructors
GroupUsageValid | usage of group accepted |
GroupUsageInsecure | usage of group provides insufficient security |
GroupUsageUnsupported String | usage of group rejected for other reason (specified as string) |
GroupUsageInvalidPublic | usage of group with an invalid public value |
Instances
Eq GroupUsage # | |
Defined in Network.TLS.Parameters | |
Show GroupUsage # | |
Defined in Network.TLS.Parameters Methods showsPrec :: Int -> GroupUsage -> ShowS # show :: GroupUsage -> String # showList :: [GroupUsage] -> ShowS # |
data CertificateUsage #
Certificate Usage callback possible returns values.
Constructors
CertificateUsageAccept | usage of certificate accepted |
CertificateUsageReject CertificateRejectReason | usage of certificate rejected |
Instances
Eq CertificateUsage # | |
Defined in Network.TLS.X509 Methods (==) :: CertificateUsage -> CertificateUsage -> Bool # (/=) :: CertificateUsage -> CertificateUsage -> Bool # | |
Show CertificateUsage # | |
Defined in Network.TLS.X509 Methods showsPrec :: Int -> CertificateUsage -> ShowS # show :: CertificateUsage -> String # showList :: [CertificateUsage] -> ShowS # |
data CertificateRejectReason #
Certificate and Chain rejection reason
Constructors
CertificateRejectExpired | |
CertificateRejectRevoked | |
CertificateRejectUnknownCA | |
CertificateRejectOther String |
Instances
Eq CertificateRejectReason # | |
Defined in Network.TLS.X509 Methods (==) :: CertificateRejectReason -> CertificateRejectReason -> Bool # (/=) :: CertificateRejectReason -> CertificateRejectReason -> Bool # | |
Show CertificateRejectReason # | |
Defined in Network.TLS.X509 Methods showsPrec :: Int -> CertificateRejectReason -> ShowS # show :: CertificateRejectReason -> String # showList :: [CertificateRejectReason] -> ShowS # |
defaultParamsClient :: HostName -> ByteString -> ClientParams #
data MaxFragmentEnum #
Constructors
MaxFragment512 | |
MaxFragment1024 | |
MaxFragment2048 | |
MaxFragment4096 |
Instances
Eq MaxFragmentEnum # | |
Defined in Network.TLS.Extension Methods (==) :: MaxFragmentEnum -> MaxFragmentEnum -> Bool # (/=) :: MaxFragmentEnum -> MaxFragmentEnum -> Bool # | |
Show MaxFragmentEnum # | |
Defined in Network.TLS.Extension Methods showsPrec :: Int -> MaxFragmentEnum -> ShowS # show :: MaxFragmentEnum -> String # showList :: [MaxFragmentEnum] -> ShowS # |
data HashAlgorithm #
Constructors
HashNone | |
HashMD5 | |
HashSHA1 | |
HashSHA224 | |
HashSHA256 | |
HashSHA384 | |
HashSHA512 | |
HashIntrinsic | |
HashOther Word8 |
Instances
Eq HashAlgorithm # | |
Defined in Network.TLS.Struct Methods (==) :: HashAlgorithm -> HashAlgorithm -> Bool # (/=) :: HashAlgorithm -> HashAlgorithm -> Bool # | |
Show HashAlgorithm # | |
Defined in Network.TLS.Struct Methods showsPrec :: Int -> HashAlgorithm -> ShowS # show :: HashAlgorithm -> String # showList :: [HashAlgorithm] -> ShowS # |
data SignatureAlgorithm #
Constructors
SignatureAnonymous | |
SignatureRSA | |
SignatureDSS | |
SignatureECDSA | |
SignatureRSApssSHA256 | |
SignatureRSApssSHA384 | |
SignatureRSApssSHA512 | |
SignatureEd25519 | |
SignatureEd448 | |
SignatureOther Word8 |
Instances
Eq SignatureAlgorithm # | |
Defined in Network.TLS.Struct Methods (==) :: SignatureAlgorithm -> SignatureAlgorithm -> Bool # (/=) :: SignatureAlgorithm -> SignatureAlgorithm -> Bool # | |
Show SignatureAlgorithm # | |
Defined in Network.TLS.Struct Methods showsPrec :: Int -> SignatureAlgorithm -> ShowS # show :: SignatureAlgorithm -> String # showList :: [SignatureAlgorithm] -> ShowS # |
data CertificateType #
Constructors
Instances
Eq CertificateType # | |
Defined in Network.TLS.Struct Methods (==) :: CertificateType -> CertificateType -> Bool # (/=) :: CertificateType -> CertificateType -> Bool # | |
Show CertificateType # | |
Defined in Network.TLS.Struct Methods showsPrec :: Int -> CertificateType -> ShowS # show :: CertificateType -> String # showList :: [CertificateType] -> ShowS # |
raw types
data ProtocolType #
Constructors
ProtocolType_ChangeCipherSpec | |
ProtocolType_Alert | |
ProtocolType_Handshake | |
ProtocolType_AppData | |
ProtocolType_DeprecatedHandshake |
Instances
Eq ProtocolType # | |
Defined in Network.TLS.Struct | |
Show ProtocolType # | |
Defined in Network.TLS.Struct Methods showsPrec :: Int -> ProtocolType -> ShowS # show :: ProtocolType -> String # showList :: [ProtocolType] -> ShowS # |
Constructors
Header ProtocolType Version Word16 |
Session
type SessionID = ByteString #
A session ID
data SessionData #
Session data to resume
Constructors
SessionData | |
Fields
|
Instances
Eq SessionData # | |
Defined in Network.TLS.Types | |
Show SessionData # | |
Defined in Network.TLS.Types Methods showsPrec :: Int -> SessionData -> ShowS # show :: SessionData -> String # showList :: [SessionData] -> ShowS # |
data SessionManager #
A session manager
Constructors
SessionManager | |
Fields
|
Backend abstraction
Connection IO backend
Constructors
Backend | |
Fields
|
Instances
HasBackend Backend # | |
Defined in Network.TLS.Backend |
Context object
ctxConnection :: Context -> Backend #
return the backend object associated with this context
Minimal complete definition
getTLSCommonParams, getTLSRole, doHandshake, doHandshakeWith
Instances
TLSParams ServerParams # | |
Defined in Network.TLS.Context Methods getTLSCommonParams :: ServerParams -> CommonParams getTLSRole :: ServerParams -> Role doHandshake :: ServerParams -> Context -> IO () doHandshakeWith :: ServerParams -> Context -> Handshake -> IO () | |
TLSParams ClientParams # | |
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 #
Instances
HasBackend Handle # | |
Defined in Network.TLS.Backend | |
HasBackend Socket # | |
Defined in Network.TLS.Backend | |
HasBackend Backend # | |
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 () #
contextClose :: Context -> IO () #
contextHookSetCertificateRecv :: Context -> (CertificateChain -> IO ()) -> IO () #
contextHookSetLogging :: Context -> Logging -> IO () #
Information gathering
data Information #
Information related to a running context, e.g. current cipher
Constructors
Information | |
Instances
Eq Information # | |
Defined in Network.TLS.Context.Internal | |
Show Information # | |
Defined in Network.TLS.Context.Internal Methods showsPrec :: Int -> Information -> ShowS # show :: Information -> String # showList :: [Information] -> ShowS # |
data ClientRandom #
Instances
Eq ClientRandom # | |
Defined in Network.TLS.Struct | |
Show ClientRandom # | |
Defined in Network.TLS.Struct Methods showsPrec :: Int -> ClientRandom -> ShowS # show :: ClientRandom -> String # showList :: [ClientRandom] -> ShowS # |
data ServerRandom #
Instances
Eq ServerRandom # | |
Defined in Network.TLS.Struct | |
Show ServerRandom # | |
Defined in Network.TLS.Struct Methods showsPrec :: Int -> ServerRandom -> ShowS # show :: ServerRandom -> String # showList :: [ServerRandom] -> ShowS # |
contextGetInformation :: Context -> IO (Maybe Information) #
Information about the current context
Credentials
newtype Credentials #
Constructors
Credentials [Credential] |
Instances
Semigroup Credentials # | |
Defined in Network.TLS.Credentials Methods (<>) :: Credentials -> Credentials -> Credentials # sconcat :: NonEmpty Credentials -> Credentials # stimes :: Integral b => b -> Credentials -> Credentials # | |
Monoid Credentials # | |
Defined in Network.TLS.Credentials Methods mempty :: Credentials # mappend :: Credentials -> Credentials -> Credentials # mconcat :: [Credentials] -> Credentials # |
type Credential = (CertificateChain, PrivKey) #
Arguments
:: FilePath | public certificate (X.509 format) |
-> FilePath | private key associated |
-> IO (Either String Credential) |
try to create a new credential object from a public certificate and the associated private key that are stored on the filesystem in PEM format.
credentialLoadX509FromMemory :: ByteString -> ByteString -> Either String Credential #
similar to credentialLoadX509
but take the certificate
and private key from memory instead of from the filesystem.
Arguments
:: FilePath | public certificate (X.509 format) |
-> [FilePath] | chain certificates (X.509 format) |
-> FilePath | private key associated |
-> IO (Either String Credential) |
similar to credentialLoadX509
but also allow specifying chain
certificates.
credentialLoadX509ChainFromMemory :: ByteString -> [ByteString] -> ByteString -> Either String Credential #
similar to credentialLoadX509FromMemory
but also allow
specifying chain certificates.
Initialisation and Termination of context
bye :: MonadIO m => Context -> m () #
notify the context that this side wants to close connection. this is important that it is called before closing the handle, otherwise the session might not be resumable (for version < TLS1.2).
this doesn't actually close the handle
handshake :: MonadIO m => Context -> m () #
Handshake for a new TLS connection This is to be called at the beginning of a connection, and during renegotiation
Application Layer Protocol Negotiation
getNegotiatedProtocol :: MonadIO m => Context -> m (Maybe ByteString) #
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) #
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 () #
sendData sends a bunch of data. It will automatically chunk data to acceptable packet size
recvData :: MonadIO m => Context -> m ByteString #
recvData get data out of Data packet, and automatically renegotiate if a Handshake ClientHello is received
recvData' :: MonadIO m => Context -> m ByteString #
Deprecated: use recvData that returns strict bytestring
same as recvData but returns a lazy bytestring.
Crypto Key
Public key types known and used in X.509
Constructors
PubKeyRSA PublicKey | RSA public key |
PubKeyDSA PublicKey | DSA public key |
PubKeyDH (Integer, Integer, Integer, Maybe Integer, ([Word8], Integer)) | DH format with (p,g,q,j,(seed,pgenCounter)) |
PubKeyEC PubKeyEC | EC public key |
PubKeyX25519 PublicKey | X25519 public key |
PubKeyX448 PublicKey | X448 public key |
PubKeyEd25519 PublicKey | Ed25519 public key |
PubKeyEd448 PublicKey | Ed448 public key |
PubKeyUnknown OID ByteString | unrecognized format |
Private key types known and used in X.509
Constructors
PrivKeyRSA PrivateKey | RSA private key |
PrivKeyDSA PrivateKey | DSA private key |
PrivKeyEC PrivKeyEC | EC private key |
PrivKeyX25519 SecretKey | X25519 private key |
PrivKeyX448 SecretKey | X448 private key |
PrivKeyEd25519 SecretKey | Ed25519 private key |
PrivKeyEd448 SecretKey | Ed448 private key |
Compressions & Predefined compressions
data Compression #
every compression need to be wrapped in this, to fit in structure
Constructors
CompressionC a => Compression a |
Instances
Eq Compression # | |
Defined in Network.TLS.Compression | |
Show Compression # | |
Defined in Network.TLS.Compression Methods showsPrec :: Int -> Compression -> ShowS # show :: Compression -> String # showList :: [Compression] -> ShowS # |
class CompressionC a where #
supported compression algorithms need to be part of this class
Methods
compressionCID :: a -> CompressionID #
compressionCDeflate :: a -> ByteString -> (a, ByteString) #
compressionCInflate :: a -> ByteString -> (a, ByteString) #
nullCompression :: Compression #
default null compression
Ciphers & Predefined ciphers
data CipherKeyExchangeType #
Constructors
Instances
Eq CipherKeyExchangeType # | |
Defined in Network.TLS.Cipher Methods (==) :: CipherKeyExchangeType -> CipherKeyExchangeType -> Bool # (/=) :: CipherKeyExchangeType -> CipherKeyExchangeType -> Bool # | |
Show CipherKeyExchangeType # | |
Defined in Network.TLS.Cipher Methods showsPrec :: Int -> CipherKeyExchangeType -> ShowS # show :: CipherKeyExchangeType -> String # showList :: [CipherKeyExchangeType] -> ShowS # |
Constructors
Bulk | |
Fields
|
data BulkFunctions #
Constructors
BulkBlockF (BulkDirection -> BulkKey -> BulkBlock) | |
BulkStreamF (BulkDirection -> BulkKey -> BulkStream) | |
BulkAeadF (BulkDirection -> BulkKey -> BulkAEAD) |
data BulkDirection #
Constructors
BulkEncrypt | |
BulkDecrypt |
Instances
Eq BulkDirection # | |
Defined in Network.TLS.Cipher Methods (==) :: BulkDirection -> BulkDirection -> Bool # (/=) :: BulkDirection -> BulkDirection -> Bool # | |
Show BulkDirection # | |
Defined in Network.TLS.Cipher Methods showsPrec :: Int -> BulkDirection -> ShowS # show :: BulkDirection -> String # showList :: [BulkDirection] -> ShowS # |
newtype BulkStream #
Constructors
BulkStream (ByteString -> (ByteString, BulkStream)) |
type BulkBlock = BulkIV -> ByteString -> (ByteString, BulkIV) #
type BulkAEAD = BulkNonce -> ByteString -> BulkAdditionalData -> (ByteString, AuthTag) #
Cipher algorithm
Constructors
Cipher | |
Fields
|
cipherKeyBlockSize :: Cipher -> Int #
type BulkKey = ByteString #
type BulkIV = ByteString #
type BulkNonce = ByteString #
type BulkAdditionalData = ByteString #
cipherAllowedForVersion :: Version -> Cipher -> Bool #
Check if a specific Cipher
is allowed to be used
with the version specified
hasMAC :: BulkFunctions -> Bool #
hasRecordIV :: BulkFunctions -> Bool #
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 # | |
Show TLSError # | |
Exception TLSError # | |
Defined in Network.TLS.Struct Methods toException :: TLSError -> SomeException # fromException :: SomeException -> Maybe TLSError # displayException :: TLSError -> String # |
Constructors
RSAError Error | |
KxUnsupported |
data AlertDescription #
Constructors
Instances
Eq AlertDescription # | |
Defined in Network.TLS.Struct Methods (==) :: AlertDescription -> AlertDescription -> Bool # (/=) :: AlertDescription -> AlertDescription -> Bool # | |
Show AlertDescription # | |
Defined in Network.TLS.Struct Methods showsPrec :: Int -> AlertDescription -> ShowS # show :: AlertDescription -> String # showList :: [AlertDescription] -> ShowS # |
Exceptions
data TLSException #
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 # | |
Defined in Network.TLS.Struct | |
Show TLSException # | |
Defined in Network.TLS.Struct Methods showsPrec :: Int -> TLSException -> ShowS # show :: TLSException -> String # showList :: [TLSException] -> ShowS # | |
Exception TLSException # | |
Defined in Network.TLS.Struct Methods toException :: TLSException -> SomeException # fromException :: SomeException -> Maybe TLSException # displayException :: TLSException -> String # |
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.
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 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.
Constructors
ValidationHooks | |
Fields
|
Instances
Default ValidationHooks | |
Defined in Data.X509.Validation Methods def :: ValidationHooks # |
X509 Validation Cache
data ValidationCache #
All the callbacks needed for querying and adding to the cache.
Constructors
ValidationCache | |
Fields
|
Instances
Default ValidationCache | |
Defined in Data.X509.Validation.Cache Methods def :: ValidationCache # |
data ValidationCacheResult #
The result of a cache query
Constructors
ValidationCachePass | cache allow this fingerprint to go through |
ValidationCacheDenied String | cache denied this fingerprint for further validation |
ValidationCacheUnknown | unknown fingerprint in cache |
Instances
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 #
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.