{-# OPTIONS_HADDOCK hide #-}
{-# LANGUAGE DeriveDataTypeable #-}
-- |
-- Module      : Network.TLS.Struct
-- License     : BSD-style
-- Maintainer  : Vincent Hanquez <vincent@snarc.org>
-- Stability   : experimental
-- Portability : unknown
--
-- the Struct module contains all definitions and values of the TLS protocol
--
module Network.TLS.Struct
    ( Version(..)
    , ConnectionEnd(..)
    , CipherType(..)
    , CipherData(..)
    , ExtensionID
    , ExtensionRaw(..)
    , CertificateType(..)
    , lastSupportedCertificateType
    , HashAlgorithm(..)
    , SignatureAlgorithm(..)
    , HashAndSignatureAlgorithm
    , DigitallySigned(..)
    , Signature
    , ProtocolType(..)
    , TLSError(..)
    , TLSException(..)
    , DistinguishedName
    , BigNum(..)
    , bigNumToInteger
    , bigNumFromInteger
    , ServerDHParams(..)
    , serverDHParamsToParams
    , serverDHParamsToPublic
    , serverDHParamsFrom
    , ServerECDHParams(..)
    , ServerRSAParams(..)
    , ServerKeyXchgAlgorithmData(..)
    , ClientKeyXchgAlgorithmData(..)
    , Packet(..)
    , Header(..)
    , ServerRandom(..)
    , ClientRandom(..)
    , FinishedData
    , SessionID
    , Session(..)
    , SessionData(..)
    , AlertLevel(..)
    , AlertDescription(..)
    , HandshakeType(..)
    , Handshake(..)
    , numericalVer
    , verOfNum
    , TypeValuable, valOfType, valToType
    , EnumSafe8(..)
    , EnumSafe16(..)
    , packetType
    , typeOfHandshake
    ) where

import Data.X509 (CertificateChain, DistinguishedName)
import Data.Typeable
import Control.Exception (Exception(..))
import Network.TLS.Types
import Network.TLS.Crypto
import Network.TLS.Util.Serialization
import Network.TLS.Imports

data ConnectionEnd = ConnectionServer | ConnectionClient
data CipherType = CipherStream | CipherBlock | CipherAEAD

data CipherData = CipherData
    { CipherData -> ByteString
cipherDataContent :: ByteString
    , CipherData -> Maybe ByteString
cipherDataMAC     :: Maybe ByteString
    , CipherData -> Maybe (ByteString, Int)
cipherDataPadding :: Maybe (ByteString, Int)
    } deriving (Int -> CipherData -> ShowS
[CipherData] -> ShowS
CipherData -> String
(Int -> CipherData -> ShowS)
-> (CipherData -> String)
-> ([CipherData] -> ShowS)
-> Show CipherData
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CipherData] -> ShowS
$cshowList :: [CipherData] -> ShowS
show :: CipherData -> String
$cshow :: CipherData -> String
showsPrec :: Int -> CipherData -> ShowS
$cshowsPrec :: Int -> CipherData -> ShowS
Show,CipherData -> CipherData -> Bool
(CipherData -> CipherData -> Bool)
-> (CipherData -> CipherData -> Bool) -> Eq CipherData
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CipherData -> CipherData -> Bool
$c/= :: CipherData -> CipherData -> Bool
== :: CipherData -> CipherData -> Bool
$c== :: CipherData -> CipherData -> Bool
Eq)

-- | Some of the IANA registered code points for 'CertificateType' are not
-- currently supported by the library.  Nor should they be, they're are either
-- unwise, obsolete or both.  There's no point in conveying these to the user
-- in the client certificate request callback.  The request callback will be
-- filtered to exclude unsupported values.  If the user cannot find a certificate
-- for a supported code point, we'll go ahead without a client certificate and
-- hope for the best, unless the user's callback decides to throw an exception.
--
data CertificateType =
      CertificateType_RSA_Sign         -- ^ TLS10 and up, RFC5246
    | CertificateType_DSS_Sign         -- ^ TLS10 and up, RFC5246
    | CertificateType_ECDSA_Sign       -- ^ TLS10 and up, RFC8422
    | CertificateType_Ed25519_Sign     -- ^ TLS13 and up, synthetic
    | CertificateType_Ed448_Sign       -- ^ TLS13 and up, synthetic
    -- | None of the below will ever be presented to the callback.  Any future
    -- public key algorithms valid for client certificates go above this line.
    | CertificateType_RSA_Fixed_DH     -- Obsolete, unsupported
    | CertificateType_DSS_Fixed_DH     -- Obsolete, unsupported
    | CertificateType_RSA_Ephemeral_DH -- Obsolete, unsupported
    | CertificateType_DSS_Ephemeral_DH -- Obsolete, unsupported
    | CertificateType_fortezza_dms     -- Obsolete, unsupported
    | CertificateType_RSA_Fixed_ECDH   -- Obsolete, unsupported
    | CertificateType_ECDSA_Fixed_ECDH -- Obsolete, unsupported
    | CertificateType_Unknown Word8    -- Obsolete, unsupported
    deriving (CertificateType -> CertificateType -> Bool
(CertificateType -> CertificateType -> Bool)
-> (CertificateType -> CertificateType -> Bool)
-> Eq CertificateType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CertificateType -> CertificateType -> Bool
$c/= :: CertificateType -> CertificateType -> Bool
== :: CertificateType -> CertificateType -> Bool
$c== :: CertificateType -> CertificateType -> Bool
Eq, Eq CertificateType
Eq CertificateType
-> (CertificateType -> CertificateType -> Ordering)
-> (CertificateType -> CertificateType -> Bool)
-> (CertificateType -> CertificateType -> Bool)
-> (CertificateType -> CertificateType -> Bool)
-> (CertificateType -> CertificateType -> Bool)
-> (CertificateType -> CertificateType -> CertificateType)
-> (CertificateType -> CertificateType -> CertificateType)
-> Ord CertificateType
CertificateType -> CertificateType -> Bool
CertificateType -> CertificateType -> Ordering
CertificateType -> CertificateType -> CertificateType
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: CertificateType -> CertificateType -> CertificateType
$cmin :: CertificateType -> CertificateType -> CertificateType
max :: CertificateType -> CertificateType -> CertificateType
$cmax :: CertificateType -> CertificateType -> CertificateType
>= :: CertificateType -> CertificateType -> Bool
$c>= :: CertificateType -> CertificateType -> Bool
> :: CertificateType -> CertificateType -> Bool
$c> :: CertificateType -> CertificateType -> Bool
<= :: CertificateType -> CertificateType -> Bool
$c<= :: CertificateType -> CertificateType -> Bool
< :: CertificateType -> CertificateType -> Bool
$c< :: CertificateType -> CertificateType -> Bool
compare :: CertificateType -> CertificateType -> Ordering
$ccompare :: CertificateType -> CertificateType -> Ordering
$cp1Ord :: Eq CertificateType
Ord, Int -> CertificateType -> ShowS
[CertificateType] -> ShowS
CertificateType -> String
(Int -> CertificateType -> ShowS)
-> (CertificateType -> String)
-> ([CertificateType] -> ShowS)
-> Show CertificateType
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CertificateType] -> ShowS
$cshowList :: [CertificateType] -> ShowS
show :: CertificateType -> String
$cshow :: CertificateType -> String
showsPrec :: Int -> CertificateType -> ShowS
$cshowsPrec :: Int -> CertificateType -> ShowS
Show)

-- | Last supported certificate type, no 'CertificateType that
-- compares greater than this one (based on the 'Ord' instance,
-- not on the wire code point) will be reported to the application
-- via the client certificate request callback.
--
lastSupportedCertificateType :: CertificateType
lastSupportedCertificateType :: CertificateType
lastSupportedCertificateType = CertificateType
CertificateType_ECDSA_Sign


data HashAlgorithm =
      HashNone
    | HashMD5
    | HashSHA1
    | HashSHA224
    | HashSHA256
    | HashSHA384
    | HashSHA512
    | HashIntrinsic
    | HashOther Word8
    deriving (Int -> HashAlgorithm -> ShowS
[HashAlgorithm] -> ShowS
HashAlgorithm -> String
(Int -> HashAlgorithm -> ShowS)
-> (HashAlgorithm -> String)
-> ([HashAlgorithm] -> ShowS)
-> Show HashAlgorithm
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [HashAlgorithm] -> ShowS
$cshowList :: [HashAlgorithm] -> ShowS
show :: HashAlgorithm -> String
$cshow :: HashAlgorithm -> String
showsPrec :: Int -> HashAlgorithm -> ShowS
$cshowsPrec :: Int -> HashAlgorithm -> ShowS
Show,HashAlgorithm -> HashAlgorithm -> Bool
(HashAlgorithm -> HashAlgorithm -> Bool)
-> (HashAlgorithm -> HashAlgorithm -> Bool) -> Eq HashAlgorithm
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: HashAlgorithm -> HashAlgorithm -> Bool
$c/= :: HashAlgorithm -> HashAlgorithm -> Bool
== :: HashAlgorithm -> HashAlgorithm -> Bool
$c== :: HashAlgorithm -> HashAlgorithm -> Bool
Eq)

