module Network.TLS.Parameters
(
ClientParams(..)
, ServerParams(..)
, CommonParams
, ClientHooks(..)
, ServerHooks(..)
, Supported(..)
, Shared(..)
, defaultParamsClient
, MaxFragmentEnum(..)
, CertificateUsage(..)
, CertificateRejectReason(..)
) where
import Network.BSD (HostName)
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 Data.Monoid
import Data.Default.Class
import qualified Data.ByteString as B
type CommonParams = (Supported, Shared)
data ClientParams = ClientParams
{ clientUseMaxFragmentLength :: Maybe MaxFragmentEnum
, clientServerIdentification :: (HostName, Bytes)
, clientUseServerNameIndication :: Bool
, clientWantSessionResume :: Maybe (SessionID, SessionData)
, clientShared :: Shared
, clientHooks :: ClientHooks
, clientSupported :: Supported
} deriving (Show)
defaultParamsClient :: HostName -> Bytes -> ClientParams
defaultParamsClient serverName serverId = ClientParams
{ clientWantSessionResume = Nothing
, clientUseMaxFragmentLength = Nothing
, clientServerIdentification = (serverName, serverId)
, clientUseServerNameIndication = True
, clientShared = def
, clientHooks = def
, clientSupported = def
}
data ServerParams = ServerParams
{
serverWantClientCert :: Bool
, serverCACertificates :: [SignedCertificate]
, serverDHEParams :: Maybe DHParams
, serverShared :: Shared
, serverHooks :: ServerHooks
, serverSupported :: Supported
} deriving (Show)
defaultParamsServer :: ServerParams
defaultParamsServer = ServerParams
{ serverWantClientCert = False
, serverCACertificates = []
, serverDHEParams = Nothing
, serverHooks = def
, serverShared = def
, serverSupported = def
}
instance Default ServerParams where
def = defaultParamsServer
data Supported = Supported
{
supportedVersions :: [Version]
, supportedCiphers :: [Cipher]
, supportedCompressions :: [Compression]
, supportedHashSignatures :: [HashAndSignatureAlgorithm]
, supportedSecureRenegotiation :: Bool
, supportedSession :: Bool
} deriving (Show,Eq)
defaultSupported :: Supported
defaultSupported = Supported
{ supportedVersions = [TLS12,TLS11,TLS10]
, supportedCiphers = []
, supportedCompressions = [nullCompression]
, supportedHashSignatures = [ (Struct.HashSHA512, SignatureRSA)
, (Struct.HashSHA384, SignatureRSA)
, (Struct.HashSHA256, SignatureRSA)
, (Struct.HashSHA224, SignatureRSA)
, (Struct.HashSHA1, SignatureRSA)
, (Struct.HashSHA1, SignatureDSS)
]
, supportedSecureRenegotiation = True
, supportedSession = True
}
instance Default Supported where
def = defaultSupported
data Shared = Shared
{ sharedCredentials :: Credentials
, sharedSessionManager :: SessionManager
, sharedCAStore :: CertificateStore
, sharedValidationCache :: ValidationCache
}
instance Show Shared where
show _ = "Shared"
instance Default Shared where
def = Shared
{ sharedCAStore = mempty
, sharedCredentials = mempty
, sharedSessionManager = noSessionManager
, sharedValidationCache = def
}
data ClientHooks = ClientHooks
{
onCertificateRequest :: ([CertificateType],
Maybe [HashAndSignatureAlgorithm],
[DistinguishedName]) -> IO (Maybe (CertificateChain, PrivKey))
, onNPNServerSuggest :: Maybe ([B.ByteString] -> IO B.ByteString)
, onServerCertificate :: CertificateStore -> ValidationCache -> ServiceID -> CertificateChain -> IO [FailedReason]
, onSuggestALPN :: IO (Maybe [B.ByteString])
}
defaultClientHooks :: ClientHooks
defaultClientHooks = ClientHooks
{ onCertificateRequest = \ _ -> return Nothing
, onNPNServerSuggest = Nothing
, onServerCertificate = validateDefault
, onSuggestALPN = return Nothing
}
instance Show ClientHooks where
show _ = "ClientHooks"
instance Default ClientHooks where
def = defaultClientHooks
data ServerHooks = ServerHooks
{
onClientCertificate :: CertificateChain -> IO CertificateUsage
, onUnverifiedClientCert :: IO Bool
, onCipherChoosing :: Version -> [Cipher] -> Cipher
, onSuggestNextProtocols :: IO (Maybe [B.ByteString])
, onNewHandshake :: Measurement -> IO Bool
, onALPNClientSuggest :: Maybe ([B.ByteString] -> IO B.ByteString)
}
defaultServerHooks :: ServerHooks
defaultServerHooks = ServerHooks
{ onCipherChoosing = \_ -> head
, onClientCertificate = \_ -> return $ CertificateUsageReject $ CertificateRejectOther "no client certificates expected"
, onUnverifiedClientCert = return False
, onSuggestNextProtocols = return Nothing
, onNewHandshake = \_ -> return True
, onALPNClientSuggest = Nothing
}
instance Show ServerHooks where
show _ = "ClientHooks"
instance Default ServerHooks where
def = defaultServerHooks