tls-1.2.8: TLS/SSL protocol native implementation (Server and Client)

Portabilityunknown
Stabilityexperimental
MaintainerVincent Hanquez <vincent@snarc.org>
Safe HaskellNone

Network.TLS

Contents

Description

 

Synopsis

Context configuration

data ClientParams Source

Constructors

ClientParams 

Fields

clientUseMaxFragmentLength :: Maybe MaxFragmentEnum
 
clientServerIdentification :: (HostName, Bytes)

Define the name of the server, along with an extra service identification blob. this is important that the hostname part is properly filled for security reason, as it allow to properly associate the remote side with the given certificate during a handshake.

The extra blob is useful to differentiate services running on the same host, but that might have different certificates given. It's only used as part of the X509 validation infrastructure.

clientUseServerNameIndication :: Bool

Allow the use of the Server Name Indication TLS extension during handshake, which allow the client to specify which host name, it's trying to access. This is useful to distinguish CNAME aliasing (e.g. web virtual host).

clientWantSessionResume :: Maybe (SessionID, SessionData)

try to establish a connection using this session.

clientShared :: Shared
 
clientHooks :: ClientHooks
 
clientSupported :: Supported
 

Instances

data ServerParams Source

Constructors

ServerParams 

Fields

serverWantClientCert :: Bool

request a certificate from client.

serverCACertificates :: [SignedCertificate]

This is a list of certificates from which the disinguished names are sent in certificate request messages. For TLS1.0, it should not be empty.

serverDHEParams :: Maybe DHParams

Server Optional Diffie Hellman parameters. If this value is not properly set, no Diffie Hellman key exchange will take place.

serverShared :: Shared
 
serverHooks :: ServerHooks
 
serverSupported :: Supported
 

data ClientHooks Source

A set of callbacks run by the clients for various corners of TLS establishment

Constructors

ClientHooks 

Fields

onCertificateRequest :: ([CertificateType], Maybe [HashAndSignatureAlgorithm], [DistinguishedName]) -> IO (Maybe (CertificateChain, PrivKey))

This action is called when the server sends a certificate request. The parameter is the information from the request. The action should select a certificate chain of one of the given certificate types where the last certificate in the chain should be signed by one of the given distinguished names. Each certificate should be signed by the following one, except for the last. At least the first of the certificates in the chain must have a corresponding private key, because that is used for signing the certificate verify message.

Note that is is the responsibility of this action to select a certificate matching one of the requested certificate types. Returning a non-matching one will lead to handshake failure later.

Returning a certificate chain not matching the distinguished names may lead to problems or not, depending whether the server accepts it.

onNPNServerSuggest :: Maybe ([ByteString] -> IO ByteString)
 
onServerCertificate :: CertificateStore -> ValidationCache -> ServiceID -> CertificateChain -> IO [FailedReason]
 

data ServerHooks Source

A set of callbacks run by the server for various corners of the TLS establishment

Constructors

ServerHooks 

Fields

onClientCertificate :: CertificateChain -> IO CertificateUsage

This action is called when a client certificate chain is received from the client. When it returns a CertificateUsageReject value, the handshake is aborted.

onUnverifiedClientCert :: IO Bool

This action is called when the client certificate cannot be verified. A Nothing argument indicates a wrong signature, a 'Just e' message signals a crypto error.

onCipherChoosing :: Version -> [Cipher] -> Cipher

Allow the server to choose the cipher relative to the the client version and the client list of ciphers.

This could be useful with old clients and as a workaround to the BEAST (where RC4 is sometimes prefered with TLS < 1.1)

The client cipher list cannot be empty.

onSuggestNextProtocols :: IO (Maybe [ByteString])

suggested next protocols accoring to the next protocol negotiation extension.

onNewHandshake :: Measurement -> IO Bool

at each new handshake, we call this hook to see if we allow handshake to happens.

data Supported Source

List all the supported algorithms, versions, ciphers, etc supported.

Constructors

Supported 

Fields

supportedVersions :: [Version]

Supported Versions by this context On the client side, the highest version will be used to establish the connection. On the server side, the highest version that is less or equal than the client version will be chosed.