data SignatureAlgorithm =
      SignatureAnonymous
    | SignatureRSA
    | SignatureDSS
    | SignatureECDSA
    | SignatureRSApssRSAeSHA256
    | SignatureRSApssRSAeSHA384
    | SignatureRSApssRSAeSHA512
    | SignatureEd25519
    | SignatureEd448
    | SignatureRSApsspssSHA256
    | SignatureRSApsspssSHA384
    | SignatureRSApsspssSHA512
    | SignatureOther Word8
    deriving (Int -> SignatureAlgorithm -> ShowS
[SignatureAlgorithm] -> ShowS
SignatureAlgorithm -> String
(Int -> SignatureAlgorithm -> ShowS)
-> (SignatureAlgorithm -> String)
-> ([SignatureAlgorithm] -> ShowS)
-> Show SignatureAlgorithm
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SignatureAlgorithm] -> ShowS
$cshowList :: [SignatureAlgorithm] -> ShowS
show :: SignatureAlgorithm -> String
$cshow :: SignatureAlgorithm -> String
showsPrec :: Int -> SignatureAlgorithm -> ShowS
$cshowsPrec :: Int -> SignatureAlgorithm -> ShowS
Show,SignatureAlgorithm -> SignatureAlgorithm -> Bool
(SignatureAlgorithm -> SignatureAlgorithm -> Bool)
-> (SignatureAlgorithm -> SignatureAlgorithm -> Bool)
-> Eq SignatureAlgorithm
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SignatureAlgorithm -> SignatureAlgorithm -> Bool
$c/= :: SignatureAlgorithm -> SignatureAlgorithm -> Bool
== :: SignatureAlgorithm -> SignatureAlgorithm -> Bool
$c== :: SignatureAlgorithm -> SignatureAlgorithm -> Bool
Eq)

type HashAndSignatureAlgorithm = (HashAlgorithm, SignatureAlgorithm)

------------------------------------------------------------

type Signature = ByteString

data DigitallySigned = DigitallySigned (Maybe HashAndSignatureAlgorithm) Signature
    deriving (Int -> DigitallySigned -> ShowS
[DigitallySigned] -> ShowS
DigitallySigned -> String
(Int -> DigitallySigned -> ShowS)
-> (DigitallySigned -> String)
-> ([DigitallySigned] -> ShowS)
-> Show DigitallySigned
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DigitallySigned] -> ShowS
$cshowList :: [DigitallySigned] -> ShowS
show :: DigitallySigned -> String
$cshow :: DigitallySigned -> String
showsPrec :: Int -> DigitallySigned -> ShowS
$cshowsPrec :: Int -> DigitallySigned -> ShowS
Show,DigitallySigned -> DigitallySigned -> Bool
(DigitallySigned -> DigitallySigned -> Bool)
-> (DigitallySigned -> DigitallySigned -> Bool)
-> Eq DigitallySigned
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DigitallySigned -> DigitallySigned -> Bool
$c/= :: DigitallySigned -> DigitallySigned -> Bool
== :: DigitallySigned -> DigitallySigned -> Bool
$c== :: DigitallySigned -> DigitallySigned -> Bool
Eq)

data ProtocolType =
      ProtocolType_ChangeCipherSpec
    | ProtocolType_Alert
    | ProtocolType_Handshake
    | ProtocolType_AppData
    | ProtocolType_DeprecatedHandshake
    deriving (ProtocolType -> ProtocolType -> Bool
(ProtocolType -> ProtocolType -> Bool)
-> (ProtocolType -> ProtocolType -> Bool) -> Eq ProtocolType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ProtocolType -> ProtocolType -> Bool
$c/= :: ProtocolType -> ProtocolType -> Bool
== :: ProtocolType -> ProtocolType -> Bool
$c== :: ProtocolType -> ProtocolType -> Bool
Eq, Int -> ProtocolType -> ShowS
[ProtocolType] -> ShowS
ProtocolType -> String
(Int -> ProtocolType -> ShowS)
-> (ProtocolType -> String)
-> ([ProtocolType] -> ShowS)
-> Show ProtocolType
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ProtocolType] -> ShowS
$cshowList :: [ProtocolType] -> ShowS
show :: ProtocolType -> String
$cshow :: ProtocolType -> String
showsPrec :: Int -> ProtocolType -> ShowS
$cshowsPrec :: Int -> ProtocolType -> ShowS
Show)

-- | TLSError that might be returned through the TLS stack
data TLSError =
      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
    deriving (TLSError -> TLSError -> Bool
(TLSError -> TLSError -> Bool)
-> (TLSError -> TLSError -> Bool) -> Eq TLSError
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: TLSError -> TLSError -> Bool
$c/= :: TLSError -> TLSError -> Bool
== :: TLSError -> TLSError -> Bool
$c== :: TLSError -> TLSError -> Bool
Eq, Int -> TLSError -> ShowS
[TLSError] -> ShowS
TLSError -> String
(Int -> TLSError -> ShowS)
-> (TLSError -> String) -> ([TLSError] -> ShowS) -> Show TLSError
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [TLSError] -> ShowS
$cshowList :: [TLSError] -> ShowS
show :: TLSError -> String
$cshow :: TLSError -> String
showsPrec :: Int -> TLSError -> ShowS
$cshowsPrec :: Int -> TLSError -> ShowS
Show, Typeable)

instance Exception TLSError

-- | TLS Exceptions related to bad user usage or
-- asynchronous errors
data TLSException =
      Terminated Bool String TLSError -- ^ Early termination exception with the reason
                                      --   and the error associated
    | HandshakeFailed TLSError        -- ^ Handshake failed for the reason attached
    | ConnectionNotEstablished        -- ^ Usage error when the connection has not been established
                                      --   and the user is trying to send or receive data
    deriving (Int -> TLSException -> ShowS
[TLSException] -> ShowS
TLSException -> String
(Int -> TLSException -> ShowS)
-> (TLSException -> String)
-> ([TLSException] -> ShowS)
-> Show TLSException
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [TLSException] -> ShowS
$cshowList :: [TLSException] -> ShowS
show :: TLSException -> String
$cshow :: TLSException -> String
showsPrec :: Int -> TLSException -> ShowS
$cshowsPrec :: Int -> TLSException -> ShowS
Show,TLSException -> TLSException -> Bool
(TLSException -> TLSException -> Bool)
-> (TLSException -> TLSException -> Bool) -> Eq TLSException
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: TLSException -> TLSException -> Bool
$c/= :: TLSException -> TLSException -> Bool
== :: TLSException -> TLSException -> Bool
$c== :: TLSException -> TLSException -> Bool
Eq,Typeable)

instance Exception TLSException

data Packet =
      Handshake [Handshake]
    | Alert [(AlertLevel, AlertDescription)]
    | ChangeCipherSpec
    | AppData ByteString
    deriving (Int -> Packet -> ShowS
[Packet] -> ShowS
Packet -> String
(Int -> Packet -> ShowS)
-> (Packet -> String) -> ([Packet] -> ShowS) -> Show Packet
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Packet] -> ShowS
$cshowList :: [Packet] -> ShowS
show :: Packet -> String
$cshow :: Packet -> String
showsPrec :: Int -> Packet -> ShowS
$cshowsPrec :: Int -> Packet -> ShowS
Show,Packet -> Packet -> Bool
(Packet -> Packet -> Bool)
-> (Packet -> Packet -> Bool) -> Eq Packet
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Packet -> Packet -> Bool
$c/= :: Packet -> Packet -> Bool
== :: Packet -> Packet -> Bool
$c== :: Packet -> Packet -> Bool
Eq)

data Header = Header ProtocolType Version Word16 deriving (Int -> Header -> ShowS
[Header] -> ShowS
Header -> String
(Int -> Header -> ShowS)
-> (Header -> String) -> ([Header] -> ShowS) -> Show Header
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Header] -> ShowS
$cshowList :: [Header] -> ShowS
show :: Header -> String
$cshow :: Header -> String
showsPrec :: Int -> Header -> ShowS
$cshowsPrec :: Int -> Header -> ShowS
Show,Header -> Header -> Bool
(Header -> Header -> Bool)
-> (Header -> Header -> Bool) -> Eq Header
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Header -> Header -> Bool
$c/= :: Header -> Header -> Bool
== :: Header -> Header -> Bool
$c== :: Header -> Header -> Bool
Eq)

