Portability | unknown |
---|---|
Stability | experimental |
Maintainer | Vincent Hanquez <vincent@snarc.org> |
Safe Haskell | None |
- Context configuration
- raw types
- Session
- Backend abstraction
- Context object
- Creating a context
- deprecated type aliases
- deprecated values
- Initialisation and Termination of context
- Next Protocol Negotiation
- High level API
- Crypto Key
- Compressions & Predefined compressions
- member redefined for the class abstraction
- helper
- Ciphers & Predefined ciphers
- Versions
- Errors
- Exceptions
- data Params = forall s . SessionManager s => Params {
- pConnectVersion :: Version
- pAllowedVersions :: [Version]
- pCiphers :: [Cipher]
- pCompressions :: [Compression]
- pHashSignatures :: [HashAndSignatureAlgorithm]
- pUseSecureRenegotiation :: Bool
- pUseSession :: Bool
- pCertificates :: [(X509, Maybe PrivateKey)]
- pLogging :: Logging
- onHandshake :: Measurement -> IO Bool
- onCertificatesRecv :: [X509] -> IO CertificateUsage
- pSessionManager :: s
- onSuggestNextProtocols :: IO (Maybe [ByteString])
- onNPNServerSuggest :: Maybe ([ByteString] -> IO ByteString)
- roleParams :: RoleParams
- data RoleParams
- data ClientParams = ClientParams {}
- data ServerParams = ServerParams {
- serverWantClientCert :: Bool
- serverCACertificates :: [X509]
- onClientCertificate :: [X509] -> IO CertificateUsage
- onUnverifiedClientCert :: IO Bool
- onCipherChoosing :: Version -> [Cipher] -> Cipher
- updateClientParams :: (ClientParams -> ClientParams) -> Params -> Params
- updateServerParams :: (ServerParams -> ServerParams) -> Params -> Params
- 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 CertificateUsage
- data CertificateRejectReason
- defaultParamsClient :: Params
- defaultParamsServer :: Params
- defaultLogging :: Logging
- data MaxFragmentEnum
- type HashAndSignatureAlgorithm = (HashAlgorithm, SignatureAlgorithm)
- data HashAlgorithm
- = HashNone
- | HashMD5
- | HashSHA1
- | HashSHA224
- | HashSHA256
- | HashSHA384
- | HashSHA512
- | HashOther Word8
- data SignatureAlgorithm
- data CertificateType
- data ProtocolType
- data Header = Header ProtocolType Version Word16
- type SessionID = ByteString
- data SessionData = SessionData {}
- class SessionManager a where
- sessionResume :: a -> SessionID -> IO (Maybe SessionData)
- sessionEstablish :: a -> SessionID -> SessionData -> IO ()
- sessionInvalidate :: a -> SessionID -> IO ()
- data NoSessionManager = NoSessionManager
- setSessionManager :: SessionManager s => s -> Params -> Params
- data Backend = Backend {
- backendFlush :: IO ()
- backendClose :: IO ()
- backendSend :: ByteString -> IO ()
- backendRecv :: Int -> IO ByteString
- data Context
- ctxConnection :: Context -> Backend
- contextNew :: (MonadIO m, CPRG rng) => Backend -> Params -> rng -> m Context
- contextNewOnHandle :: (MonadIO m, CPRG rng) => Handle -> Params -> rng -> m Context
- contextFlush :: Context -> IO ()
- contextClose :: Context -> IO ()
- type TLSParams = Params
- type TLSLogging = Logging
- type TLSCertificateUsage = CertificateUsage
- type TLSCertificateRejectReason = CertificateRejectReason
- type TLSCtx = Context
- defaultParams :: Params
- bye :: MonadIO m => Context -> m ()
- handshake :: MonadIO m => Context -> m ()
- getNegotiatedProtocol :: MonadIO m => Context -> m (Maybe ByteString)
- sendData :: MonadIO m => Context -> ByteString -> m ()
- recvData :: MonadIO m => Context -> m ByteString
- recvData' :: MonadIO m => Context -> m ByteString
- data PrivateKey = PrivRSA PrivateKey
- class CompressionC a where
- compressionCID :: a -> CompressionID
- compressionCDeflate :: a -> ByteString -> (a, ByteString)
- compressionCInflate :: a -> ByteString -> (a, ByteString)
- data Compression = forall a . 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 BulkFunctions
- = BulkBlockF (Key -> IV -> ByteString -> ByteString) (Key -> IV -> ByteString -> ByteString)
- | BulkStreamF (Key -> IV) (IV -> ByteString -> (ByteString, IV)) (IV -> ByteString -> (ByteString, IV))
- data CipherKeyExchangeType
- data Bulk = Bulk {
- bulkName :: String
- bulkKeySize :: Int
- bulkIVSize :: Int
- bulkBlockSize :: Int
- bulkF :: BulkFunctions
- data Hash = Hash {
- hashName :: String
- hashSize :: Int
- hashF :: ByteString -> ByteString
- data Cipher = Cipher {}
- type CipherID = Word16
- cipherKeyBlockSize :: Cipher -> Int
- type Key = ByteString
- type IV = ByteString
- cipherExchangeNeedMoreData :: CipherKeyExchangeType -> Bool
- data Version
- data TLSError
- data KxError = RSAError Error
- data AlertDescription
- = CloseNotify
- | UnexpectedMessage
- | BadRecordMac
- | DecryptionFailed
- | RecordOverflow
- | DecompressionFailure
- | HandshakeFailure
- | BadCertificate
- | UnsupportedCertificate
- | CertificateRevoked
- | CertificateExpired
- | CertificateUnknown
- | IllegalParameter
- | UnknownCa
- | AccessDenied
- | DecodeError
- | DecryptError
- | ExportRestriction
- | ProtocolVersion
- | InsufficientSecurity
- | InternalError
- | UserCanceled
- | NoRenegotiation
- | UnsupportedExtension
- | CertificateUnobtainable
- | UnrecognizedName
- | BadCertificateStatusResponse
- | BadCertificateHashValue
- data Terminated = Terminated Bool String TLSError
- data HandshakeFailed = HandshakeFailed TLSError
- data ConnectionNotEstablished = ConnectionNotEstablished
Context configuration
forall s . SessionManager s => Params | |
|
data ClientParams Source
ClientParams | |
|
data ServerParams Source
ServerParams | |
|
updateClientParams :: (ClientParams -> ClientParams) -> Params -> ParamsSource
updateServerParams :: (ServerParams -> ServerParams) -> Params -> ParamsSource
Logging | |
|
data Measurement Source
record some data about this connection.
Measurement | |
|
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
data MaxFragmentEnum Source
data HashAlgorithm Source
data SignatureAlgorithm Source
data CertificateType Source
raw types
data ProtocolType Source
Session
type SessionID = ByteStringSource
A session ID
data SessionData Source
Session data to resume
class SessionManager a whereSource
A session manager
sessionResume :: a -> SessionID -> IO (Maybe SessionData)Source
used on server side to decide whether to resume a client session
sessionEstablish :: a -> SessionID -> SessionData -> IO ()Source
used when a session is established.
sessionInvalidate :: a -> SessionID -> IO ()Source
used when a session is invalidated
setSessionManager :: SessionManager s => s -> Params -> ParamsSource
Set a new session manager in a parameters structure.
Backend abstraction
Connection IO backend
Backend | |
|
Context object
ctxConnection :: Context -> BackendSource
return the backend object associated with this context
Creating a context
:: (MonadIO m, CPRG rng) | |
=> 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.
:: (MonadIO m, CPRG rng) | |
=> Handle | Handle of the connection. |
-> Params | Parameters of the context. |
-> rng | Random number generator associated with this context. |
-> m Context |
create a new context on an handle.
contextFlush :: Context -> IO ()Source
contextClose :: Context -> IO ()Source
deprecated type aliases
type TLSLogging = LoggingSource
deprecated values
Deprecated: use defaultParamsClient
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
Compressions & Predefined compressions
class CompressionC a whereSource
supported compression algorithms need to be part of this class
compressionCID :: a -> CompressionIDSource
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
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 BulkFunctions Source
BulkBlockF (Key -> IV -> ByteString -> ByteString) (Key -> IV -> ByteString -> ByteString) | |
BulkStreamF (Key -> IV) (IV -> ByteString -> (ByteString, IV)) (IV -> ByteString -> (ByteString, IV)) |
Bulk | |
|
Hash | |
|
Cipher algorithm
type Key = ByteStringSource
type IV = ByteStringSource
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 Terminated Source
Early termination exception with the reason and the TLS error associated
data HandshakeFailed Source