-- |
-- Module      : Network.TLS.Parameters
-- License     : BSD-style
-- Maintainer  : Vincent Hanquez <vincent@snarc.org>
-- Stability   : experimental
-- Portability : unknown
--
module Network.TLS.Parameters
    (
      ClientParams(..)
    , ServerParams(..)
    , CommonParams
    , DebugParams(..)
    , ClientHooks(..)
    , OnCertificateRequest
    , OnServerCertificate
    , ServerHooks(..)
    , Supported(..)
    , Shared(..)
    -- * special default
    , defaultParamsClient
    -- * Parameters
    , MaxFragmentEnum(..)
    , EMSMode(..)
    , GroupUsage(..)
    , CertificateUsage(..)
    , CertificateRejectReason(..)
    ) where

import Network.TLS.Extension
import Network.TLS.Struct
import qualified Network.TLS.Struct as Struct
import Network.TLS.Session
import Network.TLS.Cipher
import Network.TLS.Measurement
import Network.TLS.Compression
import Network.TLS.Crypto
import Network.TLS.Credentials
import Network.TLS.X509
import Network.TLS.RNG (Seed)
import Network.TLS.Imports
import Network.TLS.Types (HostName)
import Data.Default.Class
import qualified Data.ByteString as B


type CommonParams = (Supported, Shared, DebugParams)

-- | All settings should not be used in production
data DebugParams = DebugParams
    {
      -- | Disable the true randomness in favor of deterministic seed that will produce
      -- a deterministic random from. This is useful for tests and debugging purpose.
      -- Do not use in production
      --
      -- Default: 'Nothing'
      DebugParams -> Maybe Seed
debugSeed :: Maybe Seed
      -- | Add a way to print the seed that was randomly generated. re-using the same seed
      -- will reproduce the same randomness with 'debugSeed'
      --
      -- Default: no printing
    , DebugParams -> Seed -> IO ()
debugPrintSeed :: Seed -> IO ()
      -- | Force to choose this version in the server side.
      --
      -- Default: 'Nothing'
    , DebugParams -> Maybe Version
debugVersionForced :: Maybe Version
      -- | Printing master keys.
      --
      -- Default: no printing
    , DebugParams -> String -> IO ()
debugKeyLogger     :: String -> IO ()
    }

defaultDebugParams :: DebugParams
defaultDebugParams :: DebugParams
defaultDebugParams = DebugParams :: Maybe Seed
-> (Seed -> IO ())
-> Maybe Version
-> (String -> IO ())
-> DebugParams
DebugParams
    { debugSeed :: Maybe Seed
debugSeed = Maybe Seed
forall a. Maybe a
Nothing
    , debugPrintSeed :: Seed -> IO ()
debugPrintSeed = IO () -> Seed -> IO ()
forall a b. a -> b -> a
const (() -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ())
    , debugVersionForced :: Maybe Version
debugVersionForced = Maybe Version
forall a. Maybe a
Nothing
    , debugKeyLogger :: String -> IO ()
debugKeyLogger = \String
_ -> () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
    }

instance Show DebugParams where
    show :: DebugParams -> String
show DebugParams
_ = String
"DebugParams"
instance Default DebugParams where
    def :: DebugParams
def = DebugParams
defaultDebugParams

data ClientParams = ClientParams
    { -- |
      --
      -- Default: 'Nothing'
      ClientParams -> Maybe MaxFragmentEnum
clientUseMaxFragmentLength    :: Maybe MaxFragmentEnum
      -- | 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.
      --
      -- This value is typically set by 'defaultParamsClient'.
    , ClientParams -> (String, ByteString)
clientServerIdentification      :: (HostName, ByteString)
      -- | 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).
      --
      -- Default: 'True'
    , ClientParams -> Bool
clientUseServerNameIndication   :: Bool
      -- | try to establish a connection using this session.
      --
      -- Default: 'Nothing'
    , ClientParams -> Maybe (ByteString, SessionData)
clientWantSessionResume         :: Maybe (SessionID, SessionData)
      -- | See the default value of 'Shared'.
    , ClientParams -> Shared
clientShared                    :: Shared
      -- | See the default value of 'ClientHooks'.
    , ClientParams -> ClientHooks
clientHooks                     :: ClientHooks
      -- | In this element, you'll  need to override the default empty value of
      -- of 'supportedCiphers' with a suitable cipherlist.
      --
      -- See the default value of 'Supported'.
    , ClientParams -> Supported
clientSupported                 :: Supported
      -- | See the default value of 'DebugParams'.
    , ClientParams -> DebugParams
clientDebug                     :: DebugParams
      -- | Client tries to send this early data in TLS 1.3 if possible.
      -- If not accepted by the server, it is application's responsibility
      -- to re-sent it.
      --
      -- Default: 'Nothing'
    , ClientParams -> Maybe ByteString