newtype ServerRandom = ServerRandom { ServerRandom -> ByteString
unServerRandom :: ByteString } deriving (Int -> ServerRandom -> ShowS
[ServerRandom] -> ShowS
ServerRandom -> String
(Int -> ServerRandom -> ShowS)
-> (ServerRandom -> String)
-> ([ServerRandom] -> ShowS)
-> Show ServerRandom
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ServerRandom] -> ShowS
$cshowList :: [ServerRandom] -> ShowS
show :: ServerRandom -> String
$cshow :: ServerRandom -> String
showsPrec :: Int -> ServerRandom -> ShowS
$cshowsPrec :: Int -> ServerRandom -> ShowS
Show, ServerRandom -> ServerRandom -> Bool
(ServerRandom -> ServerRandom -> Bool)
-> (ServerRandom -> ServerRandom -> Bool) -> Eq ServerRandom
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ServerRandom -> ServerRandom -> Bool
$c/= :: ServerRandom -> ServerRandom -> Bool
== :: ServerRandom -> ServerRandom -> Bool
$c== :: ServerRandom -> ServerRandom -> Bool
Eq)
newtype ClientRandom = ClientRandom { ClientRandom -> ByteString
unClientRandom :: ByteString } deriving (Int -> ClientRandom -> ShowS
[ClientRandom] -> ShowS
ClientRandom -> String
(Int -> ClientRandom -> ShowS)
-> (ClientRandom -> String)
-> ([ClientRandom] -> ShowS)
-> Show ClientRandom
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ClientRandom] -> ShowS
$cshowList :: [ClientRandom] -> ShowS
show :: ClientRandom -> String
$cshow :: ClientRandom -> String
showsPrec :: Int -> ClientRandom -> ShowS
$cshowsPrec :: Int -> ClientRandom -> ShowS
Show, ClientRandom -> ClientRandom -> Bool
(ClientRandom -> ClientRandom -> Bool)
-> (ClientRandom -> ClientRandom -> Bool) -> Eq ClientRandom
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ClientRandom -> ClientRandom -> Bool
$c/= :: ClientRandom -> ClientRandom -> Bool
== :: ClientRandom -> ClientRandom -> Bool
$c== :: ClientRandom -> ClientRandom -> Bool
Eq)
newtype Session = Session (Maybe SessionID) deriving (Int -> Session -> ShowS
[Session] -> ShowS
Session -> String
(Int -> Session -> ShowS)
-> (Session -> String) -> ([Session] -> ShowS) -> Show Session
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Session] -> ShowS
$cshowList :: [Session] -> ShowS
show :: Session -> String
$cshow :: Session -> String
showsPrec :: Int -> Session -> ShowS
$cshowsPrec :: Int -> Session -> ShowS
Show, Session -> Session -> Bool
(Session -> Session -> Bool)
-> (Session -> Session -> Bool) -> Eq Session
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Session -> Session -> Bool
$c/= :: Session -> Session -> Bool
== :: Session -> Session -> Bool
$c== :: Session -> Session -> Bool
Eq)

type FinishedData = ByteString

-- | Identifier of a TLS extension.
type ExtensionID  = Word16

-- | The raw content of a TLS extension.
data ExtensionRaw = ExtensionRaw ExtensionID ByteString
    deriving (ExtensionRaw -> ExtensionRaw -> Bool
(ExtensionRaw -> ExtensionRaw -> Bool)
-> (ExtensionRaw -> ExtensionRaw -> Bool) -> Eq ExtensionRaw
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ExtensionRaw -> ExtensionRaw -> Bool
$c/= :: ExtensionRaw -> ExtensionRaw -> Bool
== :: ExtensionRaw -> ExtensionRaw -> Bool
$c== :: ExtensionRaw -> ExtensionRaw -> Bool
Eq)

instance Show ExtensionRaw where
    show :: ExtensionRaw -> String
show (ExtensionRaw ExtensionID
eid ByteString
bs) = String
"ExtensionRaw " String -> ShowS
forall a. [a] -> [a] -> [a]
++ ExtensionID -> String
showEID ExtensionID
eid String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
" " String -> ShowS
forall a. [a] -> [a] -> [a]
++ ByteString -> String
showBytesHex ByteString
bs

showEID :: ExtensionID -> String
showEID :: ExtensionID -> String
showEID ExtensionID
0x0 = String
"ServerName"
showEID ExtensionID
0x1 = String
"MaxFragmentLength"
showEID ExtensionID
0x2 = String
"ClientCertificateUrl"
showEID ExtensionID
0x3 = String
"TrustedCAKeys"
showEID ExtensionID
0x4 = String
"TruncatedHMAC"
showEID ExtensionID
0x5 = String
"StatusRequest"
showEID ExtensionID
0x6 = String
"UserMapping"
showEID ExtensionID
0x7 = String
"ClientAuthz"
showEID ExtensionID
0x8 = String
"ServerAuthz"
showEID ExtensionID
0x9 = String
"CertType"
showEID ExtensionID
0xa = String
"NegotiatedGroups"
showEID ExtensionID
0xb = String
"EcPointFormats"
showEID ExtensionID
0xc = String
"SRP"
showEID ExtensionID
0xd = String
"SignatureAlgorithm"
showEID ExtensionID
0xe = String
"SRTP"
showEID ExtensionID
0xf = String
"Heartbeat"
showEID ExtensionID
0x10 = String
"ApplicationLayerProtocolNegotiation"
showEID ExtensionID
0x11 = String
"StatusRequestv2"
showEID ExtensionID
0x12 = String
"SignedCertificateTimestamp"
showEID ExtensionID
0x13 = String
"ClientCertificateType"
showEID ExtensionID
0x14 = String
"ServerCertificateType"
showEID ExtensionID
0x15 = String
"Padding"
showEID ExtensionID
0x16 = String
"EncryptThenMAC"
showEID ExtensionID
0x17 = String
"ExtendedMasterSecret"
showEID ExtensionID
0x23 = String
"SessionTicket"
showEID ExtensionID
0x29 = String
"PreShardeKey"
showEID ExtensionID
0x2a = String
"EarlyData"
showEID ExtensionID
0x2b = String
"SupportedVersions"
showEID ExtensionID
0x2c = String
"Cookie"
showEID ExtensionID
0x2d = String
"PskKeyExchangeModes"
showEID ExtensionID
0x2f = String
"CertificateAuthorities"
showEID ExtensionID
0x30 = String
"OidFilters"
showEID ExtensionID
0x31 = String
"PostHandshakeAuth"
showEID ExtensionID
0x32 = String
"SignatureAlgorithmsCert"
showEID ExtensionID
0x33 = String
"KeyShare"
showEID ExtensionID
0x39 = String
"QuicTransportParameters"
showEID ExtensionID
0xff01 = String
"SecureRenegotiation"
showEID ExtensionID
0xffa5 = String
"QuicTransportParameters"
showEID ExtensionID
x      = ExtensionID -> String
forall a. Show a => a -> String
show ExtensionID
x

data AlertLevel =
      AlertLevel_Warning
    | AlertLevel_Fatal
    deriving (Int -> AlertLevel -> ShowS
[AlertLevel] -> ShowS
AlertLevel -> String
(Int -> AlertLevel -> ShowS)
-> (AlertLevel -> String)
-> ([AlertLevel] -> ShowS)
-> Show AlertLevel
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [AlertLevel] -> ShowS
$cshowList :: [AlertLevel] -> ShowS
show :: AlertLevel -> String
$cshow :: AlertLevel -> String
showsPrec :: Int -> AlertLevel -> ShowS
$cshowsPrec :: Int -> AlertLevel -> ShowS
Show,AlertLevel -> AlertLevel -> Bool
(AlertLevel -> AlertLevel -> Bool)
-> (AlertLevel -> AlertLevel -> Bool) -> Eq AlertLevel
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: AlertLevel -> AlertLevel -> Bool
$c/= :: AlertLevel -> AlertLevel -> Bool
== :: AlertLevel -> AlertLevel -> Bool
$c== :: AlertLevel -> AlertLevel -> Bool
Eq)

data AlertDescription =
      CloseNotify
    | UnexpectedMessage
    | BadRecordMac
    | DecryptionFailed       -- ^ deprecated alert, should never be sent by compliant implementation
    | RecordOverflow
    | DecompressionFailure
    | HandshakeFailure
    | BadCertificate
    | UnsupportedCertificate
    | CertificateRevoked
    | CertificateExpired
    | CertificateUnknown
    | IllegalParameter
    | UnknownCa
    | AccessDenied
    | DecodeError
    | DecryptError
    | ExportRestriction
    | ProtocolVersion
    | InsufficientSecurity
    | InternalError
    | InappropriateFallback -- RFC7507
    | UserCanceled
    | NoRenegotiation
    | MissingExtension
    | UnsupportedExtension
    | CertificateUnobtainable
    | UnrecognizedName
    | BadCertificateStatusResponse
    | BadCertificateHashValue
    | UnknownPskIdentity
    | CertificateRequired
    | NoApplicationProtocol -- RFC7301
    deriving (Int -> AlertDescription -> ShowS
[AlertDescription] -> ShowS
AlertDescription -> String
(Int -> AlertDescription -> ShowS)
-> (AlertDescription -> String)
-> ([AlertDescription] -> ShowS)
-> Show AlertDescription
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [AlertDescription] -> ShowS
$cshowList :: [AlertDescription] -> ShowS
show :: AlertDescription -> String
$cshow :: AlertDescription -> String
showsPrec :: Int -> AlertDescription -> ShowS
$cshowsPrec :: Int -> AlertDescription -> ShowS
Show,AlertDescription -> AlertDescription -> Bool
(AlertDescription -> AlertDescription -> Bool)
-> (AlertDescription -> AlertDescription -> Bool)
-> Eq AlertDescription
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: AlertDescription -> AlertDescription -> Bool
$c/= :: AlertDescription -> AlertDescription -> Bool
== :: AlertDescription -> AlertDescription -> Bool
$c== :: AlertDescription -> AlertDescription -> Bool
Eq)

