1-- |
2-- Module      : Network.TLS.Extra.Cipher
3-- License     : BSD-style
4-- Maintainer  : Vincent Hanquez <vincent@snarc.org>
5-- Stability   : experimental
6-- Portability : unknown
7--
8module Network.TLS.Extra.Cipher
9    (
10    -- * cipher suite
11      ciphersuite_default
12    , ciphersuite_default_det
13    , ciphersuite_all
14    , ciphersuite_all_det
15    , ciphersuite_medium
16    , ciphersuite_strong
17    , ciphersuite_strong_det
18    , ciphersuite_unencrypted
19    , ciphersuite_dhe_rsa
20    , ciphersuite_dhe_dss
21    -- * individual ciphers
22    , cipher_null_SHA1
23    , cipher_AES128_SHA1
24    , cipher_AES256_SHA1
25    , cipher_AES128_SHA256
26    , cipher_AES256_SHA256
27    , cipher_AES128CCM_SHA256
28    , cipher_AES128CCM8_SHA256
29    , cipher_AES128GCM_SHA256
30    , cipher_AES256CCM_SHA256
31    , cipher_AES256CCM8_SHA256
32    , cipher_AES256GCM_SHA384
33    , cipher_DHE_RSA_AES128_SHA1
34    , cipher_DHE_RSA_AES256_SHA1
35    , cipher_DHE_RSA_AES128_SHA256
36    , cipher_DHE_RSA_AES256_SHA256
37    , cipher_DHE_DSS_AES128_SHA1
38    , cipher_DHE_DSS_AES256_SHA1
39    , cipher_DHE_RSA_AES128CCM_SHA256
40    , cipher_DHE_RSA_AES128CCM8_SHA256
41    , cipher_DHE_RSA_AES128GCM_SHA256
42    , cipher_DHE_RSA_AES256CCM_SHA256
43    , cipher_DHE_RSA_AES256CCM8_SHA256
44    , cipher_DHE_RSA_AES256GCM_SHA384
45    , cipher_DHE_RSA_CHACHA20POLY1305_SHA256
46    , cipher_ECDHE_RSA_AES128GCM_SHA256
47    , cipher_ECDHE_RSA_AES256GCM_SHA384
48    , cipher_ECDHE_RSA_AES128CBC_SHA256
49    , cipher_ECDHE_RSA_AES128CBC_SHA
50    , cipher_ECDHE_RSA_AES256CBC_SHA
51    , cipher_ECDHE_RSA_AES256CBC_SHA384
52    , cipher_ECDHE_RSA_CHACHA20POLY1305_SHA256
53    , cipher_ECDHE_ECDSA_AES128CBC_SHA
54    , cipher_ECDHE_ECDSA_AES256CBC_SHA
55    , cipher_ECDHE_ECDSA_AES128CBC_SHA256
56    , cipher_ECDHE_ECDSA_AES256CBC_SHA384
57    , cipher_ECDHE_ECDSA_AES128CCM_SHA256
58    , cipher_ECDHE_ECDSA_AES128CCM8_SHA256
59    , cipher_ECDHE_ECDSA_AES128GCM_SHA256
60    , cipher_ECDHE_ECDSA_AES256CCM_SHA256
61    , cipher_ECDHE_ECDSA_AES256CCM8_SHA256
62    , cipher_ECDHE_ECDSA_AES256GCM_SHA384
63    , cipher_ECDHE_ECDSA_CHACHA20POLY1305_SHA256
64    -- TLS 1.3
65    , cipher_TLS13_AES128GCM_SHA256
66    , cipher_TLS13_AES256GCM_SHA384
67    , cipher_TLS13_CHACHA20POLY1305_SHA256
68    , cipher_TLS13_AES128CCM_SHA256
69    , cipher_TLS13_AES128CCM8_SHA256
70    -- * obsolete and non-standard ciphers
71    , cipher_RSA_3DES_EDE_CBC_SHA1
72    , cipher_RC4_128_MD5
73    , cipher_RC4_128_SHA1
74    , cipher_null_MD5
75    , cipher_DHE_DSS_RC4_SHA1
76    ) where
77
78import qualified Data.ByteString as B
79
80import Network.TLS.Types (Version(..))
81import Network.TLS.Cipher
82import Network.TLS.Imports
83import Data.Tuple (swap)
84
85import Crypto.Cipher.AES
86import qualified Crypto.Cipher.ChaChaPoly1305 as ChaChaPoly1305
87import qualified Crypto.Cipher.RC4 as RC4
88import Crypto.Cipher.TripleDES
89import Crypto.Cipher.Types hiding (Cipher, cipherName)
90import Crypto.Error
91import qualified Crypto.MAC.Poly1305 as Poly1305
92import Crypto.System.CPU
93
94takelast :: Int -> B.ByteString -> B.ByteString
95takelast i b = B.drop (B.length b - i) b
96
97aes128cbc :: BulkDirection -> BulkKey -> BulkBlock
98aes128cbc BulkEncrypt key =
99    let ctx = noFail (cipherInit key) :: AES128
100     in (\iv input -> let output = cbcEncrypt ctx (makeIV_ iv) input in (output, takelast 16 output))
101aes128cbc BulkDecrypt key =
102    let ctx = noFail (cipherInit key) :: AES128
103     in (\iv input -> let output = cbcDecrypt ctx (makeIV_ iv) input in (output, takelast 16 input))
104
105aes256cbc :: BulkDirection -> BulkKey -> BulkBlock
106aes256cbc BulkEncrypt key =
107    let ctx = noFail (cipherInit key) :: AES256
108     in (\iv input -> let output = cbcEncrypt ctx (makeIV_ iv) input in (output, takelast 16 output))
109aes256cbc BulkDecrypt key =
110    let ctx = noFail (cipherInit key) :: AES256
111     in (\iv input -> let output = cbcDecrypt ctx (makeIV_ iv) input in (output, takelast 16 input))
112
113aes128ccm :: BulkDirection -> BulkKey -> BulkAEAD
114aes128ccm BulkEncrypt key =
115    let ctx = noFail (cipherInit key) :: AES128
116     in (\nonce d ad ->
117            let mode = AEAD_CCM (B.length d) CCM_M16 CCM_L3
118                aeadIni = noFail (aeadInit mode ctx nonce)
119             in swap $ aeadSimpleEncrypt aeadIni ad d 16)
120aes128ccm BulkDecrypt key =
121    let ctx = noFail (cipherInit key) :: AES128
122     in (\nonce d ad ->
123            let mode = AEAD_CCM (B.length d) CCM_M16 CCM_L3
124                aeadIni = noFail (aeadInit mode ctx nonce)
125             in simpleDecrypt aeadIni ad d 16)
126
127aes128ccm8 :: BulkDirection -> BulkKey -> BulkAEAD
128aes128ccm8 BulkEncrypt key =
129    let ctx = noFail (cipherInit key) :: AES128
130     in (\nonce d ad ->
131            let mode = AEAD_CCM (B.length d) CCM_M8 CCM_L3
132                aeadIni = noFail (aeadInit mode ctx nonce)
133             in swap $ aeadSimpleEncrypt aeadIni ad d 8)
134aes128ccm8 BulkDecrypt key =
135    let ctx = noFail (cipherInit key) :: AES128
136     in (\nonce d ad ->
137            let mode = AEAD_CCM (B.length d) CCM_M8 CCM_L3
138                aeadIni = noFail (aeadInit mode ctx nonce)
139             in simpleDecrypt aeadIni ad d 8)
140
141aes128gcm :: BulkDirection -> BulkKey -> BulkAEAD
142aes128gcm BulkEncrypt key =
143    let ctx = noFail (cipherInit key) :: AES128
144     in (\nonce d ad ->
145            let aeadIni = noFail (aeadInit AEAD_GCM ctx nonce)
146             in swap $ aeadSimpleEncrypt aeadIni ad d 16)
147aes128gcm BulkDecrypt key =
148    let ctx = noFail (cipherInit key) :: AES128
149     in (\nonce d ad ->
150            let aeadIni = noFail (aeadInit AEAD_GCM ctx nonce)
151             in simpleDecrypt aeadIni ad d 16)
152
153aes256ccm :: BulkDirection -> BulkKey -> BulkAEAD
154aes256ccm BulkEncrypt key =
155    let ctx = noFail (cipherInit key) :: AES256
156     in (\nonce d ad ->
157            let mode = AEAD_CCM (B.length d) CCM_M16 CCM_L3
158                aeadIni = noFail (aeadInit mode ctx nonce)
159             in swap $ aeadSimpleEncrypt aeadIni ad d 16)
160aes256ccm BulkDecrypt key =
161    let ctx = noFail (cipherInit key) :: AES256
162     in (\nonce d ad ->
163            let mode = AEAD_CCM (B.length d) CCM_M16 CCM_L3
164                aeadIni = noFail (aeadInit mode ctx nonce)
165             in simpleDecrypt aeadIni ad d 16)
166
167aes256ccm8 :: BulkDirection -> BulkKey -> BulkAEAD
168aes256ccm8 BulkEncrypt key =
169    let ctx = noFail (cipherInit key) :: AES256
170     in (\nonce d ad ->
171            let mode = AEAD_CCM (B.length d) CCM_M8 CCM_L3
172                aeadIni = noFail (aeadInit mode ctx nonce)
173             in swap $ aeadSimpleEncrypt aeadIni ad d 8)
174aes256ccm8 BulkDecrypt key =
175    let ctx = noFail (cipherInit key) :: AES256
176     in (\nonce d ad ->
177            let mode = AEAD_CCM (B.length d) CCM_M8 CCM_L3
178                aeadIni = noFail (aeadInit mode ctx nonce)
179             in simpleDecrypt aeadIni ad d 8)
180
181aes256gcm :: BulkDirection -> BulkKey -> BulkAEAD
182aes256gcm BulkEncrypt key =
183    let ctx = noFail (cipherInit key) :: AES256
184     in (\nonce d ad ->
185            let aeadIni = noFail (aeadInit AEAD_GCM ctx nonce)
186             in swap $ aeadSimpleEncrypt aeadIni ad d 16)
187aes256gcm BulkDecrypt key =
188    let ctx = noFail (cipherInit key) :: AES256
189     in (\nonce d ad ->
190            let aeadIni = noFail (aeadInit AEAD_GCM ctx nonce)
191             in simpleDecrypt aeadIni ad d 16)
192
193simpleDecrypt :: AEAD cipher -> B.ByteString -> B.ByteString -> Int -> (B.ByteString, AuthTag)
194simpleDecrypt aeadIni header input taglen = (output, tag)
195  where
196        aead                = aeadAppendHeader aeadIni header
197        (output, aeadFinal) = aeadDecrypt aead input
198        tag                 = aeadFinalize aeadFinal taglen
199
200noFail :: CryptoFailable a -> a
201noFail = throwCryptoError
202
203makeIV_ :: BlockCipher a => B.ByteString -> IV a
204makeIV_ = fromMaybe (error "makeIV_") . makeIV
205
206tripledes_ede :: BulkDirection -> BulkKey -> BulkBlock
207tripledes_ede BulkEncrypt key =
208    let ctx = noFail $ cipherInit key
209     in (\iv input -> let output = cbcEncrypt ctx (tripledes_iv iv) input in (output, takelast 8 output))
210tripledes_ede BulkDecrypt key =
211    let ctx = noFail $ cipherInit key
212     in (\iv input -> let output = cbcDecrypt ctx (tripledes_iv iv) input in (output, takelast 8 input))
213
214tripledes_iv :: BulkIV -> IV DES_EDE3
215tripledes_iv iv = fromMaybe (error "tripledes cipher iv internal error") $ makeIV iv
216
217rc4 :: BulkDirection -> BulkKey -> BulkStream
218rc4 _ bulkKey = BulkStream (combineRC4 $ RC4.initialize bulkKey)
219  where
220    combineRC4 ctx input =
221        let (ctx', output) = RC4.combine ctx input
222         in (output, BulkStream (combineRC4 ctx'))
223
224chacha20poly1305 :: BulkDirection -> BulkKey -> BulkAEAD
225chacha20poly1305 BulkEncrypt key nonce =
226    let st = noFail (ChaChaPoly1305.nonce12 nonce >>= ChaChaPoly1305.initialize key)
227     in (\input ad ->
228            let st2 = ChaChaPoly1305.finalizeAAD (ChaChaPoly1305.appendAAD ad st)
229                (output, st3) = ChaChaPoly1305.encrypt input st2
230                Poly1305.Auth tag = ChaChaPoly1305.finalize st3
231            in (output, AuthTag tag))
232chacha20poly1305 BulkDecrypt key nonce =
233    let st = noFail (ChaChaPoly1305.nonce12 nonce >>= ChaChaPoly1305.initialize key)
234     in (\input ad ->
235            let st2 = ChaChaPoly1305.finalizeAAD (ChaChaPoly1305.appendAAD ad st)
236                (output, st3) = ChaChaPoly1305.decrypt input st2
237                Poly1305.Auth tag = ChaChaPoly1305.finalize st3
238            in (output, AuthTag tag))
239
240data CipherSet
241    = SetAead [Cipher] [Cipher] [Cipher]  -- gcm, chacha, ccm
242    | SetOther [Cipher]
243
244-- Preference between AEAD ciphers having equivalent properties is based on
245-- hardware-acceleration support in the cryptonite implementation.
246sortOptimized :: [CipherSet] -> [Cipher]
247sortOptimized = concatMap f
248  where
249    f (SetAead gcm chacha ccm)
250        | AESNI  `notElem` processorOptions = chacha ++ gcm ++ ccm
251        | PCLMUL `notElem` processorOptions = ccm ++ chacha ++ gcm
252        | otherwise                         = gcm ++ ccm ++ chacha
253    f (SetOther ciphers) = ciphers
254
255-- Order which is deterministic but not optimized for the CPU.
256sortDeterministic :: [CipherSet] -> [Cipher]
257sortDeterministic = concatMap f
258  where
259    f (SetAead gcm chacha ccm) = gcm ++ chacha ++ ccm
260    f (SetOther ciphers) = ciphers
261
262-- | All AES and ChaCha20-Poly1305 ciphers supported ordered from strong to
263-- weak.  This choice of ciphersuites should satisfy most normal needs.  For
264-- otherwise strong ciphers we make little distinction between AES128 and
265-- AES256, and list each but the weakest of the AES128 ciphers ahead of the
266-- corresponding AES256 ciphers.
267--
268-- AEAD ciphers with equivalent security properties are ordered based on CPU
269-- hardware-acceleration support.  If this dynamic runtime behavior is not
270-- desired, use 'ciphersuite_default_det' instead.
271ciphersuite_default :: [Cipher]
272ciphersuite_default = sortOptimized sets_default
273
274-- | Same as 'ciphersuite_default', but using deterministic preference not
275-- influenced by the CPU.
276ciphersuite_default_det :: [Cipher]
277ciphersuite_default_det = sortDeterministic sets_default
278
279sets_default :: [CipherSet]
280sets_default =
281    [        -- First the PFS + GCM + SHA2 ciphers
282      SetAead
283        [ cipher_ECDHE_ECDSA_AES128GCM_SHA256, cipher_ECDHE_ECDSA_AES256GCM_SHA384 ]
284        [ cipher_ECDHE_ECDSA_CHACHA20POLY1305_SHA256 ]
285        [ cipher_ECDHE_ECDSA_AES128CCM_SHA256, cipher_ECDHE_ECDSA_AES256CCM_SHA256 ]
286    , SetAead
287        [ cipher_ECDHE_RSA_AES128GCM_SHA256, cipher_ECDHE_RSA_AES256GCM_SHA384 ]
288        [ cipher_ECDHE_RSA_CHACHA20POLY1305_SHA256 ]
289        []
290    , SetAead
291        [ cipher_DHE_RSA_AES128GCM_SHA256, cipher_DHE_RSA_AES256GCM_SHA384 ]
292        [ cipher_DHE_RSA_CHACHA20POLY1305_SHA256 ]
293        [ cipher_DHE_RSA_AES128CCM_SHA256, cipher_DHE_RSA_AES256CCM_SHA256 ]
294             -- Next the PFS + CBC + SHA2 ciphers
295    , SetOther
296          [ cipher_ECDHE_ECDSA_AES128CBC_SHA256, cipher_ECDHE_ECDSA_AES256CBC_SHA384
297          , cipher_ECDHE_RSA_AES128CBC_SHA256, cipher_ECDHE_RSA_AES256CBC_SHA384
298          , cipher_DHE_RSA_AES128_SHA256, cipher_DHE_RSA_AES256_SHA256
299          ]
300             -- Next the PFS + CBC + SHA1 ciphers
301    , SetOther
302          [ cipher_ECDHE_ECDSA_AES128CBC_SHA, cipher_ECDHE_ECDSA_AES256CBC_SHA
303          , cipher_ECDHE_RSA_AES128CBC_SHA, cipher_ECDHE_RSA_AES256CBC_SHA
304          , cipher_DHE_RSA_AES128_SHA1, cipher_DHE_RSA_AES256_SHA1
305          ]
306             -- Next the non-PFS + AEAD + SHA2 ciphers
307    , SetAead
308        [ cipher_AES128GCM_SHA256, cipher_AES256GCM_SHA384 ]
309        []
310        [ cipher_AES128CCM_SHA256, cipher_AES256CCM_SHA256 ]
311             -- Next the non-PFS + CBC + SHA2 ciphers
312    , SetOther [ cipher_AES256_SHA256, cipher_AES128_SHA256 ]
313             -- Next the non-PFS + CBC + SHA1 ciphers
314    , SetOther [ cipher_AES256_SHA1, cipher_AES128_SHA1 ]
315             -- Nobody uses or should use DSS, RC4,  3DES or MD5
316--  , SetOther
317--      [ cipher_DHE_DSS_AES256_SHA1, cipher_DHE_DSS_AES128_SHA1
318--      , cipher_DHE_DSS_RC4_SHA1, cipher_RC4_128_SHA1, cipher_RC4_128_MD5
319--      , cipher_RSA_3DES_EDE_CBC_SHA1
320--      ]
321             -- TLS13 (listed at the end but version is negotiated first)
322    , SetAead
323        [ cipher_TLS13_AES128GCM_SHA256, cipher_TLS13_AES256GCM_SHA384 ]
324        [ cipher_TLS13_CHACHA20POLY1305_SHA256 ]
325        [ cipher_TLS13_AES128CCM_SHA256 ]
326    ]
327
328{-# WARNING ciphersuite_all "This ciphersuite list contains RC4. Use ciphersuite_strong or ciphersuite_default instead." #-}
329-- | The default ciphersuites + some not recommended last resort ciphers.
330--
331-- AEAD ciphers with equivalent security properties are ordered based on CPU
332-- hardware-acceleration support.  If this dynamic runtime behavior is not
333-- desired, use 'ciphersuite_all_det' instead.
334ciphersuite_all :: [Cipher]
335ciphersuite_all = ciphersuite_default ++ complement_all
336
337{-# WARNING ciphersuite_all_det "This ciphersuite list contains RC4. Use ciphersuite_strong_det or ciphersuite_default_det instead." #-}
338-- | Same as 'ciphersuite_all', but using deterministic preference not
339-- influenced by the CPU.
340ciphersuite_all_det :: [Cipher]
341ciphersuite_all_det = ciphersuite_default_det ++ complement_all
342
343complement_all :: [Cipher]
344complement_all =
345    [ cipher_ECDHE_ECDSA_AES128CCM8_SHA256, cipher_ECDHE_ECDSA_AES256CCM8_SHA256
346    , cipher_DHE_RSA_AES128CCM8_SHA256, cipher_DHE_RSA_AES256CCM8_SHA256
347    , cipher_DHE_DSS_AES256_SHA1, cipher_DHE_DSS_AES128_SHA1
348    , cipher_AES128CCM8_SHA256, cipher_AES256CCM8_SHA256
349    , cipher_RSA_3DES_EDE_CBC_SHA1
350    , cipher_RC4_128_SHA1
351    , cipher_TLS13_AES128CCM8_SHA256
352    ]
353
354{-# DEPRECATED ciphersuite_medium "Use ciphersuite_strong or ciphersuite_default instead." #-}
355-- | list of medium ciphers.
356ciphersuite_medium :: [Cipher]
357ciphersuite_medium = [ cipher_RC4_128_SHA1
358                     , cipher_AES128_SHA1
359                     ]
360
361-- | The strongest ciphers supported.  For ciphers with PFS, AEAD and SHA2, we
362-- list each AES128 variant after the corresponding AES256 and ChaCha20-Poly1305
363-- variants.  For weaker constructs, we use just the AES256 form.
364--
365-- AEAD ciphers with equivalent security properties are ordered based on CPU
366-- hardware-acceleration support.  If this dynamic runtime behavior is not
367-- desired, use 'ciphersuite_strong_det' instead.
368ciphersuite_strong :: [Cipher]
369ciphersuite_strong = sortOptimized sets_strong
370
371-- | Same as 'ciphersuite_strong', but using deterministic preference not
372-- influenced by the CPU.
373ciphersuite_strong_det :: [Cipher]
374ciphersuite_strong_det = sortDeterministic sets_strong
375
376sets_strong :: [CipherSet]
377sets_strong =
378    [        -- If we have PFS + AEAD + SHA2, then allow AES128, else just 256
379      SetAead [ cipher_ECDHE_ECDSA_AES256GCM_SHA384 ]
380              [ cipher_ECDHE_ECDSA_CHACHA20POLY1305_SHA256 ]
381              [ cipher_ECDHE_ECDSA_AES256CCM_SHA256 ]
382    , SetAead [ cipher_ECDHE_ECDSA_AES128GCM_SHA256 ]
383              []
384              [ cipher_ECDHE_ECDSA_AES128CCM_SHA256 ]
385    , SetAead [ cipher_ECDHE_RSA_AES256GCM_SHA384 ]
386              [ cipher_ECDHE_RSA_CHACHA20POLY1305_SHA256 ]
387              []
388    , SetAead [ cipher_ECDHE_RSA_AES128GCM_SHA256 ]
389              []
390              []
391    , SetAead [ cipher_DHE_RSA_AES256GCM_SHA384 ]
392              [ cipher_DHE_RSA_CHACHA20POLY1305_SHA256 ]
393              [ cipher_DHE_RSA_AES256CCM_SHA256 ]
394    , SetAead [ cipher_DHE_RSA_AES128GCM_SHA256 ]
395              []
396              [ cipher_DHE_RSA_AES128CCM_SHA256 ]
397             -- No AEAD
398    , SetOther
399        [ cipher_ECDHE_ECDSA_AES256CBC_SHA384
400        , cipher_ECDHE_RSA_AES256CBC_SHA384
401        , cipher_DHE_RSA_AES256_SHA256
402        ]
403             -- No SHA2
404    , SetOther
405        [ cipher_ECDHE_ECDSA_AES256CBC_SHA
406        , cipher_ECDHE_RSA_AES256CBC_SHA
407        , cipher_DHE_RSA_AES256_SHA1
408        ]
409             -- No PFS
410    , SetAead [ cipher_AES256GCM_SHA384 ]
411              []
412              [ cipher_AES256CCM_SHA256 ]
413             -- Neither PFS nor AEAD, just SHA2
414    , SetOther [ cipher_AES256_SHA256 ]
415             -- Last resort no PFS, AEAD or SHA2
416    , SetOther [ cipher_AES256_SHA1 ]
417             -- TLS13 (listed at the end but version is negotiated first)
418    , SetAead [ cipher_TLS13_AES256GCM_SHA384 ]
419              [ cipher_TLS13_CHACHA20POLY1305_SHA256 ]
420              []
421    , SetAead [ cipher_TLS13_AES128GCM_SHA256 ]
422              []
423              [ cipher_TLS13_AES128CCM_SHA256 ]
424    ]
425
426-- | DHE-RSA cipher suite.  This only includes ciphers bound specifically to
427-- DHE-RSA so TLS 1.3 ciphers must be added separately.
428ciphersuite_dhe_rsa :: [Cipher]
429ciphersuite_dhe_rsa = [ cipher_DHE_RSA_AES256GCM_SHA384, cipher_DHE_RSA_AES256CCM_SHA256
430                      , cipher_DHE_RSA_CHACHA20POLY1305_SHA256
431                      , cipher_DHE_RSA_AES128GCM_SHA256, cipher_DHE_RSA_AES128CCM_SHA256
432                      , cipher_DHE_RSA_AES256_SHA256, cipher_DHE_RSA_AES128_SHA256
433                      , cipher_DHE_RSA_AES256_SHA1, cipher_DHE_RSA_AES128_SHA1
434                      ]
435
436ciphersuite_dhe_dss :: [Cipher]
437ciphersuite_dhe_dss = [cipher_DHE_DSS_AES256_SHA1, cipher_DHE_DSS_AES128_SHA1, cipher_DHE_DSS_RC4_SHA1]
438
439-- | all unencrypted ciphers, do not use on insecure network.
440ciphersuite_unencrypted :: [Cipher]
441ciphersuite_unencrypted = [cipher_null_MD5, cipher_null_SHA1]
442
443bulk_null, bulk_rc4, bulk_aes128, bulk_aes256, bulk_tripledes_ede, bulk_aes128gcm, bulk_aes256gcm :: Bulk
444bulk_aes128ccm, bulk_aes128ccm8, bulk_aes256ccm, bulk_aes256ccm8, bulk_chacha20poly1305 :: Bulk
445bulk_null = Bulk
446    { bulkName         = "null"
447    , bulkKeySize      = 0
448    , bulkIVSize       = 0
449    , bulkExplicitIV   = 0
450    , bulkAuthTagLen   = 0
451    , bulkBlockSize    = 0
452    , bulkF            = BulkStreamF passThrough
453    }
454  where
455    passThrough _ _ = BulkStream go where go inp = (inp, BulkStream go)
456
457bulk_rc4 = Bulk
458    { bulkName         = "RC4-128"
459    , bulkKeySize      = 16
460    , bulkIVSize       = 0
461    , bulkExplicitIV   = 0
462    , bulkAuthTagLen   = 0
463    , bulkBlockSize    = 0
464    , bulkF            = BulkStreamF rc4
465    }
466
467bulk_aes128 = Bulk
468    { bulkName         = "AES128"
469    , bulkKeySize      = 16
470    , bulkIVSize       = 16
471    , bulkExplicitIV   = 0
472    , bulkAuthTagLen   = 0
473    , bulkBlockSize    = 16
474    , bulkF            = BulkBlockF aes128cbc
475    }
476
477bulk_aes128ccm = Bulk
478    { bulkName         = "AES128CCM"
479    , bulkKeySize      = 16 -- RFC 5116 Sec 5.1: K_LEN
480    , bulkIVSize       = 4  -- RFC 6655 CCMNonce.salt, fixed_iv_length
481    , bulkExplicitIV   = 8
482    , bulkAuthTagLen   = 16
483    , bulkBlockSize    = 0  -- dummy, not used
484    , bulkF            = BulkAeadF aes128ccm
485    }
486
487bulk_aes128ccm8 = Bulk
488    { bulkName         = "AES128CCM8"
489    , bulkKeySize      = 16 -- RFC 5116 Sec 5.1: K_LEN
490    , bulkIVSize       = 4  -- RFC 6655 CCMNonce.salt, fixed_iv_length
491    , bulkExplicitIV   = 8
492    , bulkAuthTagLen   = 8
493    , bulkBlockSize    = 0  -- dummy, not used
494    , bulkF            = BulkAeadF aes128ccm8
495    }
496
497bulk_aes128gcm = Bulk
498    { bulkName         = "AES128GCM"
499    , bulkKeySize      = 16 -- RFC 5116 Sec 5.1: K_LEN
500    , bulkIVSize       = 4  -- RFC 5288 GCMNonce.salt, fixed_iv_length
501    , bulkExplicitIV   = 8
502    , bulkAuthTagLen   = 16
503    , bulkBlockSize    = 0  -- dummy, not used
504    , bulkF            = BulkAeadF aes128gcm
505    }
506
507bulk_aes256ccm = Bulk
508    { bulkName         = "AES256CCM"
509    , bulkKeySize      = 32 -- RFC 5116 Sec 5.1: K_LEN
510    , bulkIVSize       = 4  -- RFC 6655 CCMNonce.salt, fixed_iv_length
511    , bulkExplicitIV   = 8
512    , bulkAuthTagLen   = 16
513    , bulkBlockSize    = 0  -- dummy, not used
514    , bulkF            = BulkAeadF aes256ccm
515    }
516
517bulk_aes256ccm8 = Bulk
518    { bulkName         = "AES256CCM8"
519    , bulkKeySize      = 32 -- RFC 5116 Sec 5.1: K_LEN
520    , bulkIVSize       = 4  -- RFC 6655 CCMNonce.salt, fixed_iv_length
521    , bulkExplicitIV   = 8
522    , bulkAuthTagLen   = 8
523    , bulkBlockSize    = 0  -- dummy, not used
524    , bulkF            = BulkAeadF aes256ccm8
525    }
526
527bulk_aes256gcm = Bulk
528    { bulkName         = "AES256GCM"
529    , bulkKeySize      = 32 -- RFC 5116 Sec 5.1: K_LEN
530    , bulkIVSize       = 4  -- RFC 5288 GCMNonce.salt, fixed_iv_length
531    , bulkExplicitIV   = 8
532    , bulkAuthTagLen   = 16
533    , bulkBlockSize    = 0  -- dummy, not used
534    , bulkF            = BulkAeadF aes256gcm
535    }
536
537bulk_aes256 = Bulk
538    { bulkName         = "AES256"
539    , bulkKeySize      = 32
540    , bulkIVSize       = 16
541    , bulkExplicitIV   = 0
542    , bulkAuthTagLen   = 0
543    , bulkBlockSize    = 16
544    , bulkF            = BulkBlockF aes256cbc
545    }
546
547bulk_tripledes_ede = Bulk
548    { bulkName      = "3DES-EDE-CBC"
549    , bulkKeySize   = 24
550    , bulkIVSize    = 8
551    , bulkExplicitIV = 0
552    , bulkAuthTagLen = 0
553    , bulkBlockSize = 8
554    , bulkF         = BulkBlockF tripledes_ede
555    }
556
557bulk_chacha20poly1305 = Bulk
558    { bulkName         = "CHACHA20POLY1305"
559    , bulkKeySize      = 32
560    , bulkIVSize       = 12 -- RFC 7905 section 2, fixed_iv_length
561    , bulkExplicitIV   = 0
562    , bulkAuthTagLen   = 16
563    , bulkBlockSize    = 0  -- dummy, not used
564    , bulkF            = BulkAeadF chacha20poly1305
565    }
566
567-- TLS13 bulks are same as TLS12 except they never have explicit IV
568bulk_aes128gcm_13, bulk_aes256gcm_13, bulk_aes128ccm_13, bulk_aes128ccm8_13 :: Bulk
569bulk_aes128gcm_13  = bulk_aes128gcm  { bulkIVSize = 12, bulkExplicitIV = 0 }
570bulk_aes256gcm_13  = bulk_aes256gcm  { bulkIVSize = 12, bulkExplicitIV = 0 }
571bulk_aes128ccm_13  = bulk_aes128ccm  { bulkIVSize = 12, bulkExplicitIV = 0 }
572bulk_aes128ccm8_13 = bulk_aes128ccm8 { bulkIVSize = 12, bulkExplicitIV = 0 }
573
574-- | unencrypted cipher using RSA for key exchange and MD5 for digest
575cipher_null_MD5 :: Cipher
576cipher_null_MD5 = Cipher
577    { cipherID           = 0x0001
578    , cipherName         = "RSA-null-MD5"
579    , cipherBulk         = bulk_null
580    , cipherHash         = MD5
581    , cipherPRFHash      = Nothing
582    , cipherKeyExchange  = CipherKeyExchange_RSA
583    , cipherMinVer       = Nothing
584    }
585
586-- | unencrypted cipher using RSA for key exchange and SHA1 for digest
587cipher_null_SHA1 :: Cipher
588cipher_null_SHA1 = Cipher
589    { cipherID           = 0x0002
590    , cipherName         = "RSA-null-SHA1"
591    , cipherBulk         = bulk_null
592    , cipherHash         = SHA1
593    , cipherPRFHash      = Nothing
594    , cipherKeyExchange  = CipherKeyExchange_RSA
595    , cipherMinVer       = Nothing
596    }
597
598-- | RC4 cipher, RSA key exchange and MD5 for digest
599cipher_RC4_128_MD5 :: Cipher
600cipher_RC4_128_MD5 = Cipher
601    { cipherID           = 0x0004
602    , cipherName         = "RSA-rc4-128-md5"
603    , cipherBulk         = bulk_rc4
604    , cipherHash         = MD5
605    , cipherPRFHash      = Nothing
606    , cipherKeyExchange  = CipherKeyExchange_RSA
607    , cipherMinVer       = Nothing
608    }
609
610-- | RC4 cipher, RSA key exchange and SHA1 for digest
611cipher_RC4_128_SHA1 :: Cipher
612cipher_RC4_128_SHA1 = Cipher
613    { cipherID           = 0x0005
614    , cipherName         = "RSA-rc4-128-sha1"
615    , cipherBulk         = bulk_rc4
616    , cipherHash         = SHA1
617    , cipherPRFHash      = Nothing
618    , cipherKeyExchange  = CipherKeyExchange_RSA
619    , cipherMinVer       = Nothing
620    }
621
622-- | 3DES cipher (168 bit key), RSA key exchange and SHA1 for digest
623cipher_RSA_3DES_EDE_CBC_SHA1 :: Cipher
624cipher_RSA_3DES_EDE_CBC_SHA1 = Cipher
625    { cipherID           = 0x000A
626    , cipherName         = "RSA-3DES-EDE-CBC-SHA1"
627    , cipherBulk         = bulk_tripledes_ede
628    , cipherHash         = SHA1
629    , cipherPRFHash      = Nothing
630    , cipherKeyExchange  = CipherKeyExchange_RSA
631    , cipherMinVer       = Nothing
632    }
633
634-- | AES cipher (128 bit key), RSA key exchange and SHA1 for digest
635cipher_AES128_SHA1 :: Cipher
636cipher_AES128_SHA1 = Cipher
637    { cipherID           = 0x002F
638    , cipherName         = "RSA-AES128-SHA1"
639    , cipherBulk         = bulk_aes128
640    , cipherHash         = SHA1
641    , cipherPRFHash      = Nothing
642    , cipherKeyExchange  = CipherKeyExchange_RSA
643    , cipherMinVer       = Just SSL3
644    }
645
646-- | AES cipher (128 bit key), DHE key exchanged signed by DSA and SHA1 for digest
647cipher_DHE_DSS_AES128_SHA1 :: Cipher
648cipher_DHE_DSS_AES128_SHA1 = Cipher
649    { cipherID           = 0x0032
650    , cipherName         = "DHE-DSA-AES128-SHA1"
651    , cipherBulk         = bulk_aes128
652    , cipherHash         = SHA1
653    , cipherPRFHash      = Nothing
654    , cipherKeyExchange  = CipherKeyExchange_DHE_DSS
655    , cipherMinVer       = Nothing
656    }
657
658-- | AES cipher (128 bit key), DHE key exchanged signed by RSA and SHA1 for digest
659cipher_DHE_RSA_AES128_SHA1 :: Cipher
660cipher_DHE_RSA_AES128_SHA1 = Cipher
661    { cipherID           = 0x0033
662    , cipherName         = "DHE-RSA-AES128-SHA1"
663    , cipherBulk         = bulk_aes128
664    , cipherHash         = SHA1
665    , cipherPRFHash      = Nothing
666    , cipherKeyExchange  = CipherKeyExchange_DHE_RSA
667    , cipherMinVer       = Nothing
668    }
669
670-- | AES cipher (256 bit key), RSA key exchange and SHA1 for digest
671cipher_AES256_SHA1 :: Cipher
672cipher_AES256_SHA1 = Cipher
673    { cipherID           = 0x0035
674    , cipherName         = "RSA-AES256-SHA1"
675    , cipherBulk         = bulk_aes256
676    , cipherHash         = SHA1
677    , cipherPRFHash      = Nothing
678    , cipherKeyExchange  = CipherKeyExchange_RSA
679    , cipherMinVer       = Just SSL3
680    }
681
682-- | AES cipher (256 bit key), DHE key exchanged signed by DSA and SHA1 for digest
683cipher_DHE_DSS_AES256_SHA1 :: Cipher
684cipher_DHE_DSS_AES256_SHA1 = cipher_DHE_DSS_AES128_SHA1
685    { cipherID           = 0x0038
686    , cipherName         = "DHE-DSA-AES256-SHA1"
687    , cipherBulk         = bulk_aes256
688    }
689
690-- | AES cipher (256 bit key), DHE key exchanged signed by RSA and SHA1 for digest
691cipher_DHE_RSA_AES256_SHA1 :: Cipher
692cipher_DHE_RSA_AES256_SHA1 = cipher_DHE_RSA_AES128_SHA1
693    { cipherID           = 0x0039
694    , cipherName         = "DHE-RSA-AES256-SHA1"
695    , cipherBulk         = bulk_aes256
696    }
697
698-- | AES cipher (128 bit key), RSA key exchange and SHA256 for digest
699cipher_AES128_SHA256 :: Cipher
700cipher_AES128_SHA256 = Cipher
701    { cipherID           = 0x003C
702    , cipherName         = "RSA-AES128-SHA256"
703    , cipherBulk         = bulk_aes128
704    , cipherHash         = SHA256
705    , cipherPRFHash      = Just SHA256
706    , cipherKeyExchange  = CipherKeyExchange_RSA
707    , cipherMinVer       = Just TLS12
708    }
709
710-- | AES cipher (256 bit key), RSA key exchange and SHA256 for digest
711cipher_AES256_SHA256 :: Cipher
712cipher_AES256_SHA256 = Cipher
713    { cipherID           = 0x003D
714    , cipherName         = "RSA-AES256-SHA256"
715    , cipherBulk         = bulk_aes256
716    , cipherHash         = SHA256
717    , cipherPRFHash      = Just SHA256
718    , cipherKeyExchange  = CipherKeyExchange_RSA
719    , cipherMinVer       = Just TLS12
720    }
721
722-- This is not registered in IANA.
723-- So, this will be removed in the next major release.
724cipher_DHE_DSS_RC4_SHA1 :: Cipher
725cipher_DHE_DSS_RC4_SHA1 = cipher_DHE_DSS_AES128_SHA1
726    { cipherID           = 0x0066
727    , cipherName         = "DHE-DSA-RC4-SHA1"
728    , cipherBulk         = bulk_rc4
729    }
730
731cipher_DHE_RSA_AES128_SHA256 :: Cipher
732cipher_DHE_RSA_AES128_SHA256 = cipher_DHE_RSA_AES128_SHA1
733    { cipherID           = 0x0067
734    , cipherName         = "DHE-RSA-AES128-SHA256"
735    , cipherHash         = SHA256
736    , cipherPRFHash      = Just SHA256
737    , cipherMinVer       = Just TLS12
738    }
739
740cipher_DHE_RSA_AES256_SHA256 :: Cipher
741cipher_DHE_RSA_AES256_SHA256 = cipher_DHE_RSA_AES128_SHA256
742    { cipherID           = 0x006B
743    , cipherName         = "DHE-RSA-AES256-SHA256"
744    , cipherBulk         = bulk_aes256
745    }
746
747-- | AESCCM cipher (128 bit key), RSA key exchange.
748-- The SHA256 digest is used as a PRF, not as a MAC.
749cipher_AES128CCM_SHA256 :: Cipher
750cipher_AES128CCM_SHA256 = Cipher
751    { cipherID           = 0xc09c
752    , cipherName         = "RSA-AES128CCM-SHA256"
753    , cipherBulk         = bulk_aes128ccm
754    , cipherHash         = SHA256
755    , cipherPRFHash      = Just SHA256
756    , cipherKeyExchange  = CipherKeyExchange_RSA
757    , cipherMinVer       = Just TLS12 -- RFC 6655 Sec 3
758    }
759
760-- | AESCCM8 cipher (128 bit key), RSA key exchange.
761-- The SHA256 digest is used as a PRF, not as a MAC.
762cipher_AES128CCM8_SHA256 :: Cipher
763cipher_AES128CCM8_SHA256 = Cipher
764    { cipherID           = 0xc0a0
765    , cipherName         = "RSA-AES128CCM8-SHA256"
766    , cipherBulk         = bulk_aes128ccm8
767    , cipherHash         = SHA256
768    , cipherPRFHash      = Just SHA256
769    , cipherKeyExchange  = CipherKeyExchange_RSA
770    , cipherMinVer       = Just TLS12 -- RFC 6655 Sec 3
771    }
772
773-- | AESGCM cipher (128 bit key), RSA key exchange.
774-- The SHA256 digest is used as a PRF, not as a MAC.
775cipher_AES128GCM_SHA256 :: Cipher
776cipher_AES128GCM_SHA256 = Cipher
777    { cipherID           = 0x009C
778    , cipherName         = "RSA-AES128GCM-SHA256"
779    , cipherBulk         = bulk_aes128gcm
780    , cipherHash         = SHA256
781    , cipherPRFHash      = Just SHA256
782    , cipherKeyExchange  = CipherKeyExchange_RSA
783    , cipherMinVer       = Just TLS12
784    }
785
786-- | AESCCM cipher (256 bit key), RSA key exchange.
787-- The SHA256 digest is used as a PRF, not as a MAC.
788cipher_AES256CCM_SHA256 :: Cipher
789cipher_AES256CCM_SHA256 = Cipher
790    { cipherID           = 0xc09d
791    , cipherName         = "RSA-AES256CCM-SHA256"
792    , cipherBulk         = bulk_aes256ccm
793    , cipherHash         = SHA256
794    , cipherPRFHash      = Just SHA256
795    , cipherKeyExchange  = CipherKeyExchange_RSA
796    , cipherMinVer       = Just TLS12 -- RFC 6655 Sec 3
797    }
798
799-- | AESCCM8 cipher (256 bit key), RSA key exchange.
800-- The SHA256 digest is used as a PRF, not as a MAC.
801cipher_AES256CCM8_SHA256 :: Cipher
802cipher_AES256CCM8_SHA256 = Cipher
803    { cipherID           = 0xc0a1
804    , cipherName         = "RSA-AES256CCM8-SHA256"
805    , cipherBulk         = bulk_aes256ccm8
806    , cipherHash         = SHA256
807    , cipherPRFHash      = Just SHA256
808    , cipherKeyExchange  = CipherKeyExchange_RSA
809    , cipherMinVer       = Just TLS12 -- RFC 6655 Sec 3
810    }
811
812-- | AESGCM cipher (256 bit key), RSA key exchange.
813-- The SHA384 digest is used as a PRF, not as a MAC.
814cipher_AES256GCM_SHA384 :: Cipher
815cipher_AES256GCM_SHA384 = Cipher
816    { cipherID           = 0x009D
817    , cipherName         = "RSA-AES256GCM-SHA384"
818    , cipherBulk         = bulk_aes256gcm
819    , cipherHash         = SHA384
820    , cipherPRFHash      = Just SHA384
821    , cipherKeyExchange  = CipherKeyExchange_RSA
822    , cipherMinVer       = Just TLS12
823    }
824
825cipher_DHE_RSA_AES128CCM_SHA256 :: Cipher
826cipher_DHE_RSA_AES128CCM_SHA256 = Cipher
827    { cipherID           = 0xc09e
828    , cipherName         = "DHE-RSA-AES128CCM-SHA256"
829    , cipherBulk         = bulk_aes128ccm
830    , cipherHash         = SHA256
831    , cipherPRFHash      = Just SHA256
832    , cipherKeyExchange  = CipherKeyExchange_DHE_RSA
833    , cipherMinVer       = Just TLS12 -- RFC 6655 Sec 3
834    }
835
836cipher_DHE_RSA_AES128CCM8_SHA256 :: Cipher
837cipher_DHE_RSA_AES128CCM8_SHA256 = Cipher
838    { cipherID           = 0xc0a2
839    , cipherName         = "DHE-RSA-AES128CCM8-SHA256"
840    , cipherBulk         = bulk_aes128ccm8
841    , cipherHash         = SHA256
842    , cipherPRFHash      = Just SHA256
843    , cipherKeyExchange  = CipherKeyExchange_DHE_RSA
844    , cipherMinVer       = Just TLS12 -- RFC 6655 Sec 3
845    }
846
847cipher_DHE_RSA_AES128GCM_SHA256 :: Cipher
848cipher_DHE_RSA_AES128GCM_SHA256 = Cipher
849    { cipherID           = 0x009E
850    , cipherName         = "DHE-RSA-AES128GCM-SHA256"
851    , cipherBulk         = bulk_aes128gcm
852    , cipherHash         = SHA256
853    , cipherPRFHash      = Just SHA256
854    , cipherKeyExchange  = CipherKeyExchange_DHE_RSA
855    , cipherMinVer       = Just TLS12 -- RFC 5288 Sec 4
856    }
857
858cipher_DHE_RSA_AES256CCM_SHA256 :: Cipher
859cipher_DHE_RSA_AES256CCM_SHA256 = Cipher
860    { cipherID           = 0xc09f
861    , cipherName         = "DHE-RSA-AES256CCM-SHA256"
862    , cipherBulk         = bulk_aes256ccm
863    , cipherHash         = SHA256
864    , cipherPRFHash      = Just SHA256
865    , cipherKeyExchange  = CipherKeyExchange_DHE_RSA
866    , cipherMinVer       = Just TLS12 -- RFC 6655 Sec 3
867    }
868
869cipher_DHE_RSA_AES256CCM8_SHA256 :: Cipher
870cipher_DHE_RSA_AES256CCM8_SHA256 = Cipher
871    { cipherID           = 0xc0a3
872    , cipherName         = "DHE-RSA-AES256CCM8-SHA256"
873    , cipherBulk         = bulk_aes256ccm8
874    , cipherHash         = SHA256
875    , cipherPRFHash      = Just SHA256
876    , cipherKeyExchange  = CipherKeyExchange_DHE_RSA
877    , cipherMinVer       = Just TLS12 -- RFC 6655 Sec 3
878    }
879
880cipher_DHE_RSA_AES256GCM_SHA384 :: Cipher
881cipher_DHE_RSA_AES256GCM_SHA384 = Cipher
882    { cipherID           = 0x009F
883    , cipherName         = "DHE-RSA-AES256GCM-SHA384"
884    , cipherBulk         = bulk_aes256gcm
885    , cipherHash         = SHA384
886    , cipherPRFHash      = Just SHA384
887    , cipherKeyExchange  = CipherKeyExchange_DHE_RSA
888    , cipherMinVer       = Just TLS12
889    }
890
891cipher_ECDHE_RSA_CHACHA20POLY1305_SHA256 :: Cipher
892cipher_ECDHE_RSA_CHACHA20POLY1305_SHA256 = Cipher
893    { cipherID           = 0xCCA8
894    , cipherName         = "ECDHE-RSA-CHACHA20POLY1305-SHA256"
895    , cipherBulk         = bulk_chacha20poly1305
896    , cipherHash         = SHA256
897    , cipherPRFHash      = Just SHA256
898    , cipherKeyExchange  = CipherKeyExchange_ECDHE_RSA
899    , cipherMinVer       = Just TLS12
900    }
901
902cipher_ECDHE_ECDSA_CHACHA20POLY1305_SHA256 :: Cipher
903cipher_ECDHE_ECDSA_CHACHA20POLY1305_SHA256 = Cipher
904    { cipherID           = 0xCCA9
905    , cipherName         = "ECDHE-ECDSA-CHACHA20POLY1305-SHA256"
906    , cipherBulk         = bulk_chacha20poly1305
907    , cipherHash         = SHA256
908    , cipherPRFHash      = Just SHA256
909    , cipherKeyExchange  = CipherKeyExchange_ECDHE_ECDSA
910    , cipherMinVer       = Just TLS12
911    }
912
913cipher_DHE_RSA_CHACHA20POLY1305_SHA256 :: Cipher
914cipher_DHE_RSA_CHACHA20POLY1305_SHA256 = Cipher
915    { cipherID           = 0xCCAA
916    , cipherName         = "DHE-RSA-CHACHA20POLY1305-SHA256"
917    , cipherBulk         = bulk_chacha20poly1305
918    , cipherHash         = SHA256
919    , cipherPRFHash      = Just SHA256
920    , cipherKeyExchange  = CipherKeyExchange_DHE_RSA
921    , cipherMinVer       = Just TLS12
922    }
923
924cipher_TLS13_AES128GCM_SHA256 :: Cipher
925cipher_TLS13_AES128GCM_SHA256 = Cipher
926    { cipherID           = 0x1301
927    , cipherName         = "AES128GCM-SHA256"
928    , cipherBulk         = bulk_aes128gcm_13
929    , cipherHash         = SHA256
930    , cipherPRFHash      = Nothing
931    , cipherKeyExchange  = CipherKeyExchange_TLS13
932    , cipherMinVer       = Just TLS13
933    }
934
935cipher_TLS13_AES256GCM_SHA384 :: Cipher
936cipher_TLS13_AES256GCM_SHA384 = Cipher
937    { cipherID           = 0x1302
938    , cipherName         = "AES256GCM-SHA384"
939    , cipherBulk         = bulk_aes256gcm_13
940    , cipherHash         = SHA384
941    , cipherPRFHash      = Nothing
942    , cipherKeyExchange  = CipherKeyExchange_TLS13
943    , cipherMinVer       = Just TLS13
944    }
945
946cipher_TLS13_CHACHA20POLY1305_SHA256 :: Cipher
947cipher_TLS13_CHACHA20POLY1305_SHA256 = Cipher
948    { cipherID           = 0x1303
949    , cipherName         = "CHACHA20POLY1305-SHA256"
950    , cipherBulk         = bulk_chacha20poly1305
951    , cipherHash         = SHA256
952    , cipherPRFHash      = Nothing
953    , cipherKeyExchange  = CipherKeyExchange_TLS13
954    , cipherMinVer       = Just TLS13
955    }
956
957cipher_TLS13_AES128CCM_SHA256 :: Cipher
958cipher_TLS13_AES128CCM_SHA256 = Cipher
959    { cipherID           = 0x1304
960    , cipherName         = "AES128CCM-SHA256"
961    , cipherBulk         = bulk_aes128ccm_13
962    , cipherHash         = SHA256
963    , cipherPRFHash      = Nothing
964    , cipherKeyExchange  = CipherKeyExchange_TLS13
965    , cipherMinVer       = Just TLS13
966    }
967
968cipher_TLS13_AES128CCM8_SHA256 :: Cipher
969cipher_TLS13_AES128CCM8_SHA256 = Cipher
970    { cipherID           = 0x1305
971    , cipherName         = "AES128CCM8-SHA256"
972    , cipherBulk         = bulk_aes128ccm8_13
973    , cipherHash         = SHA256
974    , cipherPRFHash      = Nothing
975    , cipherKeyExchange  = CipherKeyExchange_TLS13
976    , cipherMinVer       = Just TLS13
977    }
978
979cipher_ECDHE_ECDSA_AES128CBC_SHA :: Cipher
980cipher_ECDHE_ECDSA_AES128CBC_SHA = Cipher
981    { cipherID           = 0xC009
982    , cipherName         = "ECDHE-ECDSA-AES128CBC-SHA"
983    , cipherBulk         = bulk_aes128
984    , cipherHash         = SHA1
985    , cipherPRFHash      = Nothing
986    , cipherKeyExchange  = CipherKeyExchange_ECDHE_ECDSA
987    , cipherMinVer       = Just TLS10
988    }
989
990cipher_ECDHE_ECDSA_AES256CBC_SHA :: Cipher
991cipher_ECDHE_ECDSA_AES256CBC_SHA = Cipher
992    { cipherID           = 0xC00A
993    , cipherName         = "ECDHE-ECDSA-AES256CBC-SHA"
994    , cipherBulk         = bulk_aes256
995    , cipherHash         = SHA1
996    , cipherPRFHash      = Nothing
997    , cipherKeyExchange  = CipherKeyExchange_ECDHE_ECDSA
998    , cipherMinVer       = Just TLS10
999    }
1000
1001cipher_ECDHE_RSA_AES128CBC_SHA :: Cipher
1002cipher_ECDHE_RSA_AES128CBC_SHA = Cipher
1003    { cipherID           = 0xC013
1004    , cipherName         = "ECDHE-RSA-AES128CBC-SHA"
1005    , cipherBulk         = bulk_aes128
1006    , cipherHash         = SHA1
1007    , cipherPRFHash      = Nothing
1008    , cipherKeyExchange  = CipherKeyExchange_ECDHE_RSA
1009    , cipherMinVer       = Just TLS10
1010    }
1011
1012cipher_ECDHE_RSA_AES256CBC_SHA :: Cipher
1013cipher_ECDHE_RSA_AES256CBC_SHA = Cipher
1014    { cipherID           = 0xC014
1015    , cipherName         = "ECDHE-RSA-AES256CBC-SHA"
1016    , cipherBulk         = bulk_aes256
1017    , cipherHash         = SHA1
1018    , cipherPRFHash      = Nothing
1019    , cipherKeyExchange  = CipherKeyExchange_ECDHE_RSA
1020    , cipherMinVer       = Just TLS10
1021    }
1022
1023cipher_ECDHE_RSA_AES128CBC_SHA256 :: Cipher
1024cipher_ECDHE_RSA_AES128CBC_SHA256 = Cipher
1025    { cipherID           = 0xC027
1026    , cipherName         = "ECDHE-RSA-AES128CBC-SHA256"
1027    , cipherBulk         = bulk_aes128
1028    , cipherHash         = SHA256
1029    , cipherPRFHash      = Just SHA256
1030    , cipherKeyExchange  = CipherKeyExchange_ECDHE_RSA
1031    , cipherMinVer       = Just TLS12 -- RFC 5288 Sec 4
1032    }
1033
1034cipher_ECDHE_RSA_AES256CBC_SHA384 :: Cipher
1035cipher_ECDHE_RSA_AES256CBC_SHA384 = Cipher
1036    { cipherID           = 0xC028
1037    , cipherName         = "ECDHE-RSA-AES256CBC-SHA384"
1038    , cipherBulk         = bulk_aes256
1039    , cipherHash         = SHA384
1040    , cipherPRFHash      = Just SHA384
1041    , cipherKeyExchange  = CipherKeyExchange_ECDHE_RSA
1042    , cipherMinVer       = Just TLS12 -- RFC 5288 Sec 4
1043    }
1044
1045cipher_ECDHE_ECDSA_AES128CBC_SHA256 :: Cipher
1046cipher_ECDHE_ECDSA_AES128CBC_SHA256 = Cipher
1047    { cipherID           = 0xc023
1048    , cipherName         = "ECDHE-ECDSA-AES128CBC-SHA256"
1049    , cipherBulk         = bulk_aes128
1050    , cipherHash         = SHA256
1051    , cipherPRFHash      = Just SHA256
1052    , cipherKeyExchange  = CipherKeyExchange_ECDHE_ECDSA
1053    , cipherMinVer       = Just TLS12 -- RFC 5289
1054    }
1055
1056cipher_ECDHE_ECDSA_AES256CBC_SHA384 :: Cipher
1057cipher_ECDHE_ECDSA_AES256CBC_SHA384 = Cipher
1058    { cipherID           = 0xC024
1059    , cipherName         = "ECDHE-ECDSA-AES256CBC-SHA384"
1060    , cipherBulk         = bulk_aes256
1061    , cipherHash         = SHA384
1062    , cipherPRFHash      = Just SHA384
1063    , cipherKeyExchange  = CipherKeyExchange_ECDHE_ECDSA
1064    , cipherMinVer       = Just TLS12 -- RFC 5289
1065    }
1066
1067cipher_ECDHE_ECDSA_AES128CCM_SHA256 :: Cipher
1068cipher_ECDHE_ECDSA_AES128CCM_SHA256 = Cipher
1069    { cipherID           = 0xc0ac
1070    , cipherName         = "ECDHE-ECDSA-AES128CCM-SHA256"
1071    , cipherBulk         = bulk_aes128ccm
1072    , cipherHash         = SHA256
1073    , cipherPRFHash      = Just SHA256
1074    , cipherKeyExchange  = CipherKeyExchange_ECDHE_ECDSA
1075    , cipherMinVer       = Just TLS12 -- RFC 7251
1076    }
1077
1078cipher_ECDHE_ECDSA_AES128CCM8_SHA256 :: Cipher
1079cipher_ECDHE_ECDSA_AES128CCM8_SHA256 = Cipher
1080    { cipherID           = 0xc0ae
1081    , cipherName         = "ECDHE-ECDSA-AES128CCM8-SHA256"
1082    , cipherBulk         = bulk_aes128ccm8
1083    , cipherHash         = SHA256
1084    , cipherPRFHash      = Just SHA256
1085    , cipherKeyExchange  = CipherKeyExchange_ECDHE_ECDSA
1086    , cipherMinVer       = Just TLS12 -- RFC 7251
1087    }
1088
1089cipher_ECDHE_ECDSA_AES128GCM_SHA256 :: Cipher
1090cipher_ECDHE_ECDSA_AES128GCM_SHA256 = Cipher
1091    { cipherID           = 0xC02B
1092    , cipherName         = "ECDHE-ECDSA-AES128GCM-SHA256"
1093    , cipherBulk         = bulk_aes128gcm
1094    , cipherHash         = SHA256
1095    , cipherPRFHash      = Just SHA256
1096    , cipherKeyExchange  = CipherKeyExchange_ECDHE_ECDSA
1097    , cipherMinVer       = Just TLS12 -- RFC 5289
1098    }
1099
1100cipher_ECDHE_ECDSA_AES256CCM_SHA256 :: Cipher
1101cipher_ECDHE_ECDSA_AES256CCM_SHA256 = Cipher
1102    { cipherID           = 0xc0ad
1103    , cipherName         = "ECDHE-ECDSA-AES256CCM-SHA256"
1104    , cipherBulk         = bulk_aes256ccm
1105    , cipherHash         = SHA256
1106    , cipherPRFHash      = Just SHA256
1107    , cipherKeyExchange  = CipherKeyExchange_ECDHE_ECDSA
1108    , cipherMinVer       = Just TLS12 -- RFC 7251
1109    }
1110
1111cipher_ECDHE_ECDSA_AES256CCM8_SHA256 :: Cipher
1112cipher_ECDHE_ECDSA_AES256CCM8_SHA256 = Cipher
1113    { cipherID           = 0xc0af
1114    , cipherName         = "ECDHE-ECDSA-AES256CCM8-SHA256"
1115    , cipherBulk         = bulk_aes256ccm8
1116    , cipherHash         = SHA256
1117    , cipherPRFHash      = Just SHA256
1118    , cipherKeyExchange  = CipherKeyExchange_ECDHE_ECDSA
1119    , cipherMinVer       = Just TLS12 -- RFC 7251
1120    }
1121
1122cipher_ECDHE_ECDSA_AES256GCM_SHA384 :: Cipher
1123cipher_ECDHE_ECDSA_AES256GCM_SHA384 = Cipher
1124    { cipherID           = 0xC02C
1125    , cipherName         = "ECDHE-ECDSA-AES256GCM-SHA384"
1126    , cipherBulk         = bulk_aes256gcm
1127    , cipherHash         = SHA384
1128    , cipherPRFHash      = Just SHA384
1129    , cipherKeyExchange  = CipherKeyExchange_ECDHE_ECDSA
1130    , cipherMinVer       = Just TLS12 -- RFC 5289
1131    }
1132
1133cipher_ECDHE_RSA_AES128GCM_SHA256 :: Cipher
1134cipher_ECDHE_RSA_AES128GCM_SHA256 = Cipher
1135    { cipherID           = 0xC02F
1136    , cipherName         = "ECDHE-RSA-AES128GCM-SHA256"
1137    , cipherBulk         = bulk_aes128gcm
1138    , cipherHash         = SHA256
1139    , cipherPRFHash      = Just SHA256
1140    , cipherKeyExchange  = CipherKeyExchange_ECDHE_RSA
1141    , cipherMinVer       = Just TLS12 -- RFC 5288 Sec 4
1142    }
1143
1144cipher_ECDHE_RSA_AES256GCM_SHA384 :: Cipher
1145cipher_ECDHE_RSA_AES256GCM_SHA384 = Cipher
1146    { cipherID           = 0xC030
1147    , cipherName         = "ECDHE-RSA-AES256GCM-SHA384"
1148    , cipherBulk         = bulk_aes256gcm
1149    , cipherHash         = SHA384
1150    , cipherPRFHash      = Just SHA384
1151    , cipherKeyExchange  = CipherKeyExchange_ECDHE_RSA
1152    , cipherMinVer       = Just TLS12 -- RFC 5289
1153    }
1154
1155-- A list of cipher suite is found from:
1156-- https://www.iana.org/assignments/tls-parameters/tls-parameters.xhtml#tls-parameters-4
1157