module Network.TLS.Parameters
    (
      ClientParams(..)
    , ServerParams(..)
    , CommonParams
    , DebugParams(..)
    , ClientHooks(..)
    , OnCertificateRequest
    , OnServerCertificate
    , ServerHooks(..)
    , Supported(..)
    , Shared(..)
    
    , defaultParamsClient
    
    , 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)
data DebugParams = DebugParams
    {
      
      
      
      
      
      DebugParams -> Maybe Seed
debugSeed :: Maybe Seed
      
      
      
      
    , DebugParams -> Seed -> IO ()
debugPrintSeed :: Seed -> IO ()
      
      
      
    , DebugParams -> Maybe Version
debugVersionForced :: Maybe Version
      
      
      
    , 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
    { 
      
      
      ClientParams -> Maybe MaxFragmentEnum
clientUseMaxFragmentLength    :: Maybe MaxFragmentEnum
      
      
      
      
      
      
      
      
      
      
    , ClientParams -> (String, ByteString)
clientServerIdentification      :: (HostName, ByteString)
      
      
      
      
      
    , ClientParams -> Bool
clientUseServerNameIndication   :: Bool
      
      
      
    , ClientParams -> Maybe (ByteString, SessionData)
clientWantSessionResume         :: Maybe (SessionID, SessionData)
      
    , ClientParams -> Shared
clientShared                    :: Shared
      
    , ClientParams -> ClientHooks
clientHooks                     :: ClientHooks
      
      
      
      
    , ClientParams -> Supported
clientSupported                 :: Supported
      
    , ClientParams -> DebugParams
clientDebug                     :: DebugParams
      
      
      
      
      
    , 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
    { 
      
      
      ServerParams -> Bool
serverWantClientCert    :: Bool
      
      
      
      
      
    , ServerParams -> [SignedCertificate]
serverCACertificates :: [SignedCertificate]
      
      
      
      
      
      
      
      
      
    , ServerParams -> Maybe DHParams
serverDHEParams         :: Maybe DHParams
      
    , ServerParams -> ServerHooks
serverHooks             :: ServerHooks
      
    , ServerParams -> Shared
serverShared            :: Shared
      
    , ServerParams -> Supported
serverSupported         :: Supported
      
    , ServerParams -> DebugParams
serverDebug             :: DebugParams
      
      
      
      
    , ServerParams -> Int
serverEarlyDataSize     :: Int
      
      
      
      
      
    , 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
data Supported = Supported
    {
      
      
      
      
      
      
      
      
      
      Supported -> [Version]
supportedVersions       :: [Version]
      
      
      
      
      
    , Supported -> [Cipher]
supportedCiphers        :: [Cipher]
      
      
      
      
      
      
    , Supported -> [Compression]
supportedCompressions   :: [Compression]
      
      
      
      
      
      
      
      
      
      
      
      
      
      
      
      
      
      
      
      
      
      
      
      
      
      
      
      
      
      
      
      
      
      
      
    , Supported -> [HashAndSignatureAlgorithm]
supportedHashSignatures :: [HashAndSignatureAlgorithm]
      
      
      
      
      
      
    , Supported -> Bool
supportedSecureRenegotiation :: Bool
      
      
      
      
      
      
    , Supported -> Bool
supportedClientInitiatedRenegotiation :: Bool
      
      
      
      
      
      
      
      
      
      
    , Supported -> EMSMode
supportedExtendedMasterSec   :: EMSMode
      
      
      
    , Supported -> Bool
supportedSession             :: Bool
      
      
      
      
      
    , Supported -> Bool
supportedFallbackScsv        :: Bool
      
      
      
      
      
      
      
      
    , Supported -> Bool
supportedEmptyPacket         :: Bool
      
      
      
      
      
      
      
      
      
      
      
      
      
    , 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)
data EMSMode
    = NoEMS       
    | AllowEMS    
    | RequireEMS  
    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
data Shared = Shared
    { 
      
      
      
      
      
      
      
      
      
      Shared -> Credentials
sharedCredentials     :: Credentials
      
      
      
      
      
      
    , Shared -> SessionManager
sharedSessionManager  :: SessionManager
      
      
      
      
      
      
      
      
    , Shared -> CertificateStore
sharedCAStore         :: CertificateStore
      
      
      
      
      
      
    , Shared -> ValidationCache
sharedValidationCache :: ValidationCache
      
      
      
      
      
      
      
    , 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 = []
            }
data GroupUsage =
          GroupUsageValid                 
        | GroupUsageInsecure              
        | GroupUsageUnsupported String    
        | GroupUsageInvalidPublic         
        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
    
    | 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 OnCertificateRequest = ([CertificateType],
                             Maybe [HashAndSignatureAlgorithm],
                             [DistinguishedName])
                           -> IO (Maybe (CertificateChain, PrivKey))
type OnServerCertificate = CertificateStore -> ValidationCache -> ServiceID -> CertificateChain -> IO [FailedReason]
data ClientHooks = ClientHooks
    { 
      
      
      
      
      
      
      
      
      
      
      
      
      
      
      
      
      
      
      
      
      
      
      
      
      
      
      
      
      
      
      
      
      
      
      
      
      
      
      
      
      
      
      
      
      
      
      
      
      
      
      ClientHooks -> OnCertificateRequest
onCertificateRequest :: OnCertificateRequest
      
      
      
      
      
      
      
      
      
      
      
    , ClientHooks -> OnServerCertificate
onServerCertificate  :: OnServerCertificate
      
      
      
      
    , ClientHooks -> IO (Maybe [ByteString])
onSuggestALPN :: IO (Maybe [B.ByteString])
      
      
      
      
      
      
      
      
      
      
      
      
      
      
      
      
    , 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
data ServerHooks = ServerHooks
    {
      
      
      
      
      
      
      
      
      
      
      
      
      
      ServerHooks -> CertificateChain -> IO CertificateUsage
onClientCertificate :: CertificateChain -> IO CertificateUsage
      
      
      
      
      
    , ServerHooks -> IO Bool
onUnverifiedClientCert :: IO Bool
      
      
      
      
      
      
      
      
      
    , ServerHooks -> Version -> [Cipher] -> Cipher
onCipherChoosing        :: Version -> [Cipher] -> Cipher
      
      
      
      
      
      
      
      
      
      
      
      
    , ServerHooks -> Maybe String -> IO Credentials
onServerNameIndication  :: Maybe HostName -> IO Credentials
      
      
      
    , ServerHooks -> Measurement -> IO Bool
onNewHandshake          :: Measurement -> IO Bool
      
      
      
      
      
      
      
    , ServerHooks -> Maybe ([ByteString] -> IO ByteString)
onALPNClientSuggest     :: Maybe ([B.ByteString] -> IO B.ByteString)
      
      
      
      
    , ServerHooks -> [ExtensionRaw] -> IO [ExtensionRaw]
onEncryptedExtensionsCreating :: [ExtensionRaw] -> IO [ExtensionRaw]
    }
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)
-> ([ExtensionRaw] -> IO [ExtensionRaw])
-> 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
    , onEncryptedExtensionsCreating :: [ExtensionRaw] -> IO [ExtensionRaw]
onEncryptedExtensionsCreating = [ExtensionRaw] -> IO [ExtensionRaw]
forall (m :: * -> *) a. Monad m => a -> m a
return ([ExtensionRaw] -> IO [ExtensionRaw])
-> ([ExtensionRaw] -> [ExtensionRaw])
-> [ExtensionRaw]
-> IO [ExtensionRaw]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [ExtensionRaw] -> [ExtensionRaw]
forall a. a -> a
id
    }
instance Show ServerHooks where
    show :: ServerHooks -> String
show ServerHooks
_ = String
"ServerHooks"
instance Default ServerHooks where
    def :: ServerHooks
def = ServerHooks
defaultServerHooks