clientEarlyData                 :: Maybe ByteString
    } deriving (Int -> ClientParams -> ShowS
[ClientParams] -> ShowS
ClientParams -> String
(Int -> ClientParams -> ShowS)
-> (ClientParams -> String)
-> ([ClientParams] -> ShowS)
-> Show ClientParams
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ClientParams] -> ShowS
$cshowList :: [ClientParams] -> ShowS
show :: ClientParams -> String
$cshow :: ClientParams -> String
showsPrec :: Int -> ClientParams -> ShowS
$cshowsPrec :: Int -> ClientParams -> ShowS
Show)

defaultParamsClient :: HostName -> ByteString -> ClientParams
defaultParamsClient :: String -> ByteString -> ClientParams
defaultParamsClient String
serverName ByteString
serverId = ClientParams :: Maybe MaxFragmentEnum
-> (String, ByteString)
-> Bool
-> Maybe (ByteString, SessionData)
-> Shared
-> ClientHooks
-> Supported
-> DebugParams
-> Maybe ByteString
-> ClientParams
ClientParams
    { clientUseMaxFragmentLength :: Maybe MaxFragmentEnum
clientUseMaxFragmentLength    = Maybe MaxFragmentEnum
forall a. Maybe a
Nothing
    , clientServerIdentification :: (String, ByteString)
clientServerIdentification    = (String
serverName, ByteString
serverId)
    , clientUseServerNameIndication :: Bool
clientUseServerNameIndication = Bool
True
    , clientWantSessionResume :: Maybe (ByteString, SessionData)
clientWantSessionResume       = Maybe (ByteString, SessionData)
forall a. Maybe a
Nothing
    , clientShared :: Shared
clientShared                  = Shared
forall a. Default a => a
def
    , clientHooks :: ClientHooks
clientHooks                   = ClientHooks
forall a. Default a => a
def
    , clientSupported :: Supported
clientSupported               = Supported
forall a. Default a => a
def
    , clientDebug :: DebugParams
clientDebug                   = DebugParams
defaultDebugParams
    , clientEarlyData :: Maybe ByteString
clientEarlyData               = Maybe ByteString
forall a. Maybe a
Nothing
    }

data ServerParams = ServerParams
    { -- | Request a certificate from client.
      --
      -- Default: 'False'
      ServerParams -> Bool
serverWantClientCert    :: Bool

      -- | 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.
      --
      -- Default: '[]'
    , ServerParams -> [SignedCertificate]
serverCACertificates :: [SignedCertificate]

      -- | Server Optional Diffie Hellman parameters.  Setting parameters is
      -- necessary for FFDHE key exchange when clients are not compatible
      -- with RFC 7919.
      --
      -- Value can be one of the standardized groups from module
      -- "Network.TLS.Extra.FFDHE" or custom parameters generated with
      -- 'Crypto.PubKey.DH.generateParams'.
      --
      -- Default: 'Nothing'
    , ServerParams -> Maybe DHParams
serverDHEParams         :: Maybe DHParams
      -- | See the default value of 'ServerHooks'.
    , ServerParams -> ServerHooks
serverHooks             :: ServerHooks
      -- | See the default value of 'Shared'.
    , ServerParams -> Shared
serverShared            :: Shared
      -- | See the default value of 'Supported'.
    , ServerParams -> Supported
serverSupported         :: Supported
      -- | See the default value of 'DebugParams'.
    , ServerParams -> DebugParams
serverDebug             :: DebugParams
      -- | Server accepts this size of early data in TLS 1.3.
      -- 0 (or lower) means that the server does not accept early data.
      --
      -- Default: 0
    , ServerParams -> Int
serverEarlyDataSize     :: Int
      -- | Lifetime in seconds for session tickets generated by the server.
      -- Acceptable value range is 0 to 604800 (7 days).  The default lifetime
      -- is 86400 seconds (1 day).
      --
      -- Default: 86400 (one day)
    , ServerParams -> Int
serverTicketLifetime    :: Int
    } deriving (Int -> ServerParams -> ShowS
[ServerParams] -> ShowS
ServerParams -> String
(Int -> ServerParams -> ShowS)
-> (ServerParams -> String)
-> ([ServerParams] -> ShowS)
-> Show ServerParams
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ServerParams] -> ShowS
$cshowList :: [ServerParams] -> ShowS
show :: ServerParams -> String
$cshow :: ServerParams -> String
showsPrec :: Int -> ServerParams -> ShowS
$cshowsPrec :: Int -> ServerParams -> ShowS
Show)

