module Network.TLS.Extra.Cipher
(
ciphersuite_all
, ciphersuite_medium
, ciphersuite_strong
, ciphersuite_unencrypted
, ciphersuite_dhe_rsa
, ciphersuite_dhe_dss
, cipher_null_SHA1
, cipher_null_MD5
, cipher_RC4_128_MD5
, cipher_RC4_128_SHA1
, cipher_AES128_SHA1
, cipher_AES256_SHA1
, cipher_AES128_SHA256
, cipher_AES256_SHA256
, cipher_RSA_3DES_EDE_CBC_SHA1
, cipher_DHE_RSA_AES128_SHA1
, cipher_DHE_RSA_AES256_SHA1
, cipher_DHE_RSA_AES128_SHA256
, cipher_DHE_RSA_AES256_SHA256
, cipher_DHE_DSS_AES128_SHA1
, cipher_DHE_DSS_AES256_SHA1
, cipher_DHE_DSS_RC4_SHA1
, cipher_DHE_RSA_AES128GCM_SHA256
, cipher_ECDHE_RSA_AES128GCM_SHA256
) where
import qualified Data.ByteString as B
import Network.TLS (Version(..))
import Network.TLS.Cipher
import Data.Tuple (swap)
import Crypto.Cipher.AES
import qualified Crypto.Cipher.RC4 as RC4
import Crypto.Cipher.TripleDES
import Crypto.Cipher.Types hiding (Cipher, cipherName)
import Crypto.Error
takelast :: Int -> B.ByteString -> B.ByteString
takelast i b = B.drop (B.length b i) b
aes128cbc :: BulkDirection -> BulkKey -> BulkBlock
aes128cbc BulkEncrypt key =
let ctx = noFail (cipherInit key) :: AES128
in (\iv input -> let output = cbcEncrypt ctx (makeIV_ iv) input in (output, takelast 16 output))
aes128cbc BulkDecrypt key =
let ctx = noFail (cipherInit key) :: AES128
in (\iv input -> let output = cbcDecrypt ctx (makeIV_ iv) input in (output, takelast 16 input))
aes256cbc :: BulkDirection -> BulkKey -> BulkBlock
aes256cbc BulkEncrypt key =
let ctx = noFail (cipherInit key) :: AES256
in (\iv input -> let output = cbcEncrypt ctx (makeIV_ iv) input in (output, takelast 16 output))
aes256cbc BulkDecrypt key =
let ctx = noFail (cipherInit key) :: AES256
in (\iv input -> let output = cbcDecrypt ctx (makeIV_ iv) input in (output, takelast 16 input))
aes128gcm :: BulkDirection -> BulkKey -> BulkAEAD
aes128gcm BulkEncrypt key =
let ctx = noFail (cipherInit key) :: AES128
in (\nonce d ad ->
let aeadIni = noFail (aeadInit AEAD_GCM ctx nonce)
in swap $ aeadSimpleEncrypt aeadIni ad d 16)
aes128gcm BulkDecrypt key =
let ctx = noFail (cipherInit key) :: AES128
in (\nonce d ad ->
let aeadIni = noFail (aeadInit AEAD_GCM ctx nonce)
in simpleDecrypt aeadIni ad d)
where
simpleDecrypt aeadIni header input = (output, tag)
where
aead = aeadAppendHeader aeadIni header
(output, aeadFinal) = aeadDecrypt aead input
tag = aeadFinalize aeadFinal 16
noFail :: CryptoFailable a -> a
noFail = throwCryptoError
makeIV_ :: BlockCipher a => B.ByteString -> IV a
makeIV_ = maybe (error "makeIV_") id . makeIV
tripledes_ede :: BulkDirection -> BulkKey -> BulkBlock
tripledes_ede BulkEncrypt key =
let ctx = noFail $ cipherInit key
in (\iv input -> let output = cbcEncrypt ctx (tripledes_iv iv) input in (output, takelast 16 output))
tripledes_ede BulkDecrypt key =
let ctx = noFail $ cipherInit key
in (\iv input -> let output = cbcDecrypt ctx (tripledes_iv iv) input in (output, takelast 16 input))
tripledes_iv :: BulkIV -> IV DES_EDE3
tripledes_iv iv = maybe (error "tripledes cipher iv internal error") id $ makeIV iv
rc4 :: BulkDirection -> BulkKey -> BulkStream
rc4 _ bulkKey = BulkStream (combineRC4 $ RC4.initialize bulkKey)
where
combineRC4 ctx input =
let (ctx', output) = RC4.combine ctx input
in (output, BulkStream (combineRC4 ctx'))
ciphersuite_all :: [Cipher]
ciphersuite_all =
[ cipher_DHE_RSA_AES256_SHA256, cipher_DHE_RSA_AES128_SHA256
, cipher_DHE_RSA_AES256_SHA1, cipher_DHE_RSA_AES128_SHA1
, cipher_DHE_DSS_AES256_SHA1, cipher_DHE_DSS_AES128_SHA1
, cipher_AES128_SHA256, cipher_AES256_SHA256
, cipher_AES128_SHA1, cipher_AES256_SHA1
, cipher_DHE_DSS_RC4_SHA1, cipher_RC4_128_SHA1, cipher_RC4_128_MD5
, cipher_RSA_3DES_EDE_CBC_SHA1
, cipher_DHE_RSA_AES128GCM_SHA256
]
ciphersuite_medium :: [Cipher]
ciphersuite_medium = [cipher_RC4_128_MD5, cipher_RC4_128_SHA1, cipher_AES128_SHA1, cipher_AES256_SHA1]
ciphersuite_strong :: [Cipher]
ciphersuite_strong = [cipher_DHE_RSA_AES256_SHA256, cipher_AES256_SHA256, cipher_AES256_SHA1]
ciphersuite_dhe_rsa :: [Cipher]
ciphersuite_dhe_rsa = [cipher_DHE_RSA_AES256_SHA256, cipher_DHE_RSA_AES128_SHA256
, cipher_DHE_RSA_AES256_SHA1, cipher_DHE_RSA_AES128_SHA1
, cipher_DHE_RSA_AES128GCM_SHA256]
ciphersuite_dhe_dss :: [Cipher]
ciphersuite_dhe_dss = [cipher_DHE_DSS_AES256_SHA1, cipher_DHE_DSS_AES128_SHA1, cipher_DHE_DSS_RC4_SHA1]
ciphersuite_unencrypted :: [Cipher]
ciphersuite_unencrypted = [cipher_null_MD5, cipher_null_SHA1]
bulk_null, bulk_rc4, bulk_aes128, bulk_aes256, bulk_tripledes_ede, bulk_aes128gcm :: Bulk
bulk_null = Bulk
{ bulkName = "null"
, bulkKeySize = 0
, bulkIVSize = 0
, bulkBlockSize = 0
, bulkF = BulkStreamF passThrough
}
where
passThrough _ _ = BulkStream go where go inp = (inp, BulkStream go)
bulk_rc4 = Bulk
{ bulkName = "RC4-128"
, bulkKeySize = 16
, bulkIVSize = 0
, bulkBlockSize = 0
, bulkF = BulkStreamF rc4
}
bulk_aes128 = Bulk
{ bulkName = "AES128"
, bulkKeySize = 16
, bulkIVSize = 16
, bulkBlockSize = 16
, bulkF = BulkBlockF aes128cbc
}
bulk_aes128gcm = Bulk
{ bulkName = "AES128GCM"
, bulkKeySize = 16
, bulkIVSize = 4
, bulkBlockSize = 0
, bulkF = BulkAeadF aes128gcm
}
bulk_aes256 = Bulk
{ bulkName = "AES256"
, bulkKeySize = 32
, bulkIVSize = 16
, bulkBlockSize = 16
, bulkF = BulkBlockF aes256cbc
}
bulk_tripledes_ede = Bulk
{ bulkName = "3DES-EDE-CBC"
, bulkKeySize = 24
, bulkIVSize = 8
, bulkBlockSize = 8
, bulkF = BulkBlockF tripledes_ede
}
cipher_null_MD5 :: Cipher
cipher_null_MD5 = Cipher
{ cipherID = 0x1
, cipherName = "RSA-null-MD5"
, cipherBulk = bulk_null
, cipherHash = MD5
, cipherKeyExchange = CipherKeyExchange_RSA
, cipherMinVer = Nothing
}
cipher_null_SHA1 :: Cipher
cipher_null_SHA1 = Cipher
{ cipherID = 0x2
, cipherName = "RSA-null-SHA1"
, cipherBulk = bulk_null
, cipherHash = SHA1
, cipherKeyExchange = CipherKeyExchange_RSA
, cipherMinVer = Nothing
}
cipher_RC4_128_MD5 :: Cipher
cipher_RC4_128_MD5 = Cipher
{ cipherID = 0x04
, cipherName = "RSA-rc4-128-md5"
, cipherBulk = bulk_rc4
, cipherHash = MD5
, cipherKeyExchange = CipherKeyExchange_RSA
, cipherMinVer = Nothing
}
cipher_RC4_128_SHA1 :: Cipher
cipher_RC4_128_SHA1 = Cipher
{ cipherID = 0x05
, cipherName = "RSA-rc4-128-sha1"
, cipherBulk = bulk_rc4
, cipherHash = SHA1
, cipherKeyExchange = CipherKeyExchange_RSA
, cipherMinVer = Nothing
}
cipher_AES128_SHA1 :: Cipher
cipher_AES128_SHA1 = Cipher
{ cipherID = 0x2f
, cipherName = "RSA-aes128-sha1"
, cipherBulk = bulk_aes128
, cipherHash = SHA1
, cipherKeyExchange = CipherKeyExchange_RSA
, cipherMinVer = Just SSL3
}
cipher_AES256_SHA1 :: Cipher
cipher_AES256_SHA1 = Cipher
{ cipherID = 0x35
, cipherName = "RSA-aes256-sha1"
, cipherBulk = bulk_aes256
, cipherHash = SHA1
, cipherKeyExchange = CipherKeyExchange_RSA
, cipherMinVer = Just SSL3
}
cipher_AES128_SHA256 :: Cipher
cipher_AES128_SHA256 = Cipher
{ cipherID = 0x3c
, cipherName = "RSA-aes128-sha256"
, cipherBulk = bulk_aes128
, cipherHash = SHA256
, cipherKeyExchange = CipherKeyExchange_RSA
, cipherMinVer = Just TLS12
}
cipher_AES256_SHA256 :: Cipher
cipher_AES256_SHA256 = Cipher
{ cipherID = 0x3d
, cipherName = "RSA-aes256-sha256"
, cipherBulk = bulk_aes256
, cipherHash = SHA256
, cipherKeyExchange = CipherKeyExchange_RSA
, cipherMinVer = Just TLS12
}
cipher_DHE_RSA_AES128_SHA1 :: Cipher
cipher_DHE_RSA_AES128_SHA1 = Cipher
{ cipherID = 0x33
, cipherName = "DHE-RSA-AES128-SHA1"
, cipherBulk = bulk_aes128
, cipherHash = SHA1
, cipherKeyExchange = CipherKeyExchange_DHE_RSA
, cipherMinVer = Nothing
}
cipher_DHE_RSA_AES256_SHA1 :: Cipher
cipher_DHE_RSA_AES256_SHA1 = cipher_DHE_RSA_AES128_SHA1
{ cipherID = 0x39
, cipherName = "DHE-RSA-AES256-SHA1"
, cipherBulk = bulk_aes256
}
cipher_DHE_DSS_AES128_SHA1 :: Cipher
cipher_DHE_DSS_AES128_SHA1 = Cipher
{ cipherID = 0x32
, cipherName = "DHE-DSA-AES128-SHA1"
, cipherBulk = bulk_aes128
, cipherHash = SHA1
, cipherKeyExchange = CipherKeyExchange_DHE_DSS
, cipherMinVer = Nothing
}
cipher_DHE_DSS_AES256_SHA1 :: Cipher
cipher_DHE_DSS_AES256_SHA1 = cipher_DHE_DSS_AES128_SHA1
{ cipherID = 0x38
, cipherName = "DHE-DSA-AES256-SHA1"
, cipherBulk = bulk_aes256
}
cipher_DHE_DSS_RC4_SHA1 :: Cipher
cipher_DHE_DSS_RC4_SHA1 = cipher_DHE_DSS_AES128_SHA1
{ cipherID = 0x66
, cipherName = "DHE-DSA-RC4-SHA1"
, cipherBulk = bulk_rc4
}
cipher_DHE_RSA_AES128_SHA256 :: Cipher
cipher_DHE_RSA_AES128_SHA256 = cipher_DHE_RSA_AES128_SHA1
{ cipherID = 0x67
, cipherName = "DHE-RSA-AES128-SHA256"
, cipherHash = SHA256
, cipherMinVer = Just TLS12
}
cipher_DHE_RSA_AES256_SHA256 :: Cipher
cipher_DHE_RSA_AES256_SHA256 = cipher_DHE_RSA_AES128_SHA256
{ cipherID = 0x6b
, cipherName = "DHE-RSA-AES256-SHA256"
, cipherBulk = bulk_aes256
}
cipher_RSA_3DES_EDE_CBC_SHA1 :: Cipher
cipher_RSA_3DES_EDE_CBC_SHA1 = Cipher
{ cipherID = 0x0a
, cipherName = "RSA-3DES-EDE-CBC-SHA1"
, cipherBulk = bulk_tripledes_ede
, cipherHash = SHA1
, cipherKeyExchange = CipherKeyExchange_RSA
, cipherMinVer = Nothing
}
cipher_DHE_RSA_AES128GCM_SHA256 :: Cipher
cipher_DHE_RSA_AES128GCM_SHA256 = Cipher
{ cipherID = 0x9e
, cipherName = "DHE-RSA-AES128GCM-SHA256"
, cipherBulk = bulk_aes128gcm
, cipherHash = SHA256
, cipherKeyExchange = CipherKeyExchange_DHE_RSA
, cipherMinVer = Just TLS12
}
cipher_ECDHE_RSA_AES128GCM_SHA256 :: Cipher
cipher_ECDHE_RSA_AES128GCM_SHA256 = Cipher
{ cipherID = 0xc02f
, cipherName = "ECDHE-RSA-AES128GCM-SHA256"
, cipherBulk = bulk_aes128gcm
, cipherHash = SHA256
, cipherKeyExchange = CipherKeyExchange_ECDHE_RSA
, cipherMinVer = Just TLS12
}