License | BSD-style |
---|---|
Maintainer | Vincent Hanquez <vincent@snarc.org> |
Stability | experimental |
Portability | unknown |
Safe Haskell | None |
Language | Haskell98 |
- 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
- member redefined for the class abstraction
- helper
- Ciphers & Predefined ciphers
- Versions
- Errors
- Exceptions
- X509 Validation
- X509 Validation Cache
- Key exchange group
- 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 {}
- 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
- 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 :: *
- class CompressionC a where
- data Compression = CompressionC a => Compression a
- type CompressionID = Word8
- nullCompression :: Compression
- data NullCompression
- compressionID :: Compression -> CompressionID
- compressionDeflate :: ByteString -> Compression -> (Compression, ByteString)
- compressionInflate :: ByteString -> Compression -> (Compression, ByteString)
- compressionIntersectID :: [Compression] -> [Word8] -> [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 Source #
ClientParams | |
|
type Bytes = ByteString Source #
Deprecated: Use Data.ByteString.Bytestring instead of Bytes.
data ServerParams Source #
ServerParams | |
|
data DebugParams Source #
All settings should not be used in production
DebugParams | |
|
type DHPublic = PublicNumber Source #
data ClientHooks Source #
A set of callbacks run by the clients for various corners of TLS establishment
ClientHooks | |
|
data ServerHooks Source #
A set of callbacks run by the server for various corners of the TLS establishment
ServerHooks | |
|
List all the supported algorithms, versions, ciphers, etc supported.
Supported | |
|
A collection of hooks actions.
Hooks | |
|
Hooks for logging
This is called when sending and receiving packets and IO
Logging | |
|
data Measurement Source #
record some data about this connection.
Measurement | |
|
data GroupUsage Source #
Group usage callback possible return values.
GroupUsageValid | usage of group accepted |
GroupUsageInsecure | usage of group provides insufficient security |
GroupUsageUnsupported String | usage of group rejected for other reason (specified as string) |
GroupUsageInvalidPublic | usage of group with an invalid public value |
data CertificateUsage Source #
Certificate Usage callback possible returns values.
CertificateUsageAccept | usage of certificate accepted |
CertificateUsageReject CertificateRejectReason | usage of certificate rejected |
data CertificateRejectReason Source #
Certificate and Chain rejection reason
defaultParamsClient :: HostName -> ByteString -> ClientParams Source #
data MaxFragmentEnum Source #
data HashAlgorithm Source #
data SignatureAlgorithm Source #
data CertificateType Source #
raw types
data ProtocolType Source #
Session
type SessionID = ByteString Source #
A session ID
data SessionData Source #
Session data to resume
SessionData | |
|
data SessionManager Source #
A session manager
SessionManager | |
|
Backend abstraction
Connection IO backend
Backend | |
|
Context object
ctxConnection :: Context -> Backend Source #
return the backend object associated with this context
getTLSCommonParams, getTLSRole, doHandshake, doHandshakeWith
class HasBackend a where Source #
initializeBackend :: a -> IO () Source #
getBackend :: a -> Backend Source #
Creating a context
:: (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.
:: (MonadIO m, TLSParams params) | |
=> Handle | Handle of the connection. |
-> params | Parameters of the context. |
-> m Context |
Deprecated: use contextNew
create a new context on an handle.
:: (MonadIO m, TLSParams params) | |
=> Socket | Socket of the connection. |
-> params | Parameters of the context. |
-> m Context |
Deprecated: use contextNew
create a new context on a socket.
contextFlush :: Context -> IO () Source #
contextClose :: Context -> IO () Source #
contextHookSetCertificateRecv :: Context -> (CertificateChain -> IO ()) -> IO () Source #
Information gathering
contextGetInformation :: Context -> IO (Maybe Information) Source #
Information about the current context
Credentials
newtype Credentials Source #
type Credential = (CertificateChain, PrivKey) Source #
:: FilePath | public certificate (X.509 format) |
-> FilePath | private key associated |
-> IO (Either String Credential) |
try to create a new credential object from a public certificate and the associated private key that are stored on the filesystem in PEM format.
credentialLoadX509FromMemory :: ByteString -> ByteString -> Either String Credential Source #
similar to credentialLoadX509
but take the certificate
and private key from memory instead of from the filesystem.
credentialLoadX509Chain Source #
:: FilePath | public certificate (X.509 format) |
-> [FilePath] | chain certificates (X.509 format) |
-> FilePath | private key associated |
-> IO (Either String Credential) |
similar to credentialLoadX509
but also allow specifying chain
certificates.
credentialLoadX509ChainFromMemory :: ByteString -> [ByteString] -> ByteString -> Either String Credential Source #
similar to credentialLoadX509FromMemory
but also allow
specifying chain certificates.
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
Public key types known and used in X.509
Private key types known and used in X.509
PrivKeyRSA PrivateKey | RSA private key |
PrivKeyDSA PrivateKey | DSA private key |
PrivKeyEC PrivKeyEC | EC private key |
Compressions & Predefined compressions
class CompressionC a where Source #
supported compression algorithms need to be part of this class
compressionCID :: a -> CompressionID Source #
compressionCDeflate :: a -> ByteString -> (a, ByteString) Source #
compressionCInflate :: a -> ByteString -> (a, ByteString) Source #
data Compression Source #
every compression need to be wrapped in this, to fit in structure
CompressionC a => Compression a |
type CompressionID = Word8 Source #
Compression identification
nullCompression :: Compression Source #
default null compression
data NullCompression Source #
This is the default compression which is a NOOP.
member redefined for the class abstraction
compressionID :: Compression -> CompressionID Source #
return the associated ID for this algorithm
compressionDeflate :: ByteString -> Compression -> (Compression, ByteString) Source #
deflate (compress) a bytestring using a compression context and return the result along with the new compression context.
compressionInflate :: ByteString -> Compression -> (Compression, ByteString) Source #
inflate (decompress) a bytestring using a compression context and return the result along the new compression context.
helper
compressionIntersectID :: [Compression] -> [Word8] -> [Compression] Source #
intersect a list of ids commonly given by the other side with a list of compression the function keeps the list of compression in order, to be able to find quickly the prefered compression.
Ciphers & Predefined ciphers
data CipherKeyExchangeType Source #
Bulk | |
|
data BulkFunctions Source #
BulkBlockF (BulkDirection -> BulkKey -> BulkBlock) | |
BulkStreamF (BulkDirection -> BulkKey -> BulkStream) | |
BulkAeadF (BulkDirection -> BulkKey -> BulkAEAD) |
data BulkDirection Source #
newtype BulkStream Source #
BulkStream (ByteString -> (ByteString, BulkStream)) |
type BulkBlock = BulkIV -> ByteString -> (ByteString, BulkIV) Source #
type BulkAEAD = BulkNonce -> ByteString -> BulkAdditionalData -> (ByteString, AuthTag) Source #
Cipher algorithm
cipherKeyBlockSize :: Cipher -> Int Source #
type BulkKey = ByteString Source #
type BulkIV = ByteString Source #
type BulkNonce = ByteString Source #
type BulkAdditionalData = ByteString Source #
cipherAllowedForVersion :: Version -> Cipher -> Bool Source #
Check if a specific Cipher
is allowed to be used
with the version specified
hasMAC :: BulkFunctions -> Bool Source #
hasRecordIV :: BulkFunctions -> Bool Source #
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
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 |
data AlertDescription Source #
Exceptions
data TLSException Source #
TLS Exceptions related to bad user usage or asynchronous errors
Terminated Bool String TLSError | Early termination exception with the reason and the error associated |
HandshakeFailed TLSError | Handshake failed for the reason attached |
ConnectionNotEstablished | Usage error when the connection has not been established and the user is trying to send or receive data |
X509 Validation
data ValidationChecks :: * #
A set of checks to activate or parametrize to perform on certificates.
It's recommended to use defaultChecks
to create the structure,
to better cope with future changes or expansion of the structure.
ValidationChecks | |
|
data ValidationHooks :: * #
A set of hooks to manipulate the way the verification works.
BEWARE, it's easy to change behavior leading to compromised security.
ValidationHooks | |
|
X509 Validation Cache
data ValidationCache :: * #
All the callbacks needed for querying and adding to the cache.
ValidationCache | |
|
data ValidationCacheResult :: * #
The result of a cache query
ValidationCachePass | cache allow this fingerprint to go through |
ValidationCacheDenied String | cache denied this fingerprint for further validation |
ValidationCacheUnknown | unknown fingerprint in cache |
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.