defaultParamsServer :: ServerParams
defaultParamsServer :: ServerParams
defaultParamsServer = ServerParams :: Bool
-> [SignedCertificate]
-> Maybe DHParams
-> ServerHooks
-> Shared
-> Supported
-> DebugParams
-> Int
-> Int
-> ServerParams
ServerParams
    { serverWantClientCert :: Bool
serverWantClientCert   = Bool
False
    , serverCACertificates :: [SignedCertificate]
serverCACertificates   = []
    , serverDHEParams :: Maybe DHParams
serverDHEParams        = Maybe DHParams
forall a. Maybe a
Nothing
    , serverHooks :: ServerHooks
serverHooks            = ServerHooks
forall a. Default a => a
def
    , serverShared :: Shared
serverShared           = Shared
forall a. Default a => a
def
    , serverSupported :: Supported
serverSupported        = Supported
forall a. Default a => a
def
    , serverDebug :: DebugParams
serverDebug            = DebugParams
defaultDebugParams
    , serverEarlyDataSize :: Int
serverEarlyDataSize    = Int
0
    , serverTicketLifetime :: Int
serverTicketLifetime   = Int
86400
    }

instance Default ServerParams where
    def :: ServerParams
def = ServerParams
defaultParamsServer

-- | List all the supported algorithms, versions, ciphers, etc supported.
data Supported = Supported
    {
      -- | 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 chosen.
      --
      -- Versions should be listed in preference order, i.e. higher versions
      -- first.
      --
      -- Default: @[TLS13,TLS12,TLS11,TLS10]@
      Supported -> [Version]
supportedVersions       :: [Version]
      -- | Supported cipher methods.  The default is empty, specify a suitable
      -- cipher list.  'Network.TLS.Extra.Cipher.ciphersuite_default' is often
      -- a good choice.
      --
      -- Default: @[]@
    , Supported -> [Cipher]
supportedCiphers        :: [Cipher]
      -- | Supported compressions methods.  By default only the "null"
      -- compression is supported, which means no compression will be performed.
      -- Allowing other compression method is not advised as it causes a
      -- connection failure when TLS 1.3 is negotiated.
      --
      -- Default: @[nullCompression]@
    , Supported -> [Compression]
supportedCompressions   :: [Compression]
      -- | All supported hash/signature algorithms pair for client
      -- certificate verification and server signature in (EC)DHE,
      -- ordered by decreasing priority.
      --
      -- This list is sent to the peer as part of the "signature_algorithms"
      -- extension.  It is used to restrict accepted signatures received from
      -- the peer at TLS level (not in X.509 certificates), but only when the
      -- TLS version is 1.2 or above.  In order to disable SHA-1 one must then
      -- also disable earlier protocol versions in 'supportedVersions'.
      --
      -- The list also impacts the selection of possible algorithms when
      -- generating signatures.
      --
      -- Note: with TLS 1.3 some algorithms have been deprecated and will not be
      -- used even when listed in the parameter: MD5, SHA-1, SHA-224, RSA
      -- PKCS#1, DSS.
      --
      -- Default:
      --
      -- @
      --   [ (HashIntrinsic,     SignatureEd448)
      --   , (HashIntrinsic,     SignatureEd25519)
      --   , (Struct.HashSHA256, SignatureECDSA)
      --   , (Struct.HashSHA384, SignatureECDSA)
      --   , (Struct.HashSHA512, SignatureECDSA)
      --   , (HashIntrinsic,     SignatureRSApssRSAeSHA512)
      --   , (HashIntrinsic,     SignatureRSApssRSAeSHA384)
      --   , (HashIntrinsic,     SignatureRSApssRSAeSHA256)
      --   , (Struct.HashSHA512, SignatureRSA)
      --   , (Struct.HashSHA384, SignatureRSA)
      --   , (Struct.HashSHA256, SignatureRSA)
      --   , (Struct.HashSHA1,   SignatureRSA)
      --   , (Struct.HashSHA1,   SignatureDSS)
      --   ]
      -- @
    , Supported -> [HashAndSignatureAlgorithm]
supportedHashSignatures :: [HashAndSignatureAlgorithm]
      -- | Secure renegotiation defined in RFC5746.
      --   If 'True', clients send the renegotiation_info extension.
      --   If 'True', servers handle the extension or the renegotiation SCSV
      --   then send the renegotiation_info extension.
      --
      --   Default: 'True'
    , Supported -> Bool
supportedSecureRenegotiation :: Bool
      -- | If 'True', renegotiation is allowed from the client side.
      --   This is vulnerable to DOS attacks.
      --   If 'False', renegotiation is allowed only from the server side
      --   via HelloRequest.
      --
      --   Default: 'False'
    , Supported -> Bool
supportedClientInitiatedRenegotiation :: Bool
      -- | The mode regarding extended master secret.  Enabling this extension
      -- provides better security for TLS versions 1.0 to 1.2.  TLS 1.3 provides
      -- the security properties natively and does not need the extension.
      --
      -- By default the extension is enabled but not required.  If mode is set
      -- to 'RequireEMS', the handshake will fail when the peer does not support
      -- the extension.  It is also advised to disable SSLv3 which does not have
      -- this mechanism.
      --
      -- Default: 'AllowEMS'
    , Supported -> EMSMode
supportedExtendedMasterSec   :: EMSMode
      -- | Set if we support session.
      --
      --   Default: 'True'
    , Supported -> Bool
supportedSession             :: Bool
      -- | Support for fallback SCSV defined in RFC7507.
      --   If 'True', servers reject handshakes which suggest
      --   a lower protocol than the highest protocol supported.
      --
      --   Default: 'True'
    , Supported -> Bool
supportedFallbackScsv        :: Bool
      -- | In ver <= TLS1.0, block ciphers using CBC are using CBC residue as IV, which can be guessed
      -- by an attacker. Hence, an empty packet is normally sent before a normal data packet, to
      -- prevent guessability. Some Microsoft TLS-based protocol implementations, however,
      -- consider these empty packets as a protocol violation and disconnect. If this parameter is
      -- 'False', empty packets will never be added, which is less secure, but might help in rare
      -- cases.
      --
      --   Default: 'True'
    , Supported -> Bool
supportedEmptyPacket         :: Bool
      -- | A list of supported elliptic curves and finite-field groups in the
      --   preferred order.
      --
      --   The list is sent to the server as part of the "supported_groups"
      --   extension.  It is used in both clients and servers to restrict
      --   accepted groups in DH key exchange.  Up until TLS v1.2, it is also
      --   used by a client to restrict accepted elliptic curves in ECDSA
      --   signatures.
      --
      --   The default value includes all groups with security strength of 128
      --   bits or more.
      --
      --   Default: @[X25519,X448,P256,FFDHE3072,FFDHE4096,P384,FFDHE6144,FFDHE8192,P521]@
    , Supported -> [Group]
supportedGroups              :: [Group]
    } deriving (Int -> Supported -> ShowS
[Supported] -> ShowS
Supported -> String
(Int -> Supported -> ShowS)
-> (Supported -> String)
-> ([Supported] -> ShowS)
-> Show Supported
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Supported] -> ShowS
$cshowList :: [Supported] -> ShowS
show :: Supported -> String
$cshow :: Supported -> String
showsPrec :: Int -> Supported -> ShowS
$cshowsPrec :: Int -> Supported -> ShowS
Show,Supported -> Supported -> Bool
(Supported -> Supported -> Bool)
-> (Supported -> Supported -> Bool) -> Eq Supported
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Supported -> Supported -> Bool
$c/= :: Supported -> Supported -> Bool
== :: Supported -> Supported -> Bool
$c== :: Supported -> Supported -> Bool
Eq)

