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

Portabilityunknown
Stabilityexperimental
MaintainerVincent Hanquez <vincent@snarc.org>

Network.TLS

Contents

Description

 

Synopsis

Context configuration

data TLSParams Source

Constructors

TLSParams 

Fields

pConnectVersion :: Version

version to use on client connection.

pAllowedVersions :: [Version]

allowed versions that we can use.

pCiphers :: [Cipher]

all ciphers supported ordered by priority.

pCompressions :: [Compression]

all compression supported ordered by priority.

pWantClientCert :: Bool

request a certificate from client. use by server only.

pUseSecureRenegotiation :: Bool
 
pUseSession :: Bool
 
pCertificates :: [(X509, Maybe PrivateKey)]

the cert chain for this context with the associated keys if any.

pLogging :: TLSLogging

callback for logging

onHandshake :: Measurement -> IO Bool

callback on a beggining of handshake

onCertificatesRecv :: [X509] -> IO TLSCertificateUsage

callback to verify received cert chain.

onSessionResumption :: SessionID -> IO (Maybe SessionData)

callback to maybe resume session on server.

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

callback when session have been established

onSessionInvalidated :: SessionID -> IO ()

callback when session is invalidated by error

sessionResumeWith :: Maybe (SessionID, SessionData)

try to establish a connection using this session.

Instances

data TLSLogging Source

Constructors

TLSLogging 

Fields

loggingPacketSent :: String -> IO ()
 
loggingPacketRecv :: String -> IO ()
 
loggingIOSent :: Bytes -> IO ()
 
loggingIORecv :: Header -> Bytes -> IO ()
 

data TLSCertificateUsage Source

Certificate Usage callback possible returns values.

Constructors

CertificateUsageAccept

usage of certificate accepted

CertificateUsageReject TLSCertificateRejectReason

usage of certificate rejected

Context object

data TLSCtx a Source

A TLS Context is a handle augmented by tls specific state and parameters

ctxConnection :: TLSCtx a -> aSource

return the connection object associated with this context

Creating a context

client :: (MonadIO m, CryptoRandomGen g) => TLSParams -> g -> Handle -> m (TLSCtx Handle)Source

Create a new Client context with a configuration, a RNG, and a Handle. It reconfigures the handle buffermode to noBuffering

server :: (MonadIO m, CryptoRandomGen g) => TLSParams -> g -> Handle -> m (TLSCtx Handle)Source

Create a new Server context with a configuration, a RNG, and a Handle. It reconfigures the handle buffermode to noBuffering

Initialisation and Termination of context

bye :: MonadIO m => TLSCtx c -> 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 => TLSCtx c -> m BoolSource

Handshake for a new TLS connection This is to be called at the beginning of a connection, and during renegociation

High level API

sendData :: MonadIO m => TLSCtx c -> ByteString -> m ()Source

sendData sends a bunch of data. It will automatically chunk data to acceptable packet size

recvData :: MonadIO m => TLSCtx c -> m ByteStringSource

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

Crypto Key

data PrivateKey Source

Constructors

PrivRSA PrivateKey 

Instances

Compressions & Predefined compressions

class CompressionC a whereSource

supported compression algorithms need to be part of this class

Instances

CompressionC NullCompression 

data Compression Source

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

Constructors

forall a . CompressionC a => Compression a 

Instances

nullCompression :: CompressionSource

default null compression

Ciphers & Predefined ciphers

data Cipher Source

Cipher algorithm

Constructors

Cipher 

Fields

cipherID :: Word16
 
cipherName :: String
 
cipherHash :: Hash
 
cipherBulk :: Bulk
 
cipherKeyExchange :: CipherKeyExchangeType
 
cipherMinVer :: Maybe Version
 

Instances

data Bulk Source

Constructors

Bulk 

Fields

bulkName :: String
 
bulkKeySize :: Int
 
bulkIVSize :: Int
 
bulkBlockSize :: Int
 
bulkF :: BulkFunctions
 

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