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_ECDSA_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
211
212-- | Identifier of a TLS extension.
213type ExtensionID  = Word16
214
215-- | The raw content of a TLS extension.
216data ExtensionRaw = ExtensionRaw ExtensionID ByteString
217    deriving (Eq)
218
219instance Show ExtensionRaw where
220    show (ExtensionRaw eid bs) = "ExtensionRaw " ++ showEID eid ++ " " ++ showBytesHex bs
221
222showEID :: ExtensionID -> String
223showEID 0x0 = "ServerName"
224showEID 0x1 = "MaxFragmentLength"
225showEID 0x2 = "ClientCertificateUrl"
226showEID 0x3 = "TrustedCAKeys"
227showEID 0x4 = "TruncatedHMAC"
228showEID 0x5 = "StatusRequest"
229showEID 0x6 = "UserMapping"
230showEID 0x7 = "ClientAuthz"
231showEID 0x8 = "ServerAuthz"
232showEID 0x9 = "CertType"
233showEID 0xa = "NegotiatedGroups"
234showEID 0xb = "EcPointFormats"
235showEID 0xc = "SRP"
236showEID 0xd = "SignatureAlgorithm"
237showEID 0xe = "SRTP"
238showEID 0xf = "Heartbeat"
239showEID 0x10 = "ApplicationLayerProtocolNegotiation"
240showEID 0x11 = "StatusRequestv2"
241showEID 0x12 = "SignedCertificateTimestamp"
242showEID 0x13 = "ClientCertificateType"
243showEID 0x14 = "ServerCertificateType"
244showEID 0x15 = "Padding"
245showEID 0x16 = "EncryptThenMAC"
246showEID 0x17 = "ExtendedMasterSecret"
247showEID 0x23 = "SessionTicket"
248showEID 0x29 = "PreShardeKey"
249showEID 0x2a = "EarlyData"
250showEID 0x2b = "SupportedVersions"
251showEID 0x2c = "Cookie"
252showEID 0x2d = "PskKeyExchangeModes"
253showEID 0x2f = "CertificateAuthorities"
254showEID 0x30 = "OidFilters"
255showEID 0x31 = "PostHandshakeAuth"
256showEID 0x32 = "SignatureAlgorithmsCert"
257showEID 0x33 = "KeyShare"
258showEID 0xff01 = "SecureRenegotiation"
259showEID 0xffa5 = "QuicTransportParameters"
260showEID x      = show x
261
262data AlertLevel =
263      AlertLevel_Warning
264    | AlertLevel_Fatal
265    deriving (Show,Eq)
266
267data AlertDescription =
268      CloseNotify
269    | UnexpectedMessage
270    | BadRecordMac
271    | DecryptionFailed       -- ^ deprecated alert, should never be sent by compliant implementation
272    | RecordOverflow
273    | DecompressionFailure
274    | HandshakeFailure
275    | BadCertificate
276    | UnsupportedCertificate
277    | CertificateRevoked
278    | CertificateExpired
279    | CertificateUnknown
280    | IllegalParameter
281    | UnknownCa
282    | AccessDenied
283    | DecodeError
284    | DecryptError
285    | ExportRestriction
286    | ProtocolVersion
287    | InsufficientSecurity
288    | InternalError
289    | InappropriateFallback -- RFC7507
290    | UserCanceled
291    | NoRenegotiation
292    | MissingExtension
293    | UnsupportedExtension
294    | CertificateUnobtainable
295    | UnrecognizedName
296    | BadCertificateStatusResponse
297    | BadCertificateHashValue
298    | UnknownPskIdentity
299    | CertificateRequired
300    | NoApplicationProtocol -- RFC7301
301    deriving (Show,Eq)
302
303data HandshakeType =
304      HandshakeType_HelloRequest
305    | HandshakeType_ClientHello
306    | HandshakeType_ServerHello
307    | HandshakeType_Certificate
308    | HandshakeType_ServerKeyXchg
309    | HandshakeType_CertRequest
310    | HandshakeType_ServerHelloDone
311    | HandshakeType_CertVerify
312    | HandshakeType_ClientKeyXchg
313    | HandshakeType_Finished
314    deriving (Show,Eq)
315
316newtype BigNum = BigNum ByteString
317    deriving (Show,Eq)
318
319bigNumToInteger :: BigNum -> Integer
320bigNumToInteger (BigNum b) = os2ip b
321
322bigNumFromInteger :: Integer -> BigNum
323bigNumFromInteger i = BigNum $ i2osp i
324
325data ServerDHParams = ServerDHParams
326    { serverDHParams_p :: BigNum
327    , serverDHParams_g :: BigNum
328    , serverDHParams_y :: BigNum
329    } deriving (Show,Eq)
330
331serverDHParamsFrom :: DHParams -> DHPublic -> ServerDHParams
332serverDHParamsFrom params dhPub =
333    ServerDHParams (bigNumFromInteger $ dhParamsGetP params)
334                   (bigNumFromInteger $ dhParamsGetG params)
335                   (bigNumFromInteger $ dhUnwrapPublic dhPub)
336
337serverDHParamsToParams :: ServerDHParams -> DHParams
338serverDHParamsToParams serverParams =
339    dhParams (bigNumToInteger $ serverDHParams_p serverParams)
340             (bigNumToInteger $ serverDHParams_g serverParams)
341
342serverDHParamsToPublic :: ServerDHParams -> DHPublic
343serverDHParamsToPublic serverParams =
344    dhPublic (bigNumToInteger $ serverDHParams_y serverParams)
345
346data ServerECDHParams = ServerECDHParams Group GroupPublic
347    deriving (Show,Eq)
348
349data ServerRSAParams = ServerRSAParams
350    { rsa_modulus  :: Integer
351    , rsa_exponent :: Integer
352    } deriving (Show,Eq)
353
354data ServerKeyXchgAlgorithmData =
355      SKX_DH_Anon ServerDHParams
356    | SKX_DHE_DSS ServerDHParams DigitallySigned
357    | SKX_DHE_RSA ServerDHParams DigitallySigned
358    | SKX_ECDHE_RSA ServerECDHParams DigitallySigned
359    | SKX_ECDHE_ECDSA ServerECDHParams DigitallySigned
360    | SKX_RSA (Maybe ServerRSAParams)
361    | SKX_DH_DSS (Maybe ServerRSAParams)
362    | SKX_DH_RSA (Maybe ServerRSAParams)
363    | SKX_Unparsed ByteString -- if we parse the server key xchg before knowing the actual cipher, we end up with this structure.
364    | SKX_Unknown ByteString
365    deriving (Show,Eq)
366
367data ClientKeyXchgAlgorithmData =
368      CKX_RSA ByteString
369    | CKX_DH DHPublic
370    | CKX_ECDH ByteString
371    deriving (Show,Eq)
372
373type DeprecatedRecord = ByteString
374
375data Handshake =
376      ClientHello !Version !ClientRandom !Session ![CipherID] ![CompressionID] [ExtensionRaw] (Maybe DeprecatedRecord)
377    | ServerHello !Version !ServerRandom !Session !CipherID !CompressionID [ExtensionRaw]
378    | Certificates CertificateChain
379    | HelloRequest
380    | ServerHelloDone
381    | ClientKeyXchg ClientKeyXchgAlgorithmData
382    | ServerKeyXchg ServerKeyXchgAlgorithmData
383    | CertRequest [CertificateType] (Maybe [HashAndSignatureAlgorithm]) [DistinguishedName]
384    | CertVerify DigitallySigned
385    | Finished FinishedData
386    deriving (Show,Eq)
387
388packetType :: Packet -> ProtocolType
389packetType (Handshake _)    = ProtocolType_Handshake
390packetType (Alert _)        = ProtocolType_Alert
391packetType ChangeCipherSpec = ProtocolType_ChangeCipherSpec
392packetType (AppData _)      = ProtocolType_AppData
393
394typeOfHandshake :: Handshake -> HandshakeType
395typeOfHandshake ClientHello{}             = HandshakeType_ClientHello
396typeOfHandshake ServerHello{}             = HandshakeType_ServerHello
397typeOfHandshake Certificates{}            = HandshakeType_Certificate
398typeOfHandshake HelloRequest              = HandshakeType_HelloRequest
399typeOfHandshake ServerHelloDone           = HandshakeType_ServerHelloDone
400typeOfHandshake ClientKeyXchg{}           = HandshakeType_ClientKeyXchg
401typeOfHandshake ServerKeyXchg{}           = HandshakeType_ServerKeyXchg
402typeOfHandshake CertRequest{}             = HandshakeType_CertRequest
403typeOfHandshake CertVerify{}              = HandshakeType_CertVerify
404typeOfHandshake Finished{}                = HandshakeType_Finished
405
406numericalVer :: Version -> (Word8, Word8)
407numericalVer SSL2  = (2, 0)
408numericalVer SSL3  = (3, 0)
409numericalVer TLS10 = (3, 1)
410numericalVer TLS11 = (3, 2)
411numericalVer TLS12 = (3, 3)
412numericalVer TLS13 = (3, 4)
413
414verOfNum :: (Word8, Word8) -> Maybe Version
415verOfNum (2, 0) = Just SSL2
416verOfNum (3, 0) = Just SSL3
417verOfNum (3, 1) = Just TLS10
418verOfNum (3, 2) = Just TLS11
419verOfNum (3, 3) = Just TLS12
420verOfNum (3, 4) = Just TLS13
421verOfNum _      = Nothing
422
423class TypeValuable a where
424    valOfType :: a -> Word8
425    valToType :: Word8 -> Maybe a
426
427-- a better name for TypeValuable
428class EnumSafe8 a where
429    fromEnumSafe8 :: a -> Word8
430    toEnumSafe8   :: Word8 -> Maybe a
431
432class EnumSafe16 a where
433    fromEnumSafe16 :: a -> Word16
434    toEnumSafe16   :: Word16 -> Maybe a
435
436instance TypeValuable ConnectionEnd where
437    valOfType ConnectionServer = 0
438    valOfType ConnectionClient = 1
439
440    valToType 0 = Just ConnectionServer
441    valToType 1 = Just ConnectionClient
442    valToType _ = Nothing
443
444instance TypeValuable CipherType where
445    valOfType CipherStream = 0
446    valOfType CipherBlock  = 1
447    valOfType CipherAEAD   = 2
448
449    valToType 0 = Just CipherStream
450    valToType 1 = Just CipherBlock
451    valToType 2 = Just CipherAEAD
452    valToType _ = Nothing
453
454instance TypeValuable ProtocolType where
455    valOfType ProtocolType_ChangeCipherSpec    = 20
456    valOfType ProtocolType_Alert               = 21
457    valOfType ProtocolType_Handshake           = 22
458    valOfType ProtocolType_AppData             = 23
459    valOfType ProtocolType_DeprecatedHandshake = 128 -- unused
460
461    valToType 20 = Just ProtocolType_ChangeCipherSpec
462    valToType 21 = Just ProtocolType_Alert
463    valToType 22 = Just ProtocolType_Handshake
464    valToType 23 = Just ProtocolType_AppData
465    valToType _  = Nothing
466
467instance TypeValuable HandshakeType where
468    valOfType HandshakeType_HelloRequest    = 0
469    valOfType HandshakeType_ClientHello     = 1
470    valOfType HandshakeType_ServerHello     = 2
471    valOfType HandshakeType_Certificate     = 11
472    valOfType HandshakeType_ServerKeyXchg   = 12
473    valOfType HandshakeType_CertRequest     = 13
474    valOfType HandshakeType_ServerHelloDone = 14
475    valOfType HandshakeType_CertVerify      = 15
476    valOfType HandshakeType_ClientKeyXchg   = 16
477    valOfType HandshakeType_Finished        = 20
478
479    valToType 0  = Just HandshakeType_HelloRequest
480    valToType 1  = Just HandshakeType_ClientHello
481    valToType 2  = Just HandshakeType_ServerHello
482    valToType 11 = Just HandshakeType_Certificate
483    valToType 12 = Just HandshakeType_ServerKeyXchg
484    valToType 13 = Just HandshakeType_CertRequest
485    valToType 14 = Just HandshakeType_ServerHelloDone
486    valToType 15 = Just HandshakeType_CertVerify
487    valToType 16 = Just HandshakeType_ClientKeyXchg
488    valToType 20 = Just HandshakeType_Finished
489    valToType _  = Nothing
490
491instance TypeValuable AlertLevel where
492    valOfType AlertLevel_Warning = 1
493    valOfType AlertLevel_Fatal   = 2
494
495    valToType 1 = Just AlertLevel_Warning
496    valToType 2 = Just AlertLevel_Fatal
497    valToType _ = Nothing
498
499instance TypeValuable AlertDescription where
500    valOfType CloseNotify            = 0
501    valOfType UnexpectedMessage      = 10
502    valOfType BadRecordMac           = 20
503    valOfType DecryptionFailed       = 21
504    valOfType RecordOverflow         = 22
505    valOfType DecompressionFailure   = 30
506    valOfType HandshakeFailure       = 40
507    valOfType BadCertificate         = 42
508    valOfType UnsupportedCertificate = 43
509    valOfType CertificateRevoked     = 44
510    valOfType CertificateExpired     = 45
511    valOfType CertificateUnknown     = 46
512    valOfType IllegalParameter       = 47
513    valOfType UnknownCa              = 48
514    valOfType AccessDenied           = 49
515    valOfType DecodeError            = 50
516    valOfType DecryptError           = 51
517    valOfType ExportRestriction      = 60
518    valOfType ProtocolVersion        = 70
519    valOfType InsufficientSecurity   = 71
520    valOfType InternalError          = 80
521    valOfType InappropriateFallback  = 86
522    valOfType UserCanceled           = 90
523    valOfType NoRenegotiation        = 100
524    valOfType MissingExtension       = 109
525    valOfType UnsupportedExtension   = 110
526    valOfType CertificateUnobtainable = 111
527    valOfType UnrecognizedName        = 112
528    valOfType BadCertificateStatusResponse = 113
529    valOfType BadCertificateHashValue = 114
530    valOfType UnknownPskIdentity      = 115
531    valOfType CertificateRequired     = 116
532    valOfType NoApplicationProtocol   = 120
533
534    valToType 0   = Just CloseNotify
535    valToType 10  = Just UnexpectedMessage
536    valToType 20  = Just BadRecordMac
537    valToType 21  = Just DecryptionFailed
538    valToType 22  = Just RecordOverflow
539    valToType 30  = Just DecompressionFailure
540    valToType 40  = Just HandshakeFailure
541    valToType 42  = Just BadCertificate
542    valToType 43  = Just UnsupportedCertificate
543    valToType 44  = Just CertificateRevoked
544    valToType 45  = Just CertificateExpired
545    valToType 46  = Just CertificateUnknown
546    valToType 47  = Just IllegalParameter
547    valToType 48  = Just UnknownCa
548    valToType 49  = Just AccessDenied
549    valToType 50  = Just DecodeError
550    valToType 51  = Just DecryptError
551    valToType 60  = Just ExportRestriction
552    valToType 70  = Just ProtocolVersion
553    valToType 71  = Just InsufficientSecurity
554    valToType 80  = Just InternalError
555    valToType 86  = Just InappropriateFallback
556    valToType 90  = Just UserCanceled
557    valToType 100 = Just NoRenegotiation
558    valToType 109 = Just MissingExtension
559    valToType 110 = Just UnsupportedExtension
560    valToType 111 = Just CertificateUnobtainable
561    valToType 112 = Just UnrecognizedName
562    valToType 113 = Just BadCertificateStatusResponse
563    valToType 114 = Just BadCertificateHashValue
564    valToType 115 = Just UnknownPskIdentity
565    valToType 116 = Just CertificateRequired
566    valToType 120 = Just NoApplicationProtocol
567    valToType _   = Nothing
568
569instance TypeValuable CertificateType where
570    valOfType CertificateType_RSA_Sign         = 1
571    valOfType CertificateType_ECDSA_Sign       = 64
572    valOfType CertificateType_DSS_Sign         = 2
573    valOfType CertificateType_RSA_Fixed_DH     = 3
574    valOfType CertificateType_DSS_Fixed_DH     = 4
575    valOfType CertificateType_RSA_Ephemeral_DH = 5
576    valOfType CertificateType_DSS_Ephemeral_DH = 6
577    valOfType CertificateType_fortezza_dms     = 20
578    valOfType CertificateType_RSA_Fixed_ECDH   = 65
579    valOfType CertificateType_ECDSA_Fixed_ECDH = 66
580    valOfType (CertificateType_Unknown i)      = i
581    -- | There are no code points that map to the below synthetic types, these
582    -- are inferred indirectly from the @signature_algorithms@ extension of the
583    -- TLS 1.3 @CertificateRequest@ message.  the value assignments are there
584    -- only to avoid partial function warnings.
585    valOfType CertificateType_Ed25519_Sign     = 0
586    valOfType CertificateType_Ed448_Sign       = 0
587
588    valToType 1  = Just CertificateType_RSA_Sign
589    valToType 2  = Just CertificateType_DSS_Sign
590    valToType 3  = Just CertificateType_RSA_Fixed_DH
591    valToType 4  = Just CertificateType_DSS_Fixed_DH
592    valToType 5  = Just CertificateType_RSA_Ephemeral_DH
593    valToType 6  = Just CertificateType_DSS_Ephemeral_DH
594    valToType 20 = Just CertificateType_fortezza_dms
595    valToType 64 = Just CertificateType_ECDSA_Sign
596    valToType 65 = Just CertificateType_RSA_Fixed_ECDH
597    valToType 66 = Just CertificateType_ECDSA_Fixed_ECDH
598    valToType i  = Just (CertificateType_Unknown i)
599    -- | There are no code points that map to the below synthetic types, these
600    -- are inferred indirectly from the @signature_algorithms@ extension of the
601    -- TLS 1.3 @CertificateRequest@ message.
602    -- @
603    -- CertificateType_Ed25519_Sign
604    -- CertificateType_Ed448_Sign
605    -- @
606
607instance TypeValuable HashAlgorithm where
608    valOfType HashNone      = 0
609    valOfType HashMD5       = 1
610    valOfType HashSHA1      = 2
611    valOfType HashSHA224    = 3
612    valOfType HashSHA256    = 4
613    valOfType HashSHA384    = 5
614    valOfType HashSHA512    = 6
615    valOfType HashIntrinsic = 8
616    valOfType (HashOther i) = i
617
618    valToType 0 = Just HashNone
619    valToType 1 = Just HashMD5
620    valToType 2 = Just HashSHA1
621    valToType 3 = Just HashSHA224
622    valToType 4 = Just HashSHA256
623    valToType 5 = Just HashSHA384
624    valToType 6 = Just HashSHA512
625    valToType 8 = Just HashIntrinsic
626    valToType i = Just (HashOther i)
627
628instance TypeValuable SignatureAlgorithm where
629    valOfType SignatureAnonymous        =  0
630    valOfType SignatureRSA              =  1
631    valOfType SignatureDSS              =  2
632    valOfType SignatureECDSA            =  3
633    valOfType SignatureRSApssRSAeSHA256 =  4
634    valOfType SignatureRSApssRSAeSHA384 =  5
635    valOfType SignatureRSApssRSAeSHA512 =  6
636    valOfType SignatureEd25519          =  7
637    valOfType SignatureEd448            =  8
638    valOfType SignatureRSApsspssSHA256  =  9
639    valOfType SignatureRSApsspssSHA384  = 10
640    valOfType SignatureRSApsspssSHA512  = 11
641    valOfType (SignatureOther i)        =  i
642
643    valToType  0 = Just SignatureAnonymous
644    valToType  1 = Just SignatureRSA
645    valToType  2 = Just SignatureDSS
646    valToType  3 = Just SignatureECDSA
647    valToType  4 = Just SignatureRSApssRSAeSHA256
648    valToType  5 = Just SignatureRSApssRSAeSHA384
649    valToType  6 = Just SignatureRSApssRSAeSHA512
650    valToType  7 = Just SignatureEd25519
651    valToType  8 = Just SignatureEd448
652    valToType  9 = Just SignatureRSApsspssSHA256
653    valToType 10 = Just SignatureRSApsspssSHA384
654    valToType 11 = Just SignatureRSApsspssSHA512
655    valToType  i = Just (SignatureOther i)
656
657instance EnumSafe16 Group where
658    fromEnumSafe16 P256      =  23
659    fromEnumSafe16 P384      =  24
660    fromEnumSafe16 P521      =  25
661    fromEnumSafe16 X25519    =  29
662    fromEnumSafe16 X448      =  30
663    fromEnumSafe16 FFDHE2048 = 256
664    fromEnumSafe16 FFDHE3072 = 257
665    fromEnumSafe16 FFDHE4096 = 258
666    fromEnumSafe16 FFDHE6144 = 259
667    fromEnumSafe16 FFDHE8192 = 260
668
669    toEnumSafe16  23 = Just P256
670    toEnumSafe16  24 = Just P384
671    toEnumSafe16  25 = Just P521
672    toEnumSafe16  29 = Just X25519
673    toEnumSafe16  30 = Just X448
674    toEnumSafe16 256 = Just FFDHE2048
675    toEnumSafe16 257 = Just FFDHE3072
676    toEnumSafe16 258 = Just FFDHE4096
677    toEnumSafe16 259 = Just FFDHE6144
678    toEnumSafe16 260 = Just FFDHE8192
679    toEnumSafe16 _   = Nothing
680