-- | Client or server policy regarding Extended Master Secret
data EMSMode
    = NoEMS       -- ^ Extended Master Secret is not used
    | AllowEMS    -- ^ Extended Master Secret is allowed
    | RequireEMS  -- ^ Extended Master Secret is required
    deriving (Int -> EMSMode -> ShowS
[EMSMode] -> ShowS
EMSMode -> String
(Int -> EMSMode -> ShowS)
-> (EMSMode -> String) -> ([EMSMode] -> ShowS) -> Show EMSMode
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [EMSMode] -> ShowS
$cshowList :: [EMSMode] -> ShowS
show :: EMSMode -> String
$cshow :: EMSMode -> String
showsPrec :: Int -> EMSMode -> ShowS
$cshowsPrec :: Int -> EMSMode -> ShowS
Show,EMSMode -> EMSMode -> Bool
(EMSMode -> EMSMode -> Bool)
-> (EMSMode -> EMSMode -> Bool) -> Eq EMSMode
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: EMSMode -> EMSMode -> Bool
$c/= :: EMSMode -> EMSMode -> Bool
== :: EMSMode -> EMSMode -> Bool
$c== :: EMSMode -> EMSMode -> Bool
Eq)

defaultSupported :: Supported
defaultSupported :: Supported
defaultSupported = Supported :: [Version]
-> [Cipher]
-> [Compression]
-> [HashAndSignatureAlgorithm]
-> Bool
-> Bool
-> EMSMode
-> Bool
-> Bool
-> Bool
-> [Group]
-> Supported
Supported
    { supportedVersions :: [Version]
supportedVersions       = [Version
TLS13,Version
TLS12,Version
TLS11,Version
TLS10]
    , supportedCiphers :: [Cipher]
supportedCiphers        = []
    , supportedCompressions :: [Compression]
supportedCompressions   = [Compression
nullCompression]
    , supportedHashSignatures :: [HashAndSignatureAlgorithm]
supportedHashSignatures = [ (HashAlgorithm
HashIntrinsic,     SignatureAlgorithm
SignatureEd448)
                                , (HashAlgorithm
HashIntrinsic,     SignatureAlgorithm
SignatureEd25519)
                                , (HashAlgorithm
Struct.HashSHA256, SignatureAlgorithm
SignatureECDSA)
                                , (HashAlgorithm
Struct.HashSHA384, SignatureAlgorithm
SignatureECDSA)
                                , (HashAlgorithm
Struct.HashSHA512, SignatureAlgorithm
SignatureECDSA)
                                , (HashAlgorithm
HashIntrinsic,     SignatureAlgorithm
SignatureRSApssRSAeSHA512)
                                , (HashAlgorithm
HashIntrinsic,     SignatureAlgorithm
SignatureRSApssRSAeSHA384)
                                , (HashAlgorithm
HashIntrinsic,     SignatureAlgorithm
SignatureRSApssRSAeSHA256)
                                , (HashAlgorithm
Struct.HashSHA512, SignatureAlgorithm
SignatureRSA)
                                , (HashAlgorithm
Struct.HashSHA384, SignatureAlgorithm
SignatureRSA)
                                , (HashAlgorithm
Struct.HashSHA256, SignatureAlgorithm
SignatureRSA)
                                , (HashAlgorithm
Struct.HashSHA1,   SignatureAlgorithm
SignatureRSA)
                                , (HashAlgorithm
Struct.HashSHA1,   SignatureAlgorithm
SignatureDSS)
                                ]
    , supportedSecureRenegotiation :: Bool
supportedSecureRenegotiation = Bool
True
    , supportedClientInitiatedRenegotiation :: Bool
supportedClientInitiatedRenegotiation = Bool
False
    , supportedExtendedMasterSec :: EMSMode
supportedExtendedMasterSec   = EMSMode
AllowEMS
    , supportedSession :: Bool
supportedSession             = Bool
True
    , supportedFallbackScsv :: Bool
supportedFallbackScsv        = Bool
True
    , supportedEmptyPacket :: Bool
supportedEmptyPacket         = Bool
True
    , supportedGroups :: [Group]
supportedGroups              = [Group
X25519,Group
X448,Group
P256,Group
FFDHE3072,Group
FFDHE4096,Group
P384,Group
FFDHE6144,Group
FFDHE8192,Group
P521]
    }