data HandshakeType =
      HandshakeType_HelloRequest
    | HandshakeType_ClientHello
    | HandshakeType_ServerHello
    | HandshakeType_Certificate
    | HandshakeType_ServerKeyXchg
    | HandshakeType_CertRequest
    | HandshakeType_ServerHelloDone
    | HandshakeType_CertVerify
    | HandshakeType_ClientKeyXchg
    | HandshakeType_Finished
    deriving (Int -> HandshakeType -> ShowS
[HandshakeType] -> ShowS
HandshakeType -> String
(Int -> HandshakeType -> ShowS)
-> (HandshakeType -> String)
-> ([HandshakeType] -> ShowS)
-> Show HandshakeType
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [HandshakeType] -> ShowS
$cshowList :: [HandshakeType] -> ShowS
show :: HandshakeType -> String
$cshow :: HandshakeType -> String
showsPrec :: Int -> HandshakeType -> ShowS
$cshowsPrec :: Int -> HandshakeType -> ShowS
Show,HandshakeType -> HandshakeType -> Bool
(HandshakeType -> HandshakeType -> Bool)
-> (HandshakeType -> HandshakeType -> Bool) -> Eq HandshakeType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: HandshakeType -> HandshakeType -> Bool
$c/= :: HandshakeType -> HandshakeType -> Bool
== :: HandshakeType -> HandshakeType -> Bool
$c== :: HandshakeType -> HandshakeType -> Bool
Eq)

newtype BigNum = BigNum ByteString
    deriving (Int -> BigNum -> ShowS
[BigNum] -> ShowS
BigNum -> String
(Int -> BigNum -> ShowS)
-> (BigNum -> String) -> ([BigNum] -> ShowS) -> Show BigNum
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [BigNum] -> ShowS
$cshowList :: [BigNum] -> ShowS
show :: BigNum -> String
$cshow :: BigNum -> String
showsPrec :: Int -> BigNum -> ShowS
$cshowsPrec :: Int -> BigNum -> ShowS
Show,BigNum -> BigNum -> Bool
(BigNum -> BigNum -> Bool)
-> (BigNum -> BigNum -> Bool) -> Eq BigNum
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: BigNum -> BigNum -> Bool
$c/= :: BigNum -> BigNum -> Bool
== :: BigNum -> BigNum -> Bool
$c== :: BigNum -> BigNum -> Bool
Eq)

bigNumToInteger :: BigNum -> Integer
bigNumToInteger :: BigNum -> Integer
bigNumToInteger (BigNum ByteString
b) = ByteString -> Integer
forall ba. ByteArrayAccess ba => ba -> Integer
os2ip ByteString
b

bigNumFromInteger :: Integer -> BigNum
bigNumFromInteger :: Integer -> BigNum
bigNumFromInteger Integer
i = ByteString -> BigNum
BigNum (ByteString -> BigNum) -> ByteString -> BigNum
forall a b. (a -> b) -> a -> b
$ Integer -> ByteString
forall ba. ByteArray ba => Integer -> ba
i2osp Integer
i

data ServerDHParams = ServerDHParams
    { ServerDHParams -> BigNum
serverDHParams_p :: BigNum
    , ServerDHParams -> BigNum
serverDHParams_g :: BigNum
    , ServerDHParams -> BigNum
serverDHParams_y :: BigNum
    } deriving (Int -> ServerDHParams -> ShowS
[ServerDHParams] -> ShowS
ServerDHParams -> String
(Int -> ServerDHParams -> ShowS)
-> (ServerDHParams -> String)
-> ([ServerDHParams] -> ShowS)
-> Show ServerDHParams
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ServerDHParams] -> ShowS
$cshowList :: [ServerDHParams] -> ShowS
show :: ServerDHParams -> String
$cshow :: ServerDHParams -> String
showsPrec :: Int -> ServerDHParams -> ShowS
$cshowsPrec :: Int -> ServerDHParams -> ShowS
Show,ServerDHParams -> ServerDHParams -> Bool
(ServerDHParams -> ServerDHParams -> Bool)
-> (ServerDHParams -> ServerDHParams -> Bool) -> Eq ServerDHParams
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ServerDHParams -> ServerDHParams -> Bool
$c/= :: ServerDHParams -> ServerDHParams -> Bool
== :: ServerDHParams -> ServerDHParams -> Bool
$c== :: ServerDHParams -> ServerDHParams -> Bool
Eq)

serverDHParamsFrom :: DHParams -> DHPublic -> ServerDHParams
serverDHParamsFrom :: DHParams -> DHPublic -> ServerDHParams
serverDHParamsFrom DHParams
params DHPublic
dhPub =
    BigNum -> BigNum -> BigNum -> ServerDHParams
ServerDHParams (Integer -> BigNum
bigNumFromInteger (Integer -> BigNum) -> Integer -> BigNum
forall a b. (a -> b) -> a -> b
$ DHParams -> Integer
dhParamsGetP DHParams
params)
                   (Integer -> BigNum
bigNumFromInteger (Integer -> BigNum) -> Integer -> BigNum
forall a b. (a -> b) -> a -> b
$ DHParams -> Integer
dhParamsGetG DHParams
params)
                   (Integer -> BigNum
bigNumFromInteger (Integer -> BigNum) -> Integer -> BigNum
forall a b. (a -> b) -> a -> b
$ DHPublic -> Integer
dhUnwrapPublic DHPublic
dhPub)

serverDHParamsToParams :: ServerDHParams -> DHParams
serverDHParamsToParams :: ServerDHParams -> DHParams
serverDHParamsToParams ServerDHParams
serverParams =
    Integer -> Integer -> DHParams
dhParams (BigNum -> Integer
bigNumToInteger (BigNum -> Integer) -> BigNum -> Integer
forall a b. (a -> b) -> a -> b
$ ServerDHParams -> BigNum
serverDHParams_p ServerDHParams
serverParams)
             (BigNum -> Integer
bigNumToInteger (BigNum -> Integer) -> BigNum -> Integer
forall a b. (a -> b) -> a -> b
$ ServerDHParams -> BigNum
serverDHParams_g ServerDHParams
serverParams)

serverDHParamsToPublic :: ServerDHParams -> DHPublic
serverDHParamsToPublic :: ServerDHParams -> DHPublic
serverDHParamsToPublic ServerDHParams
serverParams =
    Integer -> DHPublic
dhPublic (BigNum -> Integer
bigNumToInteger (BigNum -> Integer) -> BigNum -> Integer
forall a b. (a -> b) -> a -> b
$ ServerDHParams -> BigNum
serverDHParams_y ServerDHParams
serverParams)

data ServerECDHParams = ServerECDHParams Group GroupPublic
    deriving (Int -> ServerECDHParams -> ShowS
[ServerECDHParams] -> ShowS
ServerECDHParams -> String
(Int -> ServerECDHParams -> ShowS)
-> (ServerECDHParams -> String)
-> ([ServerECDHParams] -> ShowS)
-> Show ServerECDHParams
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ServerECDHParams] -> ShowS
$cshowList :: [ServerECDHParams] -> ShowS
show :: ServerECDHParams -> String
$cshow :: ServerECDHParams -> String
showsPrec :: Int -> ServerECDHParams -> ShowS
$cshowsPrec :: Int -> ServerECDHParams -> ShowS
Show,ServerECDHParams -> ServerECDHParams -> Bool
(ServerECDHParams -> ServerECDHParams -> Bool)
-> (ServerECDHParams -> ServerECDHParams -> Bool)
-> Eq ServerECDHParams
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ServerECDHParams -> ServerECDHParams -> Bool
$c/= :: ServerECDHParams -> ServerECDHParams -> Bool
== :: ServerECDHParams -> ServerECDHParams -> Bool
$c== :: ServerECDHParams -> ServerECDHParams -> Bool
Eq)