supportedCiphers :: [Cipher]

Supported cipher methods

supportedCompressions :: [Compression]

supported compressions methods

supportedHashSignatures :: [HashAndSignatureAlgorithm]

All supported hash/signature algorithms pair for client certificate verification, ordered by decreasing priority.

supportedSecureRenegotiation :: Bool

Set if we support secure renegotiation.

supportedSession :: Bool

Set if we support session.

data Hooks Source

A collection of hooks actions.

Constructors

Hooks 

Fields

hookRecvHandshake :: Handshake -> IO Handshake

called at each handshake message received

hookRecvCertificates :: CertificateChain -> IO ()

called at each certificate chain message received

hookLogging :: Logging

hooks on IO and packets, receiving and sending.

Instances

data Logging Source

Hooks for logging

This is called when sending and receiving packets and IO

Constructors

Logging 

Instances

data Measurement Source

record some data about this connection.

Constructors

Measurement 

Fields

nbHandshakes :: !Word32

number of handshakes on this context

bytesReceived :: !Word32

bytes received since last handshake

bytesSent :: !Word32

bytes sent since last handshake

data CertificateUsage Source

Certificate Usage callback possible returns values.

Constructors

CertificateUsageAccept

usage of certificate accepted

CertificateUsageReject CertificateRejectReason

usage of certificate rejected

raw types

Session

type SessionID = ByteStringSource

A session ID

data SessionData Source

Session data to resume

data SessionManager Source

A session manager

Constructors

SessionManager 

Fields

sessionResume :: SessionID -> IO (Maybe SessionData)

used on server side to decide whether to resume a client session.

sessionEstablish :: SessionID -> SessionData -> IO ()

used when a session is established.

sessionInvalidate :: SessionID -> IO ()

used when a session is invalidated.

Backend abstraction

data Backend Source

Connection IO backend

Constructors

Backend 

Fields

backendFlush :: IO ()

Flush the connection sending buffer, if any.

backendClose :: IO ()

Close the connection.

backendSend :: ByteString -> IO ()

Send a bytestring through the connection.

backendRecv :: Int -> IO ByteString

Receive specified number of bytes from the connection.

Context object

data Context Source

A TLS Context keep tls specific state, parameters and backend information.

ctxConnection :: Context -> BackendSource

return the backend object associated with this context

Creating a context

contextNewSource

Arguments

:: (MonadIO m, CPRG rng, HasBackend backend, TLSParams params) 
=> backend

Backend abstraction with specific method to interact with the connection type.

-> params

Parameters of the context.

-> rng

Random number generator associated with this context.

-> m Context 

create a new context using the backend and parameters specified.

contextNewOnHandleSource

Arguments

:: (MonadIO m, CPRG rng, TLSParams params) 
=> Handle

Handle of the connection.

-> params

Parameters of the context.

-> rng

Random number generator associated with this context.

-> m Context 

Deprecated: use contextNew

create a new context on an handle.

contextNewOnSocketSource

Arguments

:: (MonadIO m, CPRG rng, TLSParams params) 
=> Socket

Socket of the connection.

-> params

Parameters of the context.

-> rng

Random number generator associated with this context.

-> m Context 

Deprecated: use contextNew

create a new context on a socket.

contextHookSetHandshakeRecv :: Context -> (Handshake -> IO Handshake) -> IO ()Source

Information gathering

data Information Source

Information related to a running context, e.g. current cipher

contextGetInformation :: Context -> IO (Maybe Information)Source

Information about the current context

Credentials

newtype Credentials Source

Constructors

Credentials [Credential] 

Instances

credentialLoadX509Source

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 :: Bytes -> Bytes -> Either String CredentialSource

similar to credentialLoadX509 but take the certificate and private key from memory instead of from the filesystem.

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

Next Protocol Negotiation

getNegotiatedProtocol :: MonadIO m => Context -> m (Maybe ByteString)Source

If the Next Protocol Negotiation extension has been used, this will return get the protocol agreed upon.

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 ByteStringSource

recvData get data out of Data packet, and automatically renegotiate if a Handshake ClientHello is received