instance Default Supported where
    def :: Supported
def = Supported
defaultSupported

-- | Parameters that are common to clients and servers.
data Shared = Shared
    { -- | The list of certificates and private keys that a server will use as
      -- part of authentication to clients.  Actual credentials that are used
      -- are selected dynamically from this list based on client capabilities.
      -- Additional credentials returned by 'onServerNameIndication' are also
      -- considered.
      --
      -- When credential list is left empty (the default value), no key
      -- exchange can take place.
      --
      -- Default: 'mempty'
      Shared -> Credentials
sharedCredentials     :: Credentials
      -- | Callbacks used by clients and servers in order to resume TLS
      -- sessions.  The default implementation never resumes sessions.  Package
      -- <https://hackage.haskell.org/package/tls-session-manager tls-session-manager>
      -- provides an in-memory implementation.
      --
      -- Default: 'noSessionManager'
    , Shared -> SessionManager
sharedSessionManager  :: SessionManager
      -- | A collection of trust anchors to be used by a client as
      -- part of validation of server certificates.  This is set as
      -- first argument to function 'onServerCertificate'.  Package
      -- <https://hackage.haskell.org/package/x509-system x509-system>
      -- gives access to a default certificate store configured in the
      -- system.
      --
      -- Default: 'mempty'
    , Shared -> CertificateStore
sharedCAStore         :: CertificateStore
      -- | Callbacks that may be used by a client to cache certificate
      -- validation results (positive or negative) and avoid expensive
      -- signature check.  The default implementation does not have
      -- any caching.
      --
      -- See the default value of 'ValidationCache'.
    , Shared -> ValidationCache
sharedValidationCache :: ValidationCache
      -- | Additional extensions to be sent during the Hello sequence.
      --
      -- For a client this is always included in message ClientHello.  For a
      -- server, this is sent in messages ServerHello or EncryptedExtensions
      -- based on the TLS version.
      --
      -- Default: @[]@
    , Shared -> [ExtensionRaw]
sharedHelloExtensions :: [ExtensionRaw]
    }

instance Show Shared where
    show :: Shared -> String
show Shared
_ = String
"Shared"
instance Default Shared where
    def :: Shared
def = Shared :: Credentials
-> SessionManager
-> CertificateStore
-> ValidationCache
-> [ExtensionRaw]
-> Shared
Shared
            { sharedCredentials :: Credentials
sharedCredentials     = Credentials
forall a. Monoid a => a
mempty
            , sharedSessionManager :: SessionManager
sharedSessionManager  = SessionManager
noSessionManager
            , sharedCAStore :: CertificateStore
sharedCAStore         = CertificateStore
forall a. Monoid a => a
mempty
            , sharedValidationCache :: ValidationCache
sharedValidationCache = ValidationCache
forall a. Default a => a
def
            , sharedHelloExtensions :: [ExtensionRaw]
sharedHelloExtensions = []
            }