data ServerRSAParams = ServerRSAParams
    { ServerRSAParams -> Integer
rsa_modulus  :: Integer
    , ServerRSAParams -> Integer
rsa_exponent :: Integer
    } deriving (Int -> ServerRSAParams -> ShowS
[ServerRSAParams] -> ShowS
ServerRSAParams -> String
(Int -> ServerRSAParams -> ShowS)
-> (ServerRSAParams -> String)
-> ([ServerRSAParams] -> ShowS)
-> Show ServerRSAParams
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ServerRSAParams] -> ShowS
$cshowList :: [ServerRSAParams] -> ShowS
show :: ServerRSAParams -> String
$cshow :: ServerRSAParams -> String
showsPrec :: Int -> ServerRSAParams -> ShowS
$cshowsPrec :: Int -> ServerRSAParams -> ShowS
Show,ServerRSAParams -> ServerRSAParams -> Bool
(ServerRSAParams -> ServerRSAParams -> Bool)
-> (ServerRSAParams -> ServerRSAParams -> Bool)
-> Eq ServerRSAParams
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ServerRSAParams -> ServerRSAParams -> Bool
$c/= :: ServerRSAParams -> ServerRSAParams -> Bool
== :: ServerRSAParams -> ServerRSAParams -> Bool
$c== :: ServerRSAParams -> ServerRSAParams -> Bool
Eq)

data ServerKeyXchgAlgorithmData =
      SKX_DH_Anon ServerDHParams
    | SKX_DHE_DSS ServerDHParams DigitallySigned
    | SKX_DHE_RSA ServerDHParams DigitallySigned
    | SKX_ECDHE_RSA ServerECDHParams DigitallySigned
    | SKX_ECDHE_ECDSA ServerECDHParams DigitallySigned
    | SKX_RSA (Maybe ServerRSAParams)
    | SKX_DH_DSS (Maybe ServerRSAParams)
    | SKX_DH_RSA (Maybe ServerRSAParams)
    | SKX_Unparsed ByteString -- if we parse the server key xchg before knowing the actual cipher, we end up with this structure.
    | SKX_Unknown ByteString
    deriving (Int -> ServerKeyXchgAlgorithmData -> ShowS
[ServerKeyXchgAlgorithmData] -> ShowS
ServerKeyXchgAlgorithmData -> String
(Int -> ServerKeyXchgAlgorithmData -> ShowS)
-> (ServerKeyXchgAlgorithmData -> String)
-> ([ServerKeyXchgAlgorithmData] -> ShowS)
-> Show ServerKeyXchgAlgorithmData
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ServerKeyXchgAlgorithmData] -> ShowS
$cshowList :: [ServerKeyXchgAlgorithmData] -> ShowS
show :: ServerKeyXchgAlgorithmData -> String
$cshow :: ServerKeyXchgAlgorithmData -> String
showsPrec :: Int -> ServerKeyXchgAlgorithmData -> ShowS
$cshowsPrec :: Int -> ServerKeyXchgAlgorithmData -> ShowS
Show,ServerKeyXchgAlgorithmData -> ServerKeyXchgAlgorithmData -> Bool
(ServerKeyXchgAlgorithmData -> ServerKeyXchgAlgorithmData -> Bool)
-> (ServerKeyXchgAlgorithmData
    -> ServerKeyXchgAlgorithmData -> Bool)
-> Eq ServerKeyXchgAlgorithmData
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ServerKeyXchgAlgorithmData -> ServerKeyXchgAlgorithmData -> Bool
$c/= :: ServerKeyXchgAlgorithmData -> ServerKeyXchgAlgorithmData -> Bool
== :: ServerKeyXchgAlgorithmData -> ServerKeyXchgAlgorithmData -> Bool
$c== :: ServerKeyXchgAlgorithmData -> ServerKeyXchgAlgorithmData -> Bool
Eq)

data ClientKeyXchgAlgorithmData =
      CKX_RSA ByteString
    | CKX_DH DHPublic
    | CKX_ECDH ByteString
    deriving (Int -> ClientKeyXchgAlgorithmData -> ShowS
[ClientKeyXchgAlgorithmData] -> ShowS
ClientKeyXchgAlgorithmData -> String
(Int -> ClientKeyXchgAlgorithmData -> ShowS)
-> (ClientKeyXchgAlgorithmData -> String)
-> ([ClientKeyXchgAlgorithmData] -> ShowS)
-> Show ClientKeyXchgAlgorithmData
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ClientKeyXchgAlgorithmData] -> ShowS
$cshowList :: [ClientKeyXchgAlgorithmData] -> ShowS
show :: ClientKeyXchgAlgorithmData -> String
$cshow :: ClientKeyXchgAlgorithmData -> String
showsPrec :: Int -> ClientKeyXchgAlgorithmData -> ShowS
$cshowsPrec :: Int -> ClientKeyXchgAlgorithmData -> ShowS
Show,ClientKeyXchgAlgorithmData -> ClientKeyXchgAlgorithmData -> Bool
(ClientKeyXchgAlgorithmData -> ClientKeyXchgAlgorithmData -> Bool)
-> (ClientKeyXchgAlgorithmData
    -> ClientKeyXchgAlgorithmData -> Bool)
-> Eq ClientKeyXchgAlgorithmData
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ClientKeyXchgAlgorithmData -> ClientKeyXchgAlgorithmData -> Bool
$c/= :: ClientKeyXchgAlgorithmData -> ClientKeyXchgAlgorithmData -> Bool
== :: ClientKeyXchgAlgorithmData -> ClientKeyXchgAlgorithmData -> Bool
$c== :: ClientKeyXchgAlgorithmData -> ClientKeyXchgAlgorithmData -> Bool
Eq)

type DeprecatedRecord = ByteString

data Handshake =
      ClientHello !Version !ClientRandom !Session ![CipherID] ![CompressionID] [ExtensionRaw] (Maybe DeprecatedRecord)
    | ServerHello !Version !ServerRandom !Session !CipherID !CompressionID [ExtensionRaw]
    | Certificates CertificateChain
    | HelloRequest
    | ServerHelloDone
    | ClientKeyXchg ClientKeyXchgAlgorithmData
    | ServerKeyXchg ServerKeyXchgAlgorithmData
    | CertRequest [CertificateType] (Maybe [HashAndSignatureAlgorithm]) [DistinguishedName]
    | CertVerify DigitallySigned
    | Finished FinishedData
    deriving (Int -> Handshake -> ShowS
[Handshake] -> ShowS
Handshake -> String
(Int -> Handshake -> ShowS)
-> (Handshake -> String)
-> ([Handshake] -> ShowS)
-> Show Handshake
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Handshake] -> ShowS
$cshowList :: [Handshake] -> ShowS
show :: Handshake -> String
$cshow :: Handshake -> String
showsPrec :: Int -> Handshake -> ShowS
$cshowsPrec :: Int -> Handshake -> ShowS
Show,Handshake -> Handshake -> Bool
(Handshake -> Handshake -> Bool)
-> (Handshake -> Handshake -> Bool) -> Eq Handshake
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Handshake -> Handshake -> Bool
$c/= :: Handshake -> Handshake -> Bool
== :: Handshake -> Handshake -> Bool
$c== :: Handshake -> Handshake -> Bool
Eq)

packetType :: Packet -> ProtocolType
packetType :: Packet -> ProtocolType
packetType (Handshake [Handshake]
_)    = ProtocolType
ProtocolType_Handshake
packetType (Alert [(AlertLevel, AlertDescription)]
_)        = ProtocolType
ProtocolType_Alert
packetType Packet
ChangeCipherSpec = ProtocolType
ProtocolType_ChangeCipherSpec
packetType (AppData ByteString
_)      = ProtocolType
ProtocolType_AppData

typeOfHandshake :: Handshake -> HandshakeType
typeOfHandshake :: Handshake -> HandshakeType
typeOfHandshake ClientHello{}             = HandshakeType
HandshakeType_ClientHello
typeOfHandshake ServerHello{}             = HandshakeType
HandshakeType_ServerHello
typeOfHandshake Certificates{}            = HandshakeType
HandshakeType_Certificate
typeOfHandshake Handshake
HelloRequest              = HandshakeType
HandshakeType_HelloRequest
typeOfHandshake Handshake
ServerHelloDone           = HandshakeType
HandshakeType_ServerHelloDone
typeOfHandshake ClientKeyXchg{}           = HandshakeType
HandshakeType_ClientKeyXchg
typeOfHandshake ServerKeyXchg{}           = HandshakeType
HandshakeType_ServerKeyXchg
typeOfHandshake CertRequest{}             = HandshakeType
HandshakeType_CertRequest
typeOfHandshake CertVerify{}              = HandshakeType
HandshakeType_CertVerify
typeOfHandshake Finished{}                = HandshakeType
HandshakeType_Finished

numericalVer :: Version -> (Word8, Word8)
numericalVer :: Version -> (Word8, Word8)
numericalVer Version
SSL2  = (Word8
2, Word8
0)
numericalVer Version
SSL3  = (Word8
3, Word8
0)
numericalVer Version
TLS10 = (Word8
3, Word8
1)
numericalVer Version
TLS11 = (Word8
3, Word8
2)
numericalVer Version
TLS12 = (Word8
3, Word8
3)
numericalVer Version
TLS13 = (Word8
3, Word8
4)

