1{-# OPTIONS_HADDOCK hide #-}
2{-# LANGUAGE DeriveDataTypeable #-}
3-- |
4-- Module      : Network.TLS.Struct
5-- License     : BSD-style
6-- Maintainer  : Vincent Hanquez <vincent@snarc.org>
7-- Stability   : experimental
8-- Portability : unknown
9--
10-- the Struct module contains all definitions and values of the TLS protocol
11--
12{-# LANGUAGE CPP #-}
13module Network.TLS.Struct
14    ( Version(..)
15    , ConnectionEnd(..)
16    , CipherType(..)
17    , CipherData(..)
18    , ExtensionID
19    , ExtensionRaw(..)
20    , CertificateType(..)
21    , lastSupportedCertificateType
22    , HashAlgorithm(..)
23    , SignatureAlgorithm(..)
24    , HashAndSignatureAlgorithm
25    , DigitallySigned(..)
26    , Signature
27    , ProtocolType(..)
28    , TLSError(..)
29    , TLSException(..)
30    , DistinguishedName
31    , BigNum(..)
32    , bigNumToInteger
33    , bigNumFromInteger
34    , ServerDHParams(..)
35    , serverDHParamsToParams
36    , serverDHParamsToPublic
37    , serverDHParamsFrom
38    , ServerECDHParams(..)
39    , ServerRSAParams(..)
40    , ServerKeyXchgAlgorithmData(..)
41    , ClientKeyXchgAlgorithmData(..)
42    , Packet(..)
43    , Header(..)
44    , ServerRandom(..)
45    , ClientRandom(..)
46    , FinishedData
47    , SessionID
48    , Session(..)
49    , SessionData(..)
50    , AlertLevel(..)
51    , AlertDescription(..)
52    , HandshakeType(..)
53    , Handshake(..)
54    , numericalVer
55    , verOfNum
56    , TypeValuable, valOfType, valToType
57    , EnumSafe8(..)
58    , EnumSafe16(..)
59    , packetType
60    , typeOfHandshake
61    ) where
62
63import Data.X509 (CertificateChain, DistinguishedName)
64import Data.Typeable
65import Control.Exception (Exception(..))
66import Network.TLS.Types
67import Network.TLS.Crypto
68import Network.TLS.Util.Serialization
69import Network.TLS.Imports
70#if MIN_VERSION_mtl(2,2,1)
71#else
72import Control.Monad.Error
73#endif
74
75data ConnectionEnd = ConnectionServer | ConnectionClient
76data CipherType = CipherStream | CipherBlock | CipherAEAD
77
78data CipherData = CipherData
79    { cipherDataContent :: ByteString
80    , cipherDataMAC     :: Maybe ByteString
81    , cipherDataPadding :: Maybe (ByteString, Int)
82    } deriving (Show,Eq)
83
84-- | Some of the IANA registered code points for 'CertificateType' are not
85-- currently supported by the library.  Nor should they be, they're are either
86-- unwise, obsolete or both.  There's no point in conveying these to the user
87-- in the client certificate request callback.  The request callback will be
88-- filtered to exclude unsupported values.  If the user cannot find a certificate
89-- for a supported code point, we'll go ahead without a client certificate and
90-- hope for the best, unless the user's callback decides to throw an exception.
91--
92data CertificateType =
93      CertificateType_RSA_Sign         -- ^ TLS10 and up, RFC5246
94    | CertificateType_DSS_Sign         -- ^ TLS10 and up, RFC5246
95    | CertificateType_ECDSA_Sign       -- ^ TLS10 and up, RFC8422
96    | CertificateType_Ed25519_Sign     -- ^ TLS13 and up, synthetic
97    | CertificateType_Ed448_Sign       -- ^ TLS13 and up, synthetic
98    -- | None of the below will ever be presented to the callback.  Any future
99    -- public key algorithms valid for client certificates go above this line.
100    | CertificateType_RSA_Fixed_DH     -- Obsolete, unsupported
101    | CertificateType_DSS_Fixed_DH     -- Obsolete, unsupported
102    | CertificateType_RSA_Ephemeral_DH -- Obsolete, unsupported
103    | CertificateType_DSS_Ephemeral_DH -- Obsolete, unsupported
104    | CertificateType_fortezza_dms     -- Obsolete, unsupported
105    | CertificateType_RSA_Fixed_ECDH   -- Obsolete, unsupported
106    | CertificateType_ECDSA_Fixed_ECDH -- Obsolete, unsupported
107    | CertificateType_Unknown Word8    -- Obsolete, unsupported
108    deriving (Eq, Ord, Show)
109
110-- | Last supported certificate type, no 'CertificateType that
111-- compares greater than this one (based on the 'Ord' instance,
112-- not on the wire code point) will be reported to the application
113-- via the client certificate request callback.
114--
115lastSupportedCertificateType :: CertificateType
116lastSupportedCertificateType = CertificateType_DSS_Sign
117
118
119data HashAlgorithm =
120      HashNone
121    | HashMD5
122    | HashSHA1
123    | HashSHA224
124    | HashSHA256
125    | HashSHA384
126    | HashSHA512
127    | HashIntrinsic
128    | HashOther Word8
129    deriving (Show,Eq)
130
131data SignatureAlgorithm =
132      SignatureAnonymous
133    | SignatureRSA
134    | SignatureDSS
135    | SignatureECDSA
136    | SignatureRSApssRSAeSHA256
137    | SignatureRSApssRSAeSHA384
138    | SignatureRSApssRSAeSHA512
139    | SignatureEd25519
140    | SignatureEd448
141    | SignatureRSApsspssSHA256
142    | SignatureRSApsspssSHA384
143    | SignatureRSApsspssSHA512
144    | SignatureOther Word8
145    deriving (Show,Eq)
146
147type HashAndSignatureAlgorithm = (HashAlgorithm, SignatureAlgorithm)
148
149------------------------------------------------------------
150
151type Signature = ByteString
152
153data DigitallySigned = DigitallySigned (Maybe HashAndSignatureAlgorithm) Signature
154    deriving (Show,Eq)
155
156data ProtocolType =
157      ProtocolType_ChangeCipherSpec
158    | ProtocolType_Alert
159    | ProtocolType_Handshake
160    | ProtocolType_AppData
161    | ProtocolType_DeprecatedHandshake
162    deriving (Eq, Show)
163
164-- | TLSError that might be returned through the TLS stack
165data TLSError =
166      Error_Misc String        -- ^ mainly for instance of Error
167    | Error_Protocol (String, Bool, AlertDescription)
168    | Error_Certificate String
169    | Error_HandshakePolicy String -- ^ handshake policy failed.
170    | Error_EOF
171    | Error_Packet String
172    | Error_Packet_unexpected String String
173    | Error_Packet_Parsing String
174    deriving (Eq, Show, Typeable)
175
176#if MIN_VERSION_mtl(2,2,1)
177#else
178instance Error TLSError where
179    noMsg  = Error_Misc ""
180    strMsg = Error_Misc
181#endif
182
183instance Exception TLSError
184
185-- | TLS Exceptions related to bad user usage or
186-- asynchronous errors
187data TLSException =
188      Terminated Bool String TLSError -- ^ Early termination exception with the reason
189                                      --   and the error associated
190    | HandshakeFailed TLSError        -- ^ Handshake failed for the reason attached
191    | ConnectionNotEstablished        -- ^ Usage error when the connection has not been established
192                                      --   and the user is trying to send or receive data
193    deriving (Show,Eq,Typeable)
194
195instance Exception TLSException
196
197data Packet =
198      Handshake [Handshake]
199    | Alert [(AlertLevel, AlertDescription)]
200    | ChangeCipherSpec
201    | AppData ByteString
202    deriving (Show,Eq)
203
204data Header = Header ProtocolType Version Word16 deriving (Show,Eq)
205
206newtype ServerRandom = ServerRandom { unServerRandom :: ByteString } deriving (Show, Eq)
207newtype ClientRandom = ClientRandom { unClientRandom :: ByteString } deriving (Show, Eq)
208newtype Session = Session (Maybe SessionID) deriving (Show, Eq)
209
210type FinishedData = ByteString
211type ExtensionID  = Word16
212
213data ExtensionRaw = ExtensionRaw ExtensionID ByteString
214    deriving (Eq)
215
216instance Show ExtensionRaw where
217    show (ExtensionRaw eid bs) = "ExtensionRaw " ++ showEID eid ++ " " ++ showBytesHex bs
218
219showEID :: ExtensionID -> String
220showEID 0x0 = "ServerName"
221showEID 0x1 = "MaxFragmentLength"
222showEID 0x2 = "ClientCertificateUrl"
223showEID 0x3 = "TrustedCAKeys"
224showEID 0x4 = "TruncatedHMAC"
225showEID 0x5 = "StatusRequest"
226showEID 0x6 = "UserMapping"
227showEID 0x7 = "ClientAuthz"
228showEID 0x8 = "ServerAuthz"
229showEID 0x9 = "CertType"
230showEID 0xa = "NegotiatedGroups"
231showEID 0xb = "EcPointFormats"
232showEID 0xc = "SRP"
233showEID 0xd = "SignatureAlgorithm"
234showEID 0xe = "SRTP"
235showEID 0xf = "Heartbeat"
236showEID 0x10 = "ApplicationLayerProtocolNegotiation"
237showEID 0x11 = "StatusRequestv2"
238showEID 0x12 = "SignedCertificateTimestamp"
239showEID 0x13 = "ClientCertificateType"
240showEID 0x14 = "ServerCertificateType"
241showEID 0x15 = "Padding"
242showEID 0x16 = "EncryptThenMAC"
243showEID 0x17 = "ExtendedMasterSecret"
244showEID 0x23 = "SessionTicket"
245showEID 0x29 = "PreShardeKey"
246showEID 0x2a = "EarlyData"
247showEID 0x2b = "SupportedVersions"
248showEID 0x2c = "Cookie"
249showEID 0x2d = "PskKeyExchangeModes"
250showEID 0x2f = "CertificateAuthorities"
251showEID 0x30 = "OidFilters"
252showEID 0x31 = "PostHandshakeAuth"
253showEID 0x32 = "SignatureAlgorithmsCert"
254showEID 0x33 = "KeyShare"
255showEID 0xff01 = "SecureRenegotiation"
256showEID 0xffa5 = "QuicTransportParameters"
257showEID x      = show x
258
259data AlertLevel =
260      AlertLevel_Warning
261    | AlertLevel_Fatal
262    deriving (Show,Eq)
263
264data AlertDescription =
265      CloseNotify
266    | UnexpectedMessage
267    | BadRecordMac
268    | DecryptionFailed       -- ^ deprecated alert, should never be sent by compliant implementation
269    | RecordOverflow
270    | DecompressionFailure
271    | HandshakeFailure
272    | BadCertificate
273    | UnsupportedCertificate
274    | CertificateRevoked
275    | CertificateExpired
276    | CertificateUnknown
277    | IllegalParameter
278    | UnknownCa
279    | AccessDenied
280    | DecodeError
281    | DecryptError
282    | ExportRestriction
283    | ProtocolVersion
284    | InsufficientSecurity
285    | InternalError
286    | InappropriateFallback -- RFC7507
287    | UserCanceled
288    | NoRenegotiation
289    | MissingExtension
290    | UnsupportedExtension
291    | CertificateUnobtainable
292    | UnrecognizedName
293    | BadCertificateStatusResponse
294    | BadCertificateHashValue
295    | UnknownPskIdentity
296    | CertificateRequired
297    | NoApplicationProtocol -- RFC7301
298    deriving (Show,Eq)
299
300data HandshakeType =
301      HandshakeType_HelloRequest
302    | HandshakeType_ClientHello
303    | HandshakeType_ServerHello
304    | HandshakeType_Certificate
305    | HandshakeType_ServerKeyXchg
306    | HandshakeType_CertRequest
307    | HandshakeType_ServerHelloDone
308    | HandshakeType_CertVerify
309    | HandshakeType_ClientKeyXchg
310    | HandshakeType_Finished
311    deriving (Show,Eq)
312
313newtype BigNum = BigNum ByteString
314    deriving (Show,Eq)
315
316bigNumToInteger :: BigNum -> Integer
317bigNumToInteger (BigNum b) = os2ip b
318
319bigNumFromInteger :: Integer -> BigNum
320bigNumFromInteger i = BigNum $ i2osp i
321
322data ServerDHParams = ServerDHParams
323    { serverDHParams_p :: BigNum
324    , serverDHParams_g :: BigNum
325    , serverDHParams_y :: BigNum
326    } deriving (Show,Eq)
327
328serverDHParamsFrom :: DHParams -> DHPublic -> ServerDHParams
329serverDHParamsFrom params dhPub =
330    ServerDHParams (bigNumFromInteger $ dhParamsGetP params)
331                   (bigNumFromInteger $ dhParamsGetG params)
332                   (bigNumFromInteger $ dhUnwrapPublic dhPub)
333
334serverDHParamsToParams :: ServerDHParams -> DHParams
335serverDHParamsToParams serverParams =
336    dhParams (bigNumToInteger $ serverDHParams_p serverParams)
337             (bigNumToInteger $ serverDHParams_g serverParams)
338
339serverDHParamsToPublic :: ServerDHParams -> DHPublic
340serverDHParamsToPublic serverParams =
341    dhPublic (bigNumToInteger $ serverDHParams_y serverParams)
342
343data ServerECDHParams = ServerECDHParams Group GroupPublic
344    deriving (Show,Eq)
345
346data ServerRSAParams = ServerRSAParams
347    { rsa_modulus  :: Integer
348    , rsa_exponent :: Integer
349    } deriving (Show,Eq)
350
351data ServerKeyXchgAlgorithmData =
352      SKX_DH_Anon ServerDHParams
353    | SKX_DHE_DSS ServerDHParams DigitallySigned
354    | SKX_DHE_RSA ServerDHParams DigitallySigned
355    | SKX_ECDHE_RSA ServerECDHParams DigitallySigned
356    | SKX_ECDHE_ECDSA ServerECDHParams DigitallySigned
357    | SKX_RSA (Maybe ServerRSAParams)
358    | SKX_DH_DSS (Maybe ServerRSAParams)
359    | SKX_DH_RSA (Maybe ServerRSAParams)
360    | SKX_Unparsed ByteString -- if we parse the server key xchg before knowing the actual cipher, we end up with this structure.
361    | SKX_Unknown ByteString
362    deriving (Show,Eq)
363
364data ClientKeyXchgAlgorithmData =
365      CKX_RSA ByteString
366    | CKX_DH DHPublic
367    | CKX_ECDH ByteString
368    deriving (Show,Eq)
369
370type DeprecatedRecord = ByteString
371
372data Handshake =
373      ClientHello !Version !ClientRandom !Session ![CipherID] ![CompressionID] [ExtensionRaw] (Maybe DeprecatedRecord)
374    | ServerHello !Version !ServerRandom !Session !CipherID !CompressionID [ExtensionRaw]
375    | Certificates CertificateChain
376    | HelloRequest
377    | ServerHelloDone
378    | ClientKeyXchg ClientKeyXchgAlgorithmData
379    | ServerKeyXchg ServerKeyXchgAlgorithmData
380    | CertRequest [CertificateType] (Maybe [HashAndSignatureAlgorithm]) [DistinguishedName]
381    | CertVerify DigitallySigned
382    | Finished FinishedData
383    deriving (Show,Eq)
384
385packetType :: Packet -> ProtocolType
386packetType (Handshake _)    = ProtocolType_Handshake
387packetType (Alert _)        = ProtocolType_Alert
388packetType ChangeCipherSpec = ProtocolType_ChangeCipherSpec
389packetType (AppData _)      = ProtocolType_AppData
390
391typeOfHandshake :: Handshake -> HandshakeType
392typeOfHandshake ClientHello{}             = HandshakeType_ClientHello
393typeOfHandshake ServerHello{}             = HandshakeType_ServerHello
394typeOfHandshake Certificates{}            = HandshakeType_Certificate
395typeOfHandshake HelloRequest              = HandshakeType_HelloRequest
396typeOfHandshake ServerHelloDone           = HandshakeType_ServerHelloDone
397typeOfHandshake ClientKeyXchg{}           = HandshakeType_ClientKeyXchg
398typeOfHandshake ServerKeyXchg{}           = HandshakeType_ServerKeyXchg
399typeOfHandshake CertRequest{}             = HandshakeType_CertRequest
400typeOfHandshake CertVerify{}              = HandshakeType_CertVerify
401typeOfHandshake Finished{}                = HandshakeType_Finished
402
403numericalVer :: Version -> (Word8, Word8)
404numericalVer SSL2  = (2, 0)
405numericalVer SSL3  = (3, 0)
406numericalVer TLS10 = (3, 1)
407numericalVer TLS11 = (3, 2)
408numericalVer TLS12 = (3, 3)
409numericalVer TLS13 = (3, 4)
410
411verOfNum :: (Word8, Word8) -> Maybe Version
412verOfNum (2, 0) = Just SSL2
413verOfNum (3, 0) = Just SSL3
414verOfNum (3, 1) = Just TLS10
415verOfNum (3, 2) = Just TLS11
416verOfNum (3, 3) = Just TLS12
417verOfNum (3, 4) = Just TLS13
418verOfNum _      = Nothing
419
420class TypeValuable a where
421    valOfType :: a -> Word8
422    valToType :: Word8 -> Maybe a
423
424-- a better name for TypeValuable
425class EnumSafe8 a where
426    fromEnumSafe8 :: a -> Word8
427    toEnumSafe8   :: Word8 -> Maybe a
428
429class EnumSafe16 a where
430    fromEnumSafe16 :: a -> Word16
431    toEnumSafe16   :: Word16 -> Maybe a
432
433instance TypeValuable ConnectionEnd where
434    valOfType ConnectionServer = 0
435    valOfType ConnectionClient = 1
436
437    valToType 0 = Just ConnectionServer
438    valToType 1 = Just ConnectionClient
439    valToType _ = Nothing
440
441instance TypeValuable CipherType where
442    valOfType CipherStream = 0
443    valOfType CipherBlock  = 1
444    valOfType CipherAEAD   = 2
445
446    valToType 0 = Just CipherStream
447    valToType 1 = Just CipherBlock
448    valToType 2 = Just CipherAEAD
449    valToType _ = Nothing
450
451instance TypeValuable ProtocolType where
452    valOfType ProtocolType_ChangeCipherSpec    = 20
453    valOfType ProtocolType_Alert               = 21
454    valOfType ProtocolType_Handshake           = 22
455    valOfType ProtocolType_AppData             = 23
456    valOfType ProtocolType_DeprecatedHandshake = 128 -- unused
457
458    valToType 20 = Just ProtocolType_ChangeCipherSpec
459    valToType 21 = Just ProtocolType_Alert
460    valToType 22 = Just ProtocolType_Handshake
461    valToType 23 = Just ProtocolType_AppData
462    valToType _  = Nothing
463
464instance TypeValuable HandshakeType where
465    valOfType HandshakeType_HelloRequest    = 0
466    valOfType HandshakeType_ClientHello     = 1
467    valOfType HandshakeType_ServerHello     = 2
468    valOfType HandshakeType_Certificate     = 11
469    valOfType HandshakeType_ServerKeyXchg   = 12
470    valOfType HandshakeType_CertRequest     = 13
471    valOfType HandshakeType_ServerHelloDone = 14
472    valOfType HandshakeType_CertVerify      = 15
473    valOfType HandshakeType_ClientKeyXchg   = 16
474    valOfType HandshakeType_Finished        = 20
475
476    valToType 0  = Just HandshakeType_HelloRequest
477    valToType 1  = Just HandshakeType_ClientHello
478    valToType 2  = Just HandshakeType_ServerHello
479    valToType 11 = Just HandshakeType_Certificate
480    valToType 12 = Just HandshakeType_ServerKeyXchg
481    valToType 13 = Just HandshakeType_CertRequest
482    valToType 14 = Just HandshakeType_ServerHelloDone
483    valToType 15 = Just HandshakeType_CertVerify
484    valToType 16 = Just HandshakeType_ClientKeyXchg
485    valToType 20 = Just HandshakeType_Finished
486    valToType _  = Nothing
487
488instance TypeValuable AlertLevel where
489    valOfType AlertLevel_Warning = 1
490    valOfType AlertLevel_Fatal   = 2
491
492    valToType 1 = Just AlertLevel_Warning
493    valToType 2 = Just AlertLevel_Fatal
494    valToType _ = Nothing
495
496instance TypeValuable AlertDescription where
497    valOfType CloseNotify            = 0
498    valOfType UnexpectedMessage      = 10
499    valOfType BadRecordMac           = 20
500    valOfType DecryptionFailed       = 21
501    valOfType RecordOverflow         = 22
502    valOfType DecompressionFailure   = 30
503    valOfType HandshakeFailure       = 40
504    valOfType BadCertificate         = 42
505    valOfType UnsupportedCertificate = 43
506    valOfType CertificateRevoked     = 44
507    valOfType CertificateExpired     = 45
508    valOfType CertificateUnknown     = 46
509    valOfType IllegalParameter       = 47
510    valOfType UnknownCa              = 48
511    valOfType AccessDenied           = 49
512    valOfType DecodeError            = 50
513    valOfType DecryptError           = 51
514    valOfType ExportRestriction      = 60
515    valOfType ProtocolVersion        = 70
516    valOfType InsufficientSecurity   = 71
517    valOfType InternalError          = 80
518    valOfType InappropriateFallback  = 86
519    valOfType UserCanceled           = 90
520    valOfType NoRenegotiation        = 100
521    valOfType MissingExtension       = 109
522    valOfType UnsupportedExtension   = 110
523    valOfType CertificateUnobtainable = 111
524    valOfType UnrecognizedName        = 112
525    valOfType BadCertificateStatusResponse = 113
526    valOfType BadCertificateHashValue = 114
527    valOfType UnknownPskIdentity      = 115
528    valOfType CertificateRequired     = 116
529    valOfType NoApplicationProtocol   = 120
530
531    valToType 0   = Just CloseNotify
532    valToType 10  = Just UnexpectedMessage
533    valToType 20  = Just BadRecordMac
534    valToType 21  = Just DecryptionFailed
535    valToType 22  = Just RecordOverflow
536    valToType 30  = Just DecompressionFailure
537    valToType 40  = Just HandshakeFailure
538    valToType 42  = Just BadCertificate
539    valToType 43  = Just UnsupportedCertificate
540    valToType 44  = Just CertificateRevoked
541    valToType 45  = Just CertificateExpired
542    valToType 46  = Just CertificateUnknown
543    valToType 47  = Just IllegalParameter
544    valToType 48  = Just UnknownCa
545    valToType 49  = Just AccessDenied
546    valToType 50  = Just DecodeError
547    valToType 51  = Just DecryptError
548    valToType 60  = Just ExportRestriction
549    valToType 70  = Just ProtocolVersion
550    valToType 71  = Just InsufficientSecurity
551    valToType 80  = Just InternalError
552    valToType 86  = Just InappropriateFallback
553    valToType 90  = Just UserCanceled
554    valToType 100 = Just NoRenegotiation
555    valToType 109 = Just MissingExtension
556    valToType 110 = Just UnsupportedExtension
557    valToType 111 = Just CertificateUnobtainable
558    valToType 112 = Just UnrecognizedName
559    valToType 113 = Just BadCertificateStatusResponse
560    valToType 114 = Just BadCertificateHashValue
561    valToType 115 = Just UnknownPskIdentity
562    valToType 116 = Just CertificateRequired
563    valToType 120 = Just NoApplicationProtocol
564    valToType _   = Nothing
565
566instance TypeValuable CertificateType where
567    valOfType CertificateType_RSA_Sign         = 1
568    valOfType CertificateType_ECDSA_Sign       = 64
569    valOfType CertificateType_DSS_Sign         = 2
570    valOfType CertificateType_RSA_Fixed_DH     = 3
571    valOfType CertificateType_DSS_Fixed_DH     = 4
572    valOfType CertificateType_RSA_Ephemeral_DH = 5
573    valOfType CertificateType_DSS_Ephemeral_DH = 6
574    valOfType CertificateType_fortezza_dms     = 20
575    valOfType CertificateType_RSA_Fixed_ECDH   = 65
576    valOfType CertificateType_ECDSA_Fixed_ECDH = 66
577    valOfType (CertificateType_Unknown i)      = i
578    -- | There are no code points that map to the below synthetic types, these
579    -- are inferred indirectly from the @signature_algorithms@ extension of the
580    -- TLS 1.3 @CertificateRequest@ message.  the value assignments are there
581    -- only to avoid partial function warnings.
582    valOfType CertificateType_Ed25519_Sign     = 0
583    valOfType CertificateType_Ed448_Sign       = 0
584
585    valToType 1  = Just CertificateType_RSA_Sign
586    valToType 2  = Just CertificateType_DSS_Sign
587    valToType 3  = Just CertificateType_RSA_Fixed_DH
588    valToType 4  = Just CertificateType_DSS_Fixed_DH
589    valToType 5  = Just CertificateType_RSA_Ephemeral_DH
590    valToType 6  = Just CertificateType_DSS_Ephemeral_DH
591    valToType 20 = Just CertificateType_fortezza_dms
592    valToType 64 = Just CertificateType_ECDSA_Sign
593    valToType 65 = Just CertificateType_RSA_Fixed_ECDH
594    valToType 66 = Just CertificateType_ECDSA_Fixed_ECDH
595    valToType i  = Just (CertificateType_Unknown i)
596    -- | There are no code points that map to the below synthetic types, these
597    -- are inferred indirectly from the @signature_algorithms@ extension of the
598    -- TLS 1.3 @CertificateRequest@ message.
599    -- @
600    -- CertificateType_Ed25519_Sign
601    -- CertificateType_Ed448_Sign
602    -- @
603
604instance TypeValuable HashAlgorithm where
605    valOfType HashNone      = 0
606    valOfType HashMD5       = 1
607    valOfType HashSHA1      = 2
608    valOfType HashSHA224    = 3
609    valOfType HashSHA256    = 4
610    valOfType HashSHA384    = 5
611    valOfType HashSHA512    = 6
612    valOfType HashIntrinsic = 8
613    valOfType (HashOther i) = i
614
615    valToType 0 = Just HashNone
616    valToType 1 = Just HashMD5
617    valToType 2 = Just HashSHA1
618    valToType 3 = Just HashSHA224
619    valToType 4 = Just HashSHA256
620    valToType 5 = Just HashSHA384
621    valToType 6 = Just HashSHA512
622    valToType 8 = Just HashIntrinsic
623    valToType i = Just (HashOther i)
624
625instance TypeValuable SignatureAlgorithm where
626    valOfType SignatureAnonymous        =  0
627    valOfType SignatureRSA              =  1
628    valOfType SignatureDSS              =  2
629    valOfType SignatureECDSA            =  3
630    valOfType SignatureRSApssRSAeSHA256 =  4
631    valOfType SignatureRSApssRSAeSHA384 =  5
632    valOfType SignatureRSApssRSAeSHA512 =  6
633    valOfType SignatureEd25519          =  7
634    valOfType SignatureEd448            =  8
635    valOfType SignatureRSApsspssSHA256  =  9
636    valOfType SignatureRSApsspssSHA384  = 10
637    valOfType SignatureRSApsspssSHA512  = 11
638    valOfType (SignatureOther i)        =  i
639
640    valToType  0 = Just SignatureAnonymous
641    valToType  1 = Just SignatureRSA
642    valToType  2 = Just SignatureDSS
643    valToType  3 = Just SignatureECDSA
644    valToType  4 = Just SignatureRSApssRSAeSHA256
645    valToType  5 = Just SignatureRSApssRSAeSHA384
646    valToType  6 = Just SignatureRSApssRSAeSHA512
647    valToType  7 = Just SignatureEd25519
648    valToType  8 = Just SignatureEd448
649    valToType  9 = Just SignatureRSApsspssSHA256
650    valToType 10 = Just SignatureRSApsspssSHA384
651    valToType 11 = Just SignatureRSApsspssSHA512
652    valToType  i = Just (SignatureOther i)
653
654instance EnumSafe16 Group where
655    fromEnumSafe16 P256      =  23
656    fromEnumSafe16 P384      =  24
657    fromEnumSafe16 P521      =  25
658    fromEnumSafe16 X25519    =  29
659    fromEnumSafe16 X448      =  30
660    fromEnumSafe16 FFDHE2048 = 256
661    fromEnumSafe16 FFDHE3072 = 257
662    fromEnumSafe16 FFDHE4096 = 258
663    fromEnumSafe16 FFDHE6144 = 259
664    fromEnumSafe16 FFDHE8192 = 260
665
666    toEnumSafe16  23 = Just P256
667    toEnumSafe16  24 = Just P384
668    toEnumSafe16  25 = Just P521
669    toEnumSafe16  29 = Just X25519
670    toEnumSafe16  30 = Just X448
671    toEnumSafe16 256 = Just FFDHE2048
672    toEnumSafe16 257 = Just FFDHE3072
673    toEnumSafe16 258 = Just FFDHE4096
674    toEnumSafe16 259 = Just FFDHE6144
675    toEnumSafe16 260 = Just FFDHE8192
676    toEnumSafe16 _   = Nothing
677