-- | Group usage callback possible return values.
data GroupUsage =
          GroupUsageValid                 -- ^ usage of group accepted
        | GroupUsageInsecure              -- ^ usage of group provides insufficient security
        | GroupUsageUnsupported String    -- ^ usage of group rejected for other reason (specified as string)
        | GroupUsageInvalidPublic         -- ^ usage of group with an invalid public value
        deriving (Int -> GroupUsage -> ShowS
[GroupUsage] -> ShowS
GroupUsage -> String
(Int -> GroupUsage -> ShowS)
-> (GroupUsage -> String)
-> ([GroupUsage] -> ShowS)
-> Show GroupUsage
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GroupUsage] -> ShowS
$cshowList :: [GroupUsage] -> ShowS
show :: GroupUsage -> String
$cshow :: GroupUsage -> String
showsPrec :: Int -> GroupUsage -> ShowS
$cshowsPrec :: Int -> GroupUsage -> ShowS
Show,GroupUsage -> GroupUsage -> Bool
(GroupUsage -> GroupUsage -> Bool)
-> (GroupUsage -> GroupUsage -> Bool) -> Eq GroupUsage
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GroupUsage -> GroupUsage -> Bool
$c/= :: GroupUsage -> GroupUsage -> Bool
== :: GroupUsage -> GroupUsage -> Bool
$c== :: GroupUsage -> GroupUsage -> Bool
Eq)

defaultGroupUsage :: Int -> DHParams -> DHPublic -> IO GroupUsage
defaultGroupUsage :: Int -> DHParams -> DHPublic -> IO GroupUsage
defaultGroupUsage Int
minBits DHParams
params DHPublic
public
    | Integer -> Bool
forall a. Integral a => a -> Bool
even (Integer -> Bool) -> Integer -> Bool
forall a b. (a -> b) -> a -> b
$ DHParams -> Integer
dhParamsGetP DHParams
params                   = GroupUsage -> IO GroupUsage
forall (m :: * -> *) a. Monad m => a -> m a
return (GroupUsage -> IO GroupUsage) -> GroupUsage -> IO GroupUsage
forall a b. (a -> b) -> a -> b
$ String -> GroupUsage
GroupUsageUnsupported String
"invalid odd prime"
    | Bool -> Bool
not (Bool -> Bool) -> Bool -> Bool
forall a b. (a -> b) -> a -> b
$ DHParams -> Integer -> Bool
dhValid DHParams
params (DHParams -> Integer
dhParamsGetG DHParams
params)   = GroupUsage -> IO GroupUsage
forall (m :: * -> *) a. Monad m => a -> m a
return (GroupUsage -> IO GroupUsage) -> GroupUsage -> IO GroupUsage
forall a b. (a -> b) -> a -> b
$ String -> GroupUsage
GroupUsageUnsupported String
"invalid generator"
    | Bool -> Bool
not (Bool -> Bool) -> Bool -> Bool
forall a b. (a -> b) -> a -> b
$ DHParams -> Integer -> Bool
dhValid DHParams
params (DHPublic -> Integer
dhUnwrapPublic DHPublic
public) = GroupUsage -> IO GroupUsage
forall (m :: * -> *) a. Monad m => a -> m a
return   GroupUsage
GroupUsageInvalidPublic
    -- To prevent Logjam attack
    | DHParams -> Int
dhParamsGetBits DHParams
params Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Int
minBits             = GroupUsage -> IO GroupUsage
forall (m :: * -> *) a. Monad m => a -> m a
return   GroupUsage
GroupUsageInsecure
    | Bool
otherwise                                    = GroupUsage -> IO GroupUsage
forall (m :: * -> *) a. Monad m => a -> m a
return   GroupUsage
GroupUsageValid

-- | Type for 'onCertificateRequest'. This type synonym is to make
--   document readable.
type OnCertificateRequest = ([CertificateType],
                             Maybe [HashAndSignatureAlgorithm],
                             [DistinguishedName])
                           -> IO (Maybe (CertificateChain, PrivKey))

-- | Type for 'onServerCertificate'. This type synonym is to make
--   document readable.
type OnServerCertificate = CertificateStore -> ValidationCache -> ServiceID -> CertificateChain -> IO [FailedReason]