verOfNum :: (Word8, Word8) -> Maybe Version
verOfNum :: (Word8, Word8) -> Maybe Version
verOfNum (Word8
2, Word8
0) = Version -> Maybe Version
forall a. a -> Maybe a
Just Version
SSL2
verOfNum (Word8
3, Word8
0) = Version -> Maybe Version
forall a. a -> Maybe a
Just Version
SSL3
verOfNum (Word8
3, Word8
1) = Version -> Maybe Version
forall a. a -> Maybe a
Just Version
TLS10
verOfNum (Word8
3, Word8
2) = Version -> Maybe Version
forall a. a -> Maybe a
Just Version
TLS11
verOfNum (Word8
3, Word8
3) = Version -> Maybe Version
forall a. a -> Maybe a
Just Version
TLS12
verOfNum (Word8
3, Word8
4) = Version -> Maybe Version
forall a. a -> Maybe a
Just Version
TLS13
verOfNum (Word8, Word8)
_      = Maybe Version
forall a. Maybe a
Nothing

class TypeValuable a where
    valOfType :: a -> Word8
    valToType :: Word8 -> Maybe a

-- a better name for TypeValuable
class EnumSafe8 a where
    fromEnumSafe8 :: a -> Word8
    toEnumSafe8   :: Word8 -> Maybe a

class EnumSafe16 a where
    fromEnumSafe16 :: a -> Word16
    toEnumSafe16   :: Word16 -> Maybe a

instance TypeValuable ConnectionEnd where
    valOfType :: ConnectionEnd -> Word8
valOfType ConnectionEnd
ConnectionServer = Word8
0
    valOfType ConnectionEnd
ConnectionClient = Word8
1

    valToType :: Word8 -> Maybe ConnectionEnd
valToType Word8
0 = ConnectionEnd -> Maybe ConnectionEnd
forall a. a -> Maybe a
Just ConnectionEnd
ConnectionServer
    valToType Word8
1 = ConnectionEnd -> Maybe ConnectionEnd
forall a. a -> Maybe a
Just ConnectionEnd
ConnectionClient
    valToType Word8
_ = Maybe ConnectionEnd
forall a. Maybe a
Nothing

instance TypeValuable CipherType where
    valOfType :: CipherType -> Word8
valOfType CipherType
CipherStream = Word8
0
    valOfType CipherType
CipherBlock  = Word8
1
    valOfType CipherType
CipherAEAD   = Word8
2

    valToType :: Word8 -> Maybe CipherType
valToType Word8
0 = CipherType -> Maybe CipherType
forall a. a -> Maybe a
Just CipherType
CipherStream
    valToType Word8
1 = CipherType -> Maybe CipherType
forall a. a -> Maybe a
Just CipherType
CipherBlock
    valToType Word8
2 = CipherType -> Maybe CipherType
forall a. a -> Maybe a
Just CipherType
CipherAEAD
    valToType Word8
_ = Maybe CipherType
forall a. Maybe a
Nothing

instance TypeValuable ProtocolType where
    valOfType :: ProtocolType -> Word8
valOfType ProtocolType
ProtocolType_ChangeCipherSpec    = Word8
20
    valOfType ProtocolType
ProtocolType_Alert               = Word8
21
    valOfType ProtocolType
ProtocolType_Handshake           = Word8
22
    valOfType ProtocolType
ProtocolType_AppData             = Word8
23
    valOfType ProtocolType
ProtocolType_DeprecatedHandshake = Word8
128 -- unused

    valToType :: Word8 -> Maybe ProtocolType
valToType Word8
20 = ProtocolType -> Maybe ProtocolType
forall a. a -> Maybe a
Just ProtocolType
ProtocolType_ChangeCipherSpec
    valToType Word8
21 = ProtocolType -> Maybe ProtocolType
forall a. a -> Maybe a
Just ProtocolType
ProtocolType_Alert
    valToType Word8
22 = ProtocolType -> Maybe ProtocolType
forall a. a -> Maybe a
Just ProtocolType
ProtocolType_Handshake
    valToType Word8
23 = ProtocolType -> Maybe ProtocolType
forall a. a -> Maybe a
Just ProtocolType
ProtocolType_AppData
    valToType Word8
_  = Maybe ProtocolType
forall a. Maybe a
Nothing

instance TypeValuable HandshakeType where
    valOfType :: HandshakeType -> Word8
valOfType HandshakeType
HandshakeType_HelloRequest    = Word8
0
    valOfType HandshakeType
HandshakeType_ClientHello     = Word8
1
    valOfType HandshakeType
HandshakeType_ServerHello     = Word8
2
    valOfType HandshakeType
HandshakeType_Certificate     = Word8
11
    valOfType HandshakeType
HandshakeType_ServerKeyXchg   = Word8
12
    valOfType HandshakeType
HandshakeType_CertRequest     = Word8
13
    valOfType HandshakeType
HandshakeType_ServerHelloDone = Word8
14
    valOfType HandshakeType
HandshakeType_CertVerify      = Word8
15
    valOfType HandshakeType
HandshakeType_ClientKeyXchg   = Word8
16
    valOfType HandshakeType
HandshakeType_Finished        = Word8
20

    valToType :: Word8 -> Maybe HandshakeType
valToType Word8
0  = HandshakeType -> Maybe HandshakeType
forall a. a -> Maybe a
Just HandshakeType
HandshakeType_HelloRequest
    valToType Word8
1  = HandshakeType -> Maybe HandshakeType
forall a. a -> Maybe a
Just HandshakeType
HandshakeType_ClientHello
    valToType Word8
2  = HandshakeType -> Maybe HandshakeType
forall a. a -> Maybe a
Just HandshakeType
HandshakeType_ServerHello
    valToType Word8
11 = HandshakeType -> Maybe HandshakeType
forall a. a -> Maybe a
Just HandshakeType
HandshakeType_Certificate
    valToType Word8
12 = HandshakeType -> Maybe HandshakeType
forall a. a -> Maybe a
Just HandshakeType
HandshakeType_ServerKeyXchg
    valToType Word8
13 = HandshakeType -> Maybe HandshakeType
forall a. a -> Maybe a
Just HandshakeType
HandshakeType_CertRequest
    valToType Word8
14 = HandshakeType -> Maybe HandshakeType
forall a. a -> Maybe a
Just HandshakeType
HandshakeType_ServerHelloDone
    valToType Word8
15 = HandshakeType -> Maybe HandshakeType
forall a. a -> Maybe a
Just HandshakeType
HandshakeType_CertVerify
    valToType Word8
16 = HandshakeType -> Maybe HandshakeType
forall a. a -> Maybe a
Just HandshakeType
HandshakeType_ClientKeyXchg
    valToType Word8
20 = HandshakeType -> Maybe HandshakeType
forall a. a -> Maybe a
Just HandshakeType
HandshakeType_Finished
    valToType Word8
_  = Maybe HandshakeType
forall a. Maybe a
Nothing

instance TypeValuable AlertLevel where
    valOfType :: AlertLevel -> Word8
valOfType AlertLevel
AlertLevel_Warning = Word8
1
    valOfType AlertLevel
AlertLevel_Fatal   = Word8
2

    valToType :: Word8 -> Maybe AlertLevel
valToType Word8
1 = AlertLevel -> Maybe AlertLevel
forall a. a -> Maybe a
Just AlertLevel
AlertLevel_Warning
    valToType Word8
2 = AlertLevel -> Maybe AlertLevel
forall a. a -> Maybe a
Just AlertLevel
AlertLevel_Fatal
    valToType Word8
_ = Maybe AlertLevel
forall a. Maybe a
Nothing

instance TypeValuable AlertDescription where
    valOfType :: AlertDescription -> Word8
valOfType AlertDescription
CloseNotify            = Word8
0
    valOfType AlertDescription
UnexpectedMessage      = Word8
10
    valOfType AlertDescription
BadRecordMac           = Word8
20
    valOfType AlertDescription
DecryptionFailed       = Word8
21
    valOfType AlertDescription
RecordOverflow         = Word8
22
    valOfType AlertDescription
DecompressionFailure   = Word8
30
    valOfType AlertDescription
HandshakeFailure       = Word8
40
    valOfType AlertDescription
BadCertificate         = Word8
42
    valOfType AlertDescription
UnsupportedCertificate = Word8
43
    valOfType AlertDescription
CertificateRevoked     = Word8
44
    valOfType AlertDescription
CertificateExpired     = Word8
45
    valOfType AlertDescription
CertificateUnknown     = Word8
46
    valOfType AlertDescription
IllegalParameter       = Word8
47
    valOfType AlertDescription
UnknownCa              = Word8
48
    valOfType AlertDescription
AccessDenied           = Word8
49
    valOfType AlertDescription
DecodeError            = Word8
50
    valOfType AlertDescription
DecryptError           = Word8
51
    valOfType AlertDescription
ExportRestriction      = Word8
60
    valOfType AlertDescription
ProtocolVersion        = Word8
70
    valOfType AlertDescription
InsufficientSecurity   = Word8
71
    valOfType AlertDescription
InternalError          = Word8
80
    valOfType AlertDescription
