Portability | unknown |
---|---|
Stability | experimental |
Maintainer | Vincent Hanquez <vincent@snarc.org> |
Safe Haskell | Safe-Infered |
Network.TLS
Contents
Description
- data TLSParams = TLSParams {
- pConnectVersion :: Version
- pAllowedVersions :: [Version]
- pCiphers :: [Cipher]
- pCompressions :: [Compression]
- pWantClientCert :: Bool
- pUseSecureRenegotiation :: Bool
- pUseSession :: Bool
- pCertificates :: [(X509, Maybe PrivateKey)]
- pLogging :: TLSLogging
- onHandshake :: Measurement -> IO Bool
- onCertificatesRecv :: [X509] -> IO TLSCertificateUsage
- onSessionResumption :: SessionID -> IO (Maybe SessionData)
- onSessionEstablished :: SessionID -> SessionData -> IO ()
- onSessionInvalidated :: SessionID -> IO ()
- sessionResumeWith :: Maybe (SessionID, SessionData)
- data TLSLogging = TLSLogging {
- loggingPacketSent :: String -> IO ()
- loggingPacketRecv :: String -> IO ()
- loggingIOSent :: ByteString -> IO ()
- loggingIORecv :: Header -> ByteString -> 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)
- clientWith :: (MonadIO m, CryptoRandomGen g) => TLSParams -> g -> c -> IO () -> (ByteString -> IO ()) -> (Int -> IO ByteString) -> m (TLSCtx c)
- serverWith :: (MonadIO m, CryptoRandomGen g) => TLSParams -> g -> c -> IO () -> (ByteString -> IO ()) -> (Int -> IO ByteString) -> m (TLSCtx c)
- bye :: MonadIO m => TLSCtx c -> m ()
- handshake :: MonadIO m => TLSCtx c -> m ()
- sendData :: MonadIO m => TLSCtx c -> ByteString -> m ()
- recvData :: MonadIO m => TLSCtx c -> m ByteString
- 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_HandshakePolicy 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
- data HandshakeFailed = HandshakeFailed TLSError
- data ConnectionNotEstablished = ConnectionNotEstablished
Context configuration
Constructors
TLSParams | |
Fields
|
data TLSLogging Source
Constructors
TLSLogging | |
Fields
|
data TLSCertificateUsage Source
Certificate Usage callback possible returns values.
Constructors
CertificateUsageAccept | usage of certificate accepted |
CertificateUsageReject TLSCertificateRejectReason | usage of certificate rejected |
Instances
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
Arguments
:: (MonadIO m, CryptoRandomGen g) | |
=> TLSParams | parameters to use for this context |
-> g | random number generator associated with the context |
-> Handle | handle to use |
-> m (TLSCtx Handle) |
Create a new Client context with a configuration, a RNG, and a Handle.
It reconfigures the handle's 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's BufferMode
to NoBuffering
.
Arguments
:: (MonadIO m, CryptoRandomGen g) | |
=> TLSParams | Parameters to use for this context |
-> g | Random number generator associated |
-> c | An abstract connection type |
-> IO () | A method for the connection buffer to be flushed |
-> (ByteString -> IO ()) | A method for sending bytes through the connection |
-> (Int -> IO ByteString) | A method for receiving bytes through the connection |
-> m (TLSCtx c) |
Create a new Client context with a configuration, a RNG, a generic connection and the connection operation.
serverWith :: (MonadIO m, CryptoRandomGen g) => TLSParams -> g -> c -> IO () -> (ByteString -> IO ()) -> (Int -> IO ByteString) -> m (TLSCtx c)Source
Create a new Server context with a configuration, a RNG, a generic connection and the connection operation.
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 ()Source
Handshake for a new TLS connection This is to be called at the beginning of a connection, and during renegotiation
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 renegotiate if a Handshake ClientHello is received
recvData' :: MonadIO m => TLSCtx c -> m ByteStringSource
Crypto Key
Compressions & Predefined compressions
class CompressionC a whereSource
supported compression algorithms need to be part of this class
Methods
compressionCID :: a -> Word8Source
compressionCDeflate :: a -> ByteString -> (a, ByteString)Source
compressionCInflate :: a -> ByteString -> (a, ByteString)Source
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
Cipher algorithm
Constructors
Cipher | |
Fields
|
Constructors
Bulk | |
Fields
|
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_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 |
Exceptions
data HandshakeFailed Source
Constructors
HandshakeFailed TLSError |