-- | A set of callbacks run by the clients for various corners of TLS establishment
data ClientHooks = ClientHooks
    { -- | This action is called when the a certificate request is
      -- received from the server. The callback argument is the
      -- information from the request.  The server, at its
      -- discretion, may be willing to continue the handshake
      -- without a client certificate.  Therefore, the callback is
      -- free to return 'Nothing' to indicate that no client
      -- certificate should be sent, despite the server's request.
      -- In some cases it may be appropriate to get user consent
      -- before sending the certificate; the content of the user's
      -- certificate may be sensitive and intended only for
      -- specific servers.
      --
      -- The action should select a certificate chain of one of
      -- the given certificate types and one of the certificates
      -- in the chain should (if possible) be signed by one of the
      -- given distinguished names.  Some servers, that don't have
      -- a narrow set of preferred issuer CAs, will send an empty
      -- 'DistinguishedName' list, rather than send all the names
      -- from their trusted CA bundle.  If the client does not
      -- have a certificate chaining to a matching CA, it may
      -- choose a default certificate instead.
      --
      -- Each certificate except the last should be signed by the
      -- following one.  The returned private key must be for the
      -- first certificates in the chain.  This key will be used
      -- to signing the certificate verify message.
      --
      -- The public key in the first certificate, and the matching
      -- returned private key must be compatible with one of the
      -- list of 'HashAndSignatureAlgorithm' value when provided.
      -- TLS 1.3 changes the meaning of the list elements, adding
      -- explicit code points for each supported pair of hash and
      -- signature (public key) algorithms, rather than combining
      -- separate codes for the hash and key.  For details see
      -- <https://tools.ietf.org/html/rfc8446#section-4.2.3 RFC 8446>
      -- section 4.2.3.  When no compatible certificate chain is
      -- available, return 'Nothing' if it is OK to continue
      -- without a client certificate.  Returning a non-matching
      -- certificate should result in a handshake failure.
      --
      -- While the TLS version is not provided to the callback,
      -- the content of the @signature_algorithms@ list provides
      -- a strong hint, since TLS 1.3 servers will generally list
      -- RSA pairs with a hash component of 'Intrinsic' (@0x08@).
      --
      -- Note that is is the responsibility of this action to
      -- select a certificate matching one of the requested
      -- certificate types (public key algorithms).  Returning
      -- a non-matching one will lead to handshake failure later.
      --
      -- Default: returns 'Nothing' anyway.
      ClientHooks -> OnCertificateRequest
onCertificateRequest :: OnCertificateRequest
      -- | Used by the client to validate the server certificate.  The default
      -- implementation calls 'validateDefault' which validates according to the
      -- default hooks and checks provided by "Data.X509.Validation".  This can
      -- be replaced with a custom validation function using different settings.
      --
      -- The function is not expected to verify the key-usage extension of the
      -- end-entity certificate, as this depends on the dynamically-selected
      -- cipher and this part should not be cached.  Key-usage verification
      -- is performed by the library internally.
      --
      -- Default: 'validateDefault'
    , ClientHooks -> OnServerCertificate
onServerCertificate  :: OnServerCertificate
      -- | This action is called when the client sends ClientHello
      --   to determine ALPN values such as '["h2", "http/1.1"]'.
      --
      -- Default: returns 'Nothing'
    , ClientHooks -> IO (Maybe [ByteString])
onSuggestALPN :: IO (Maybe [B.ByteString])
      -- | This action is called to validate DHE parameters when the server
      --   selected a finite-field group not part of the "Supported Groups
      --   Registry" or not part of 'supportedGroups' list.
      --
      --   With TLS 1.3 custom groups have been removed from the protocol, so
      --   this callback is only used when the version negotiated is 1.2 or
      --   below.
      --
      --   The default behavior with (dh_p, dh_g, dh_size) and pub as follows:
      --
      --   (1) rejecting if dh_p is even
      --   (2) rejecting unless 1 < dh_g && dh_g < dh_p - 1
      --   (3) rejecting unless 1 < dh_p && pub < dh_p - 1
      --   (4) rejecting if dh_size < 1024 (to prevent Logjam attack)
      --
      --   See RFC 7919 section 3.1 for recommandations.
    , ClientHooks -> DHParams -> DHPublic -> IO GroupUsage
onCustomFFDHEGroup :: DHParams -> DHPublic -> IO GroupUsage
    }

defaultClientHooks :: ClientHooks
defaultClientHooks :: ClientHooks
defaultClientHooks = ClientHooks :: OnCertificateRequest
-> OnServerCertificate
-> IO (Maybe [ByteString])
-> (DHParams -> DHPublic -> IO GroupUsage)
-> ClientHooks
ClientHooks
    { onCertificateRequest :: OnCertificateRequest
onCertificateRequest = \ ([CertificateType], Maybe [HashAndSignatureAlgorithm],
 [DistinguishedName])
_ -> Maybe (CertificateChain, PrivKey)
-> IO (Maybe (CertificateChain, PrivKey))
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe (CertificateChain, PrivKey)
forall a. Maybe a
Nothing
    , onServerCertificate :: OnServerCertificate
onServerCertificate  = OnServerCertificate
validateDefault
    , onSuggestALPN :: IO (Maybe [ByteString])
onSuggestALPN        = Maybe [ByteString] -> IO (Maybe [ByteString])
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe [ByteString]
forall a. Maybe a
Nothing
    , onCustomFFDHEGroup :: DHParams -> DHPublic -> IO GroupUsage
onCustomFFDHEGroup   = Int -> DHParams -> DHPublic -> IO GroupUsage
defaultGroupUsage Int
1024
    }

instance Show ClientHooks where
    show :: ClientHooks -> String
show ClientHooks
_ = String
"ClientHooks"
instance Default ClientHooks where
    def :: ClientHooks
def = ClientHooks
defaultClientHooks

-- | A set of callbacks run by the server for various corners of the TLS establishment
data ServerHooks = ServerHooks
    {
      -- | This action is called when a client certificate chain
      -- is received from the client.  When it returns a
      -- CertificateUsageReject value, the handshake is aborted.
      --
      -- The function is not expected to verify the key-usage
      -- extension of the certificate.  This verification is
      -- performed by the library internally.
      --
      -- Default: returns the followings:
      --
      -- @
      -- CertificateUsageReject (CertificateRejectOther "no client certificates expected")
      -- @
      ServerHooks -> CertificateChain -> IO CertificateUsage
onClientCertificate :: CertificateChain -> IO CertificateUsage

      -- | This action is called when the client certificate
      -- cannot be verified. Return 'True' to accept the certificate
      -- anyway, or 'False' to fail verification.
      --
      -- Default: returns 'False'
    , ServerHooks -> IO Bool
onUnverifiedClientCert :: IO Bool

      -- | 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.
      --
      -- Default: taking the head of ciphers.
    , ServerHooks -> Version -> [Cipher] -> Cipher
onCipherChoosing        :: Version -> [Cipher] -> Cipher

      -- | Allow the server to indicate additional credentials
      -- to be used depending on the host name indicated by the
      -- client.
      --
      -- This is most useful for transparent proxies where
      -- credentials must be generated on the fly according to
      -- the host the client is trying to connect to.
      --
      -- Returned credentials may be ignored if a client does not support
      -- the signature algorithms used in the certificate chain.
      --
      -- Default: returns 'mempty'
    , ServerHooks -> Maybe String -> IO Credentials
onServerNameIndication  :: Maybe HostName -> IO Credentials

      -- | At each new handshake, we call this hook to see if we allow handshake to happens.
      --
      -- Default: returns 'True'
    , ServerHooks -> Measurement -> IO Bool
onNewHandshake          :: Measurement -> IO Bool

      -- | Allow the server to choose an application layer protocol
      --   suggested from the client through the ALPN
      --   (Application Layer Protocol Negotiation) extensions.
      --   If the server supports no protocols that the client advertises
      --   an empty 'ByteString' should be returned.
      --
      -- Default: 'Nothing'
    , ServerHooks -> Maybe ([ByteString] -> IO ByteString)
onALPNClientSuggest     :: Maybe ([B.ByteString] -> IO B.ByteString)
    }

defaultServerHooks :: ServerHooks
defaultServerHooks :: ServerHooks
defaultServerHooks = ServerHooks :: (CertificateChain -> IO CertificateUsage)
-> IO Bool
-> (Version -> [Cipher] -> Cipher)
-> (Maybe String -> IO Credentials)
-> (Measurement -> IO Bool)
-> Maybe ([ByteString] -> IO ByteString)
-> ServerHooks
ServerHooks
    { onClientCertificate :: CertificateChain -> IO CertificateUsage
onClientCertificate    = \CertificateChain
_ -> CertificateUsage -> IO CertificateUsage
forall (m :: * -> *) a. Monad m => a -> m a
return (CertificateUsage -> IO CertificateUsage)
-> CertificateUsage -> IO CertificateUsage
forall a b. (a -> b) -> a -> b
$ CertificateRejectReason -> CertificateUsage
CertificateUsageReject (CertificateRejectReason -> CertificateUsage)
-> CertificateRejectReason -> CertificateUsage
forall a b. (a -> b) -> a -> b
$ String -> CertificateRejectReason
CertificateRejectOther String
"no client certificates expected"
    , onUnverifiedClientCert :: IO Bool
onUnverifiedClientCert = Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
False
    , onCipherChoosing :: Version -> [Cipher] -> Cipher
onCipherChoosing       = \Version
_ -> [Cipher] -> Cipher
forall a. [a] -> a
head
    , onServerNameIndication :: Maybe String -> IO Credentials
onServerNameIndication = \Maybe String
_ -> Credentials -> IO Credentials
forall (m :: * -> *) a. Monad m => a -> m a
return Credentials
forall a. Monoid a => a
mempty
    , onNewHandshake :: Measurement -> IO Bool
onNewHandshake         = \Measurement
_ -> Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
True
    , onALPNClientSuggest :: Maybe ([ByteString] -> IO ByteString)
onALPNClientSuggest    = Maybe ([ByteString] -> IO ByteString)
forall a. Maybe a
Nothing
    }

instance Show ServerHooks where
    show :: ServerHooks -> String
show ServerHooks
_ = String
"ServerHooks"
instance Default ServerHooks where
    def :: ServerHooks
def = ServerHooks
defaultServerHooks