InappropriateFallback  = Word8
86
    valOfType AlertDescription
UserCanceled           = Word8
90
    valOfType AlertDescription
NoRenegotiation        = Word8
100
    valOfType AlertDescription
MissingExtension       = Word8
109
    valOfType AlertDescription
UnsupportedExtension   = Word8
110
    valOfType AlertDescription
CertificateUnobtainable = Word8
111
    valOfType AlertDescription
UnrecognizedName        = Word8
112
    valOfType AlertDescription
BadCertificateStatusResponse = Word8
113
    valOfType AlertDescription
BadCertificateHashValue = Word8
114
    valOfType AlertDescription
UnknownPskIdentity      = Word8
115
    valOfType AlertDescription
CertificateRequired     = Word8
116
    valOfType AlertDescription
NoApplicationProtocol   = Word8
120

    valToType :: Word8 -> Maybe AlertDescription
valToType Word8
0   = AlertDescription -> Maybe AlertDescription
forall a. a -> Maybe a
Just AlertDescription
CloseNotify
    valToType Word8
10  = AlertDescription -> Maybe AlertDescription
forall a. a -> Maybe a
Just AlertDescription
UnexpectedMessage
    valToType Word8
20  = AlertDescription -> Maybe AlertDescription
forall a. a -> Maybe a
Just AlertDescription
BadRecordMac
    valToType Word8
21  = AlertDescription -> Maybe AlertDescription
forall a. a -> Maybe a
Just AlertDescription
DecryptionFailed
    valToType Word8
22  = AlertDescription -> Maybe AlertDescription
forall a. a -> Maybe a
Just AlertDescription
RecordOverflow
    valToType Word8
30  = AlertDescription -> Maybe AlertDescription
forall a. a -> Maybe a
Just AlertDescription
DecompressionFailure
    valToType Word8
40  = AlertDescription -> Maybe AlertDescription
forall a. a -> Maybe a
Just AlertDescription
HandshakeFailure
    valToType Word8
42  = AlertDescription -> Maybe AlertDescription
forall a. a -> Maybe a
Just AlertDescription
BadCertificate
    valToType Word8
43  = AlertDescription -> Maybe AlertDescription
forall a. a -> Maybe a
Just AlertDescription
UnsupportedCertificate
    valToType Word8
44  = AlertDescription -> Maybe AlertDescription
forall a. a -> Maybe a
Just AlertDescription
CertificateRevoked
    valToType Word8
45  = AlertDescription -> Maybe AlertDescription
forall a. a -> Maybe a
Just AlertDescription
CertificateExpired
    valToType Word8
46  = AlertDescription -> Maybe AlertDescription
forall a. a -> Maybe a
Just AlertDescription
CertificateUnknown
    valToType Word8
47  = AlertDescription -> Maybe AlertDescription
forall a. a -> Maybe a
Just AlertDescription
IllegalParameter
    valToType Word8
48  = AlertDescription -> Maybe AlertDescription
forall a. a -> Maybe a
Just AlertDescription
UnknownCa
    valToType Word8
49  = AlertDescription -> Maybe AlertDescription
forall a. a -> Maybe a
Just AlertDescription
AccessDenied
    valToType Word8
50  = AlertDescription -> Maybe AlertDescription
forall a. a -> Maybe a
Just AlertDescription
DecodeError
    valToType Word8
51  = AlertDescription -> Maybe AlertDescription
forall a. a -> Maybe a
Just AlertDescription
DecryptError
    valToType Word8
60  = AlertDescription -> Maybe AlertDescription
forall a. a -> Maybe a
Just AlertDescription
ExportRestriction
    valToType Word8
70  = AlertDescription -> Maybe AlertDescription
forall a. a -> Maybe a
Just AlertDescription
ProtocolVersion
    valToType Word8
71  = AlertDescription -> Maybe AlertDescription
forall a. a -> Maybe a
Just AlertDescription
InsufficientSecurity
    valToType Word8
80  = AlertDescription -> Maybe AlertDescription
forall a. a -> Maybe a
Just AlertDescription
InternalError
    valToType Word8
86  = AlertDescription -> Maybe AlertDescription
forall a. a -> Maybe a
Just AlertDescription
InappropriateFallback
    valToType Word8
90  = AlertDescription -> Maybe AlertDescription
forall a. a -> Maybe a
Just AlertDescription
UserCanceled
    valToType Word8
100 = AlertDescription -> Maybe AlertDescription
forall a. a -> Maybe a
Just AlertDescription
NoRenegotiation
    valToType Word8
109 = AlertDescription -> Maybe AlertDescription
forall a. a -> Maybe a
Just AlertDescription
MissingExtension
    valToType Word8
110 = AlertDescription -> Maybe AlertDescription
forall a. a -> Maybe a
Just AlertDescription
UnsupportedExtension
    valToType Word8
111 = AlertDescription -> Maybe AlertDescription
forall a. a -> Maybe a
Just AlertDescription
CertificateUnobtainable
    valToType Word8
112 = AlertDescription -> Maybe AlertDescription
forall a. a -> Maybe a
Just AlertDescription
UnrecognizedName
    valToType Word8
113 = AlertDescription -> Maybe AlertDescription
forall a. a -> Maybe a
Just AlertDescription
BadCertificateStatusResponse
    valToType Word8
114 = AlertDescription -> Maybe AlertDescription
forall a. a -> Maybe a
Just AlertDescription
BadCertificateHashValue
    valToType Word8
115 = AlertDescription -> Maybe AlertDescription
forall a. a -> Maybe a
Just AlertDescription
UnknownPskIdentity
    valToType Word8
116 = AlertDescription -> Maybe AlertDescription
forall a. a -> Maybe a
Just AlertDescription
CertificateRequired
    valToType Word8
120 = AlertDescription -> Maybe AlertDescription
forall a. a -> Maybe a
Just AlertDescription
NoApplicationProtocol
    valToType Word8
_   = Maybe AlertDescription
forall a. Maybe a
Nothing

instance TypeValuable CertificateType where
    valOfType :: CertificateType -> Word8
valOfType CertificateType
CertificateType_RSA_Sign         = Word8
1
    valOfType CertificateType
CertificateType_ECDSA_Sign       = Word8
64
    valOfType CertificateType
CertificateType_DSS_Sign         = Word8
2
    valOfType CertificateType
CertificateType_RSA_Fixed_DH     = Word8
3
    valOfType CertificateType
CertificateType_DSS_Fixed_DH     = Word8
4
    valOfType CertificateType
CertificateType_RSA_Ephemeral_DH = Word8
5
    valOfType CertificateType
CertificateType_DSS_Ephemeral_DH = Word8
6
    valOfType CertificateType
CertificateType_fortezza_dms     = Word8
20
    valOfType CertificateType
CertificateType_RSA_Fixed_ECDH   = Word8
65
    valOfType CertificateType
CertificateType_ECDSA_Fixed_ECDH = Word8
66
    valOfType (CertificateType_Unknown Word8
i)      = Word8
i
    -- | There are no code points that map to the below synthetic types, these
    -- are inferred indirectly from the @signature_algorithms@ extension of the
    -- TLS 1.3 @CertificateRequest@ message.  the value assignments are there
    -- only to avoid partial function warnings.
    valOfType CertificateType
CertificateType_Ed25519_Sign     = Word8
0
    valOfType CertificateType
CertificateType_Ed448_Sign       = Word8
0

    valToType :: Word8 -> Maybe CertificateType
valToType Word8
1  = CertificateType -> Maybe CertificateType
forall a. a -> Maybe a
Just CertificateType
CertificateType_RSA_Sign
    valToType Word8
2  = CertificateType -> Maybe CertificateType
forall a. a -> Maybe a
Just CertificateType
CertificateType_DSS_Sign
    valToType Word8
3  = CertificateType -> Maybe CertificateType
forall a. a -> Maybe a
Just CertificateType
CertificateType_RSA_Fixed_DH
    valToType Word8
4  = CertificateType -> Maybe CertificateType
forall a. a -> Maybe a
Just CertificateType
CertificateType_DSS_Fixed_DH
    valToType Word8
5  = CertificateType -> Maybe CertificateType
forall a. a -> Maybe a
Just CertificateType
CertificateType_RSA_Ephemeral_DH
    valToType Word8
6  = CertificateType -> Maybe CertificateType
forall a. a -> Maybe a
Just CertificateType
CertificateType_DSS_Ephemeral_DH
    valToType Word8
20 = CertificateType -> Maybe CertificateType
forall a. a -> Maybe a
Just CertificateType
CertificateType_fortezza_dms
    valToType Word8
64 = CertificateType -> Maybe CertificateType
forall a. a -> Maybe a
Just CertificateType
CertificateType_ECDSA_Sign
    valToType Word8
65 = CertificateType -> Maybe CertificateType
forall a. a -> Maybe a
Just CertificateType
CertificateType_RSA_Fixed_ECDH
    valToType Word8
66 = CertificateType -> Maybe CertificateType
forall a. a -> Maybe a
Just CertificateType
CertificateType_ECDSA_Fixed_ECDH
    valToType Word8
i  = CertificateType -> Maybe CertificateType
forall a. a -> Maybe a
Just (Word8 -> CertificateType
CertificateType_Unknown Word8
i)
    -- | There are no code points that map to the below synthetic types, these
    -- are inferred indirectly from the @signature_algorithms@ extension of the
    -- TLS 1.3 @CertificateRequest@ message.
    -- @
    -- CertificateType_Ed25519_Sign
    -- CertificateType_Ed448_Sign
    -- @

instance TypeValuable HashAlgorithm where
    valOfType :: HashAlgorithm -> Word8
valOfType HashAlgorithm
HashNone      = Word8
0
    valOfType HashAlgorithm
HashMD5       = Word8
1
    valOfType HashAlgorithm
HashSHA1      = Word8
2
    valOfType HashAlgorithm
HashSHA224    = Word8
3
    valOfType HashAlgorithm
HashSHA256    = Word8
4
    valOfType HashAlgorithm
HashSHA384    = Word8
5
    valOfType HashAlgorithm
HashSHA512    = Word8
6
    valOfType HashAlgorithm
HashIntrinsic = Word8
8
    valOfType (HashOther Word8
i) = Word8
i

    valToType :: Word8 -> Maybe HashAlgorithm
valToType Word8
0 = HashAlgorithm -> Maybe HashAlgorithm
forall a. a -> Maybe a
Just HashAlgorithm
HashNone
    valToType Word8
1 = HashAlgorithm -> Maybe HashAlgorithm
forall a. a -> Maybe a
Just HashAlgorithm
HashMD5
    valToType Word8
2 = HashAlgorithm -> Maybe HashAlgorithm
forall a. a -> Maybe a
Just HashAlgorithm
HashSHA1
    valToType Word8
3 = HashAlgorithm -> Maybe HashAlgorithm
forall a. a -> Maybe a
Just HashAlgorithm
HashSHA224
    valToType Word8
4 = HashAlgorithm -> Maybe HashAlgorithm
forall a. a -> Maybe a
Just HashAlgorithm
HashSHA256
    valToType Word8
5 = HashAlgorithm -> Maybe HashAlgorithm
forall a. a -> Maybe a
Just HashAlgorithm
HashSHA384
    valToType Word8
6 = HashAlgorithm -> Maybe HashAlgorithm
forall a. a -> Maybe a
Just HashAlgorithm
HashSHA512
    valToType Word8
8 = HashAlgorithm -> Maybe HashAlgorithm
forall a. a -> Maybe a
Just HashAlgorithm
HashIntrinsic
    valToType Word8
i = HashAlgorithm -> Maybe HashAlgorithm
forall a. a -> Maybe a
Just (Word8 -> HashAlgorithm
HashOther Word8
i)

instance TypeValuable SignatureAlgorithm where
    valOfType :: SignatureAlgorithm -> Word8
valOfType SignatureAlgorithm
SignatureAnonymous        =  Word8
0
    valOfType SignatureAlgorithm
SignatureRSA              =  Word8
1
    valOfType SignatureAlgorithm
SignatureDSS              =  Word8
2
    valOfType SignatureAlgorithm
SignatureECDSA            =  Word8
3
    valOfType SignatureAlgorithm
SignatureRSApssRSAeSHA256 =  Word8
4
    valOfType SignatureAlgorithm
SignatureRSApssRSAeSHA384 =  Word8
5
    valOfType SignatureAlgorithm
SignatureRSApssRSAeSHA512 =  Word8
6
    valOfType SignatureAlgorithm
SignatureEd25519          =  Word8
7
    valOfType SignatureAlgorithm
SignatureEd448            =  Word8
8
    valOfType SignatureAlgorithm
SignatureRSApsspssSHA256  =  Word8
9
    valOfType SignatureAlgorithm
SignatureRSApsspssSHA384  = Word8
10
    valOfType SignatureAlgorithm
SignatureRSApsspssSHA512  = Word8
11
    valOfType (SignatureOther Word8
i)        =  Word8
i

    valToType :: Word8 -> Maybe SignatureAlgorithm
valToType  Word8
0 = SignatureAlgorithm -> Maybe SignatureAlgorithm
forall a. a -> Maybe a
Just SignatureAlgorithm
SignatureAnonymous
    valToType  Word8
1 = SignatureAlgorithm -> Maybe SignatureAlgorithm
forall a. a -> Maybe a
Just SignatureAlgorithm
SignatureRSA
    valToType  Word8
2 = SignatureAlgorithm -> Maybe SignatureAlgorithm
forall a. a -> Maybe a
Just SignatureAlgorithm
SignatureDSS
    valToType  Word8
3 = SignatureAlgorithm -> Maybe SignatureAlgorithm
forall a. a -> Maybe a
Just SignatureAlgorithm
SignatureECDSA
    valToType  Word8
4 = SignatureAlgorithm -> Maybe SignatureAlgorithm
forall a. a -> Maybe a
Just SignatureAlgorithm
SignatureRSApssRSAeSHA256
    valToType  Word8
5 = SignatureAlgorithm -> Maybe SignatureAlgorithm
forall a. a -> Maybe a
Just SignatureAlgorithm
SignatureRSApssRSAeSHA384
    valToType  Word8
6 = SignatureAlgorithm -> Maybe SignatureAlgorithm
forall a. a -> Maybe a
Just SignatureAlgorithm
SignatureRSApssRSAeSHA512
    valToType  Word8
7 = SignatureAlgorithm -> Maybe SignatureAlgorithm
forall a. a -> Maybe a
Just SignatureAlgorithm
SignatureEd25519
    valToType  Word8
8 = SignatureAlgorithm -> Maybe SignatureAlgorithm
forall a. a -> Maybe a
Just SignatureAlgorithm
SignatureEd448
    valToType  Word8
9 = SignatureAlgorithm -> Maybe SignatureAlgorithm
forall a. a -> Maybe a
Just SignatureAlgorithm
SignatureRSApsspssSHA256
    valToType Word8
10 = SignatureAlgorithm -> Maybe SignatureAlgorithm
forall a. a -> Maybe a
Just SignatureAlgorithm
SignatureRSApsspssSHA384
    valToType Word8
11 = SignatureAlgorithm -> Maybe SignatureAlgorithm
forall a. a -> Maybe a
Just SignatureAlgorithm
SignatureRSApsspssSHA512
    valToType  Word8
i = SignatureAlgorithm -> Maybe SignatureAlgorithm
forall a. a -> Maybe a
Just (Word8 -> SignatureAlgorithm
SignatureOther Word8
i)

instance EnumSafe16 Group where
    fromEnumSafe16 :: Group -> ExtensionID
fromEnumSafe16 Group
P256      =  ExtensionID
23
    fromEnumSafe16 Group
P384      =  ExtensionID
24
    fromEnumSafe16 Group
P521      =  ExtensionID
25
    fromEnumSafe16 Group
X25519    =  ExtensionID
29
    fromEnumSafe16 Group
X448      =  ExtensionID
30
    fromEnumSafe16 Group
FFDHE2048 = ExtensionID
256
    fromEnumSafe16 Group
FFDHE3072 = ExtensionID
257
    fromEnumSafe16 Group
FFDHE4096 = ExtensionID
258
    fromEnumSafe16 Group
FFDHE6144 = ExtensionID
259
    fromEnumSafe16 Group
FFDHE8192 = ExtensionID
260

    toEnumSafe16 :: ExtensionID -> Maybe Group
toEnumSafe16  ExtensionID
23 = Group -> Maybe Group
forall a. a -> Maybe a
Just Group
P256
    toEnumSafe16  ExtensionID
24 = Group -> Maybe Group
forall a. a -> Maybe a
Just Group
P384
    toEnumSafe16  ExtensionID
25 = Group -> Maybe Group
forall a. a -> Maybe a
Just Group
P521
    toEnumSafe16  ExtensionID
29 = Group -> Maybe Group
forall a. a -> Maybe a
Just Group
X25519
    toEnumSafe16  ExtensionID
30 = Group -> Maybe Group
forall a. a -> Maybe a
Just Group
X448
    toEnumSafe16 ExtensionID
256 = Group -> Maybe Group
forall a. a -> Maybe a
Just Group
FFDHE2048
    toEnumSafe16 ExtensionID
257 = Group -> Maybe Group
forall a. a -> Maybe a
Just Group
FFDHE3072
    toEnumSafe16 ExtensionID
258 = Group -> Maybe Group
forall a. a -> Maybe a
Just Group
FFDHE4096
    toEnumSafe16 ExtensionID
259 = Group -> Maybe Group
forall a. a -> Maybe a
Just Group
FFDHE6144
    toEnumSafe16 ExtensionID
260 = Group -> Maybe Group
forall a. a -> Maybe a
Just Group
FFDHE8192
    toEnumSafe16 ExtensionID
_   = Maybe Group
forall a. Maybe a
Nothing