recvData' :: MonadIO m => Context -> m ByteStringSource

Deprecated: use recvData that returns strict bytestring

same as recvData but returns a lazy bytestring.

Crypto Key

data PubKey

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))

PubKeyECDSA CurveName ByteString 
PubKeyUnknown OID ByteString

unrecognized format

data PrivKey

Private key types known and used in X.509

Constructors

PrivKeyRSA PrivateKey

RSA private key

PrivKeyDSA PrivateKey

DSA private key

Instances

Compressions & Predefined compressions

class CompressionC a whereSource

supported compression algorithms need to be part of this class

data Compression Source

every compression need to be wrapped in this, to fit in structure

Constructors

forall a . CompressionC a => Compression a 

type CompressionID = Word8Source

Compression identification

nullCompression :: CompressionSource

default null compression

data NullCompression Source

This is the default compression which is a NOOP.

member redefined for the class abstraction

compressionID :: Compression -> CompressionIDSource

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 Bulk Source

Instances

data Hash Source

Constructors

Hash 

Instances

type CipherID = Word16Source

Cipher identification

cipherAllowedForVersion :: Version -> Cipher -> BoolSource

Check if a specific Cipher is allowed to be used with the version specified

Versions

data Version Source

Versions known to TLS

SSL2 is just defined, but this version is and will not be supported.

Constructors

SSL2 
SSL3 
TLS10 
TLS11 
TLS12 

Errors

data KxError Source

Instances

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

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

checkTimeValidity :: Bool

check time validity of every certificate in the chain. the make sure that current time is between each validity bounds in the certificate

checkAtTime :: Maybe UTCTime

The time when the validity check happens. When set to Nothing, the current time will be used

checkStrictOrdering :: Bool

Check that no certificate is included that shouldn't be included. unfortunately despite the specification violation, a lots of real world server serves useless and usually old certificates that are not relevant to the certificate sent, in their chain.

checkCAConstraints :: Bool

Check that signing certificate got the CA basic constraint. this is absolutely not recommended to turn it off.

checkExhaustive :: Bool

Check the whole certificate chain without stopping at the first failure. Allow gathering a exhaustive list of failure reasons. if this is turn off, it's absolutely not safe to ignore a failed reason even it doesn't look serious (e.g. Expired) as other more serious checks would not have been performed.

checkLeafV3 :: Bool

Check that the leaf certificate is version 3. If disable, version 2 certificate is authorized in leaf position and key usage cannot be checked.

checkLeafKeyUsage :: [ExtKeyUsageFlag]

Check that the leaf certificate is authorized to be used for certain usage. If set to empty list no check are performed, otherwise all the flags is the list need to exists in the key usage extension. If the extension is not present, the check will pass and behave as if the certificate key is not restricted to any specific usage.

checkLeafKeyPurpose :: [ExtKeyUsagePurpose]

Check that the leaf certificate is authorized to be used for certain purpose. If set to empty list no check are performed, otherwise all the flags is the list need to exists in the extended key usage extension if present. If the extension is not present, then the check will pass and behave as if the certificate is not restricted to any specific purpose.

checkFQHN :: Bool

Check the top certificate names matching the fully qualified hostname (FQHN). it's not recommended to turn this check off, if no other name checks are performed.

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

hookMatchSubjectIssuer :: DistinguishedName -> Certificate -> Bool

check the the issuer DistinguishedName match the subject DistinguishedName of a certificate.

hookValidateTime :: UTCTime -> Certificate -> [FailedReason]

validate that the parametrized time valide with the certificate in argument

hookValidateName :: HostName -> Certificate -> [FailedReason]

validate the certificate leaf name with the DNS named used to connect

hookFilterReason :: [FailedReason] -> [FailedReason]

user filter to modify the list of failure reasons

X509 Validation Cache

data ValidationCache

All the callbacks needed for querying and adding to the cache.

Constructors

ValidationCache 

Fields

cacheQuery :: ValidationCacheQueryCallback

cache querying callback

cacheAdd :: ValidationCacheAddCallback

cache adding callback

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

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.