Portability | unknown |
---|---|
Stability | experimental |
Maintainer | Vincent Hanquez <vincent@snarc.org> |
- data TLSParams = TLSParams {
- pConnectVersion :: Version
- pAllowedVersions :: [Version]
- pCiphers :: [Cipher]
- pCompressions :: [Compression]
- pWantClientCert :: Bool
- pUseSecureRenegotiation :: Bool
- pCertificates :: [(X509, Maybe PrivateKey)]
- pLogging :: TLSLogging
- onCertificatesRecv :: [X509] -> IO TLSCertificateUsage
- data TLSLogging = TLSLogging {
- loggingPacketSent :: String -> IO ()
- loggingPacketRecv :: String -> IO ()
- loggingIOSent :: Bytes -> IO ()
- loggingIORecv :: Header -> Bytes -> IO ()
- data TLSCertificateUsage
- data TLSCertificateRejectReason
- defaultParams :: TLSParams
- defaultLogging :: TLSLogging
- data TLSCtx a
- ctxConnection :: TLSCtx a -> a
- client :: (MonadIO m, CryptoRandomGen g) => TLSParams -> g -> Handle -> m (TLSCtx Handle)
- server :: (MonadIO m, CryptoRandomGen g) => TLSParams -> g -> Handle -> m (TLSCtx Handle)
- bye :: MonadIO m => TLSCtx c -> m ()
- handshake :: MonadIO m => TLSCtx c -> m Bool
- sendData :: MonadIO m => TLSCtx c -> ByteString -> m ()
- recvData :: MonadIO m => TLSCtx c -> m ByteString
- data PrivateKey = PrivRSA PrivateKey
- class CompressionC a where
- compressionCID :: a -> Word8
- compressionCDeflate :: a -> ByteString -> (a, ByteString)
- compressionCInflate :: a -> ByteString -> (a, ByteString)
- data Compression = forall a . CompressionC a => Compression a
- nullCompression :: Compression
- data Cipher = Cipher {
- cipherID :: Word16
- cipherName :: String
- cipherHash :: Hash
- cipherBulk :: Bulk
- cipherKeyExchange :: CipherKeyExchangeType
- cipherMinVer :: Maybe Version
- data Bulk = Bulk {
- bulkName :: String
- bulkKeySize :: Int
- bulkIVSize :: Int
- bulkBlockSize :: Int
- bulkF :: BulkFunctions
- data Version
- data TLSError
- = Error_Misc String
- | Error_Protocol (String, Bool, AlertDescription)
- | Error_Certificate String
- | Error_Random String
- | Error_EOF
- | Error_Packet String
- | Error_Packet_Size_Mismatch (Int, Int)
- | Error_Packet_unexpected String String
- | Error_Packet_Parsing String
- | Error_Internal_Packet_ByteProcessed Int Int Int
- | Error_Unknown_Version Word8 Word8
- | Error_Unknown_Type String
Context configuration
TLSParams | |
|
data TLSLogging Source
TLSLogging | |
|
data TLSCertificateUsage Source
Certificate Usage callback possible returns values.
CertificateUsageAccept | usage of certificate accepted |
CertificateUsageReject TLSCertificateRejectReason | usage of certificate rejected |
data TLSCertificateRejectReason Source
Certificate and Chain rejection reason
Context object
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
Compressions & Predefined compressions
class CompressionC a whereSource
supported compression algorithms need to be part of this class
compressionCID :: a -> Word8Source
compressionCDeflate :: a -> ByteString -> (a, ByteString)Source
compressionCInflate :: a -> ByteString -> (a, ByteString)Source
CompressionC NullCompression |
data Compression Source
every compression need to be wrapped in this, to fit in structure
forall a . CompressionC a => Compression a |
nullCompression :: CompressionSource
default null compression
Ciphers & Predefined ciphers
Cipher algorithm
Cipher | |
|
Bulk | |
|
Versions
Versions known to TLS
SSL2 is just defined, but this version is and will not be supported.
TLS12 is not yet 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_Random String | |
Error_EOF | |
Error_Packet String | |
Error_Packet_Size_Mismatch (Int, Int) | |
Error_Packet_unexpected String String | |
Error_Packet_Parsing String | |
Error_Internal_Packet_ByteProcessed Int Int Int | |
Error_Unknown_Version Word8 Word8 | |
Error_Unknown_Type String |