Skip to content

Commit

Permalink
defining CipherId and changing CipherID back to Word16
Browse files Browse the repository at this point in the history
This maintains the backward compatibility for Warp
  • Loading branch information
kazu-yamamoto committed Jan 5, 2025
1 parent 5ab5854 commit b247932
Show file tree
Hide file tree
Showing 15 changed files with 54 additions and 99 deletions.
36 changes: 18 additions & 18 deletions tls/Network/TLS/Extra/Cipher.hs
Original file line number Diff line number Diff line change
Expand Up @@ -192,7 +192,7 @@ ciphersuite_dhe_rsa =
cipher_DHE_RSA_WITH_AES_128_GCM_SHA256 :: Cipher
cipher_DHE_RSA_WITH_AES_128_GCM_SHA256 =
Cipher
{ cipherID = CipherID 0x009E
{ cipherID = 0x009E
, cipherName = "TLS_DHE_RSA_WITH_AES_128_GCM_SHA256"
, cipherBulk = bulk_aes128gcm
, cipherHash = SHA256
Expand All @@ -212,7 +212,7 @@ cipher_DHE_RSA_AES128GCM_SHA256 = cipher_DHE_RSA_WITH_AES_128_GCM_SHA256
cipher_DHE_RSA_WITH_AES_256_GCM_SHA384 :: Cipher
cipher_DHE_RSA_WITH_AES_256_GCM_SHA384 =
Cipher
{ cipherID = CipherID 0x009F
{ cipherID = 0x009F
, cipherName = "TLS_DHE_RSA_WITH_AES_256_GCM_SHA384"
, cipherBulk = bulk_aes256gcm
, cipherHash = SHA384
Expand All @@ -235,7 +235,7 @@ cipher_DHE_RSA_AES256GCM_SHA384 = cipher_DHE_RSA_WITH_AES_256_GCM_SHA384
cipher13_AES_128_GCM_SHA256 :: Cipher
cipher13_AES_128_GCM_SHA256 =
Cipher
{ cipherID = CipherID 0x1301
{ cipherID = 0x1301
, cipherName = "TLS_AES_128_GCM_SHA256"
, cipherBulk = bulk_aes128gcm_13
, cipherHash = SHA256
Expand All @@ -255,7 +255,7 @@ cipher_TLS13_AES128GCM_SHA256 = cipher13_AES_128_GCM_SHA256
cipher13_AES_256_GCM_SHA384 :: Cipher
cipher13_AES_256_GCM_SHA384 =
Cipher
{ cipherID = CipherID 0x1302
{ cipherID = 0x1302
, cipherName = "TLS_AES_256_GCM_SHA384"
, cipherBulk = bulk_aes256gcm_13
, cipherHash = SHA384
Expand All @@ -275,7 +275,7 @@ cipher_TLS13_AES256GCM_SHA384 = cipher13_AES_256_GCM_SHA384
cipher13_CHACHA20_POLY1305_SHA256 :: Cipher
cipher13_CHACHA20_POLY1305_SHA256 =
Cipher
{ cipherID = CipherID 0x1303
{ cipherID = 0x1303
, cipherName = "TLS_CHACHA20_POLY1305_SHA256"
, cipherBulk = bulk_chacha20poly1305
, cipherHash = SHA256
Expand All @@ -295,7 +295,7 @@ cipher_TLS13_CHACHA20POLY1305_SHA256 = cipher13_CHACHA20_POLY1305_SHA256
cipher13_AES_128_CCM_SHA256 :: Cipher
cipher13_AES_128_CCM_SHA256 =
Cipher
{ cipherID = CipherID 0x1304
{ cipherID = 0x1304
, cipherName = "TLS_AES_128_CCM_SHA256"
, cipherBulk = bulk_aes128ccm_13
, cipherHash = SHA256
Expand All @@ -315,7 +315,7 @@ cipher_TLS13_AES128CCM_SHA256 = cipher13_AES_128_CCM_SHA256
cipher13_AES_128_CCM_8_SHA256 :: Cipher
cipher13_AES_128_CCM_8_SHA256 =
Cipher
{ cipherID = CipherID 0x1305
{ cipherID = 0x1305
, cipherName = "TLS_AES_128_CCM_8_SHA256"
, cipherBulk = bulk_aes128ccm8_13
, cipherHash = SHA256
Expand All @@ -338,7 +338,7 @@ cipher_TLS13_AES128CCM8_SHA256 = cipher13_AES_128_CCM_8_SHA256
cipher_ECDHE_ECDSA_WITH_AES_128_GCM_SHA256 :: Cipher
cipher_ECDHE_ECDSA_WITH_AES_128_GCM_SHA256 =
Cipher
{ cipherID = CipherID 0xC02B
{ cipherID = 0xC02B
, cipherName = "TLS_ECDHE_ECDSA_WITH_AES_128_GCM_SHA256"
, cipherBulk = bulk_aes128gcm
, cipherHash = SHA256
Expand All @@ -358,7 +358,7 @@ cipher_ECDHE_ECDSA_AES128GCM_SHA256 = cipher_ECDHE_ECDSA_WITH_AES_128_GCM_SHA256
cipher_ECDHE_ECDSA_WITH_AES_256_GCM_SHA384 :: Cipher
cipher_ECDHE_ECDSA_WITH_AES_256_GCM_SHA384 =
Cipher
{ cipherID = CipherID 0xC02C
{ cipherID = 0xC02C
, cipherName = "TLS_ECDHE_ECDSA_WITH_AES_256_GCM_SHA384"
, cipherBulk = bulk_aes256gcm
, cipherHash = SHA384
Expand All @@ -378,7 +378,7 @@ cipher_ECDHE_ECDSA_AES256GCM_SHA384 = cipher_ECDHE_ECDSA_WITH_AES_256_GCM_SHA384
cipher_ECDHE_RSA_WITH_AES_128_GCM_SHA256 :: Cipher
cipher_ECDHE_RSA_WITH_AES_128_GCM_SHA256 =
Cipher
{ cipherID = CipherID 0xC02F
{ cipherID = 0xC02F
, cipherName = "TLS_ECDHE_RSA_WITH_AES_128_GCM_SHA256"
, cipherBulk = bulk_aes128gcm
, cipherHash = SHA256
Expand All @@ -398,7 +398,7 @@ cipher_ECDHE_RSA_AES128GCM_SHA256 = cipher_ECDHE_RSA_WITH_AES_128_GCM_SHA256
cipher_ECDHE_RSA_WITH_AES_256_GCM_SHA384 :: Cipher
cipher_ECDHE_RSA_WITH_AES_256_GCM_SHA384 =
Cipher
{ cipherID = CipherID 0xC030
{ cipherID = 0xC030
, cipherName = "TLS_ECDHE_RSA_WITH_AES_256_GCM_SHA384"
, cipherBulk = bulk_aes256gcm
, cipherHash = SHA384
Expand All @@ -421,7 +421,7 @@ cipher_ECDHE_RSA_AES256GCM_SHA384 = cipher_ECDHE_RSA_WITH_AES_256_GCM_SHA384
cipher_ECDHE_ECDSA_WITH_AES_128_CCM :: Cipher
cipher_ECDHE_ECDSA_WITH_AES_128_CCM =
Cipher
{ cipherID = CipherID 0xC0AC
{ cipherID = 0xC0AC
, cipherName = "TLS_ECDHE_ECDSA_WITH_AES_128_CCM"
, cipherBulk = bulk_aes128ccm
, cipherHash = SHA256
Expand All @@ -441,7 +441,7 @@ cipher_ECDHE_ECDSA_AES128CCM_SHA256 = cipher_ECDHE_ECDSA_WITH_AES_128_CCM
cipher_ECDHE_ECDSA_WITH_AES_256_CCM :: Cipher
cipher_ECDHE_ECDSA_WITH_AES_256_CCM =
Cipher
{ cipherID = CipherID 0xC0AD
{ cipherID = 0xC0AD
, cipherName = "TLS_ECDHE_ECDSA_WITH_AES_256_CCM"
, cipherBulk = bulk_aes256ccm
, cipherHash = SHA256
Expand All @@ -461,7 +461,7 @@ cipher_ECDHE_ECDSA_AES256CCM_SHA256 = cipher_ECDHE_ECDSA_WITH_AES_256_CCM
cipher_ECDHE_ECDSA_WITH_AES_128_CCM_8 :: Cipher
cipher_ECDHE_ECDSA_WITH_AES_128_CCM_8 =
Cipher
{ cipherID = CipherID 0xC0AE
{ cipherID = 0xC0AE
, cipherName = "TLS_ECDHE_ECDSA_WITH_AES_128_CCM_8"
, cipherBulk = bulk_aes128ccm8
, cipherHash = SHA256
Expand All @@ -481,7 +481,7 @@ cipher_ECDHE_ECDSA_AES128CCM8_SHA256 = cipher_ECDHE_ECDSA_WITH_AES_128_CCM_8
cipher_ECDHE_ECDSA_WITH_AES_256_CCM_8 :: Cipher
cipher_ECDHE_ECDSA_WITH_AES_256_CCM_8 =
Cipher
{ cipherID = CipherID 0xC0AF
{ cipherID = 0xC0AF
, cipherName = "TLS_ECDHE_ECDSA_WITH_AES_256_CCM_8"
, cipherBulk = bulk_aes256ccm8
, cipherHash = SHA256
Expand All @@ -504,7 +504,7 @@ cipher_ECDHE_ECDSA_AES256CCM8_SHA256 = cipher_ECDHE_ECDSA_WITH_AES_256_CCM_8
cipher_ECDHE_RSA_WITH_CHACHA20_POLY1305_SHA256 :: Cipher
cipher_ECDHE_RSA_WITH_CHACHA20_POLY1305_SHA256 =
Cipher
{ cipherID = CipherID 0xCCA8
{ cipherID = 0xCCA8
, cipherName = "TLS_ECDHE_RSA_WITH_CHACHA20_POLY1305_SHA256"
, cipherBulk = bulk_chacha20poly1305
, cipherHash = SHA256
Expand All @@ -524,7 +524,7 @@ cipher_ECDHE_RSA_CHACHA20POLY1305_SHA256 = cipher_ECDHE_RSA_WITH_CHACHA20_POLY13
cipher_ECDHE_ECDSA_WITH_CHACHA20_POLY1305_SHA256 :: Cipher
cipher_ECDHE_ECDSA_WITH_CHACHA20_POLY1305_SHA256 =
Cipher
{ cipherID = CipherID 0xCCA9
{ cipherID = 0xCCA9
, cipherName = "TLS_ECDHE_ECDSA_WITH_CHACHA20_POLY1305_SHA256"
, cipherBulk = bulk_chacha20poly1305
, cipherHash = SHA256
Expand All @@ -544,7 +544,7 @@ cipher_ECDHE_ECDSA_CHACHA20POLY1305_SHA256 = cipher_ECDHE_ECDSA_WITH_CHACHA20_PO
cipher_DHE_RSA_WITH_CHACHA20_POLY1305_SHA256 :: Cipher
cipher_DHE_RSA_WITH_CHACHA20_POLY1305_SHA256 =
Cipher
{ cipherID = CipherID 0xCCAA
{ cipherID = 0xCCAA
, cipherName = "TLS_DHE_RSA_WITH_CHACHA20_POLY1305_SHA256"
, cipherBulk = bulk_chacha20poly1305
, cipherHash = SHA256
Expand Down
2 changes: 1 addition & 1 deletion tls/Network/TLS/Handshake/Client/ClientHello.hs
Original file line number Diff line number Diff line change
Expand Up @@ -86,7 +86,7 @@ sendClientHello' cparams ctx groups crand (pskInfo, rtt0info, rtt0) = do
hrr <- usingState_ ctx getTLS13HRR
unless hrr $ startHandshake ctx ver crand
usingState_ ctx $ setVersionIfUnset highestVer
let cipherIds = map cipherID ciphers
let cipherIds = map (CipherId . cipherID) ciphers
compIds = map compressionID compressions
mkClientHello exts = ClientHello ver crand compIds $ CH clientSession cipherIds exts
extensions0 <- catMaybes <$> getExtensions
Expand Down
3 changes: 2 additions & 1 deletion tls/Network/TLS/Handshake/Client/ServerHello.hs
Original file line number Diff line number Diff line change
Expand Up @@ -76,7 +76,8 @@ processServerHello cparams ctx (ServerHello rver serverRan serverSession cipher
-- find the compression and cipher methods that the server want to use.
clientSession <- tls13stSession <$> getTLS13State ctx
sentExts <- tls13stSentExtensions <$> getTLS13State ctx
cipherAlg <- case find ((==) cipher . cipherID) (supportedCiphers $ ctxSupported ctx) of
let eqCipher c = CipherId (cipherID c) == cipher
cipherAlg <- case find eqCipher (supportedCiphers $ ctxSupported ctx) of
Nothing -> throwCore $ Error_Protocol "server choose unknown cipher" IllegalParameter
Just alg -> return alg
compressAlg <- case find
Expand Down
2 changes: 1 addition & 1 deletion tls/Network/TLS/Handshake/Server/ClientHello.hs
Original file line number Diff line number Diff line change
Expand Up @@ -52,7 +52,7 @@ processClientHello sparams ctx clientHello@(ClientHello legacyVersion cran compr
-- TLS_FALLBACK_SCSV: {0x56, 0x00}
when
( supportedFallbackScsv (ctxSupported ctx)
&& (CipherID 0x5600 `elem` chCiphers)
&& (CipherId 0x5600 `elem` chCiphers)
&& legacyVersion < TLS12
)
$ throwCore
Expand Down
6 changes: 3 additions & 3 deletions tls/Network/TLS/Handshake/Server/ClientHello12.hs
Original file line number Diff line number Diff line change
Expand Up @@ -17,7 +17,7 @@ import Network.TLS.Imports
import Network.TLS.Parameters
import Network.TLS.State
import Network.TLS.Struct
import Network.TLS.Types (CipherID (..), Role (..))
import Network.TLS.Types (CipherId (..), Role (..))

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

Expand Down Expand Up @@ -51,7 +51,7 @@ checkSecureRenegotiation :: Context -> CH -> IO ()
checkSecureRenegotiation ctx CH{..} = do
-- RFC 5746: secure renegotiation
-- TLS_EMPTY_RENEGOTIATION_INFO_SCSV: {0x00, 0xFF}
when (CipherID 0xff `elem` chCiphers) $
when (CipherId 0xff `elem` chCiphers) $
usingState_ ctx $
setSecureRenegotiation True
case extensionLookup EID_SecureRenegotiation chExtensions of
Expand Down Expand Up @@ -82,7 +82,7 @@ credsTriple sparams CH{..} extraCreds

commonCiphers creds sigCreds = filter elemCipher availableCiphers
where
elemCipher c = cipherID c `elem` chCiphers
elemCipher c = CipherId (cipherID c) `elem` chCiphers
availableCiphers = getCiphers ciphers creds sigCreds

allCreds =
Expand Down
6 changes: 4 additions & 2 deletions tls/Network/TLS/Handshake/Server/ClientHello13.hs
Original file line number Diff line number Diff line change
Expand Up @@ -20,6 +20,7 @@ import Network.TLS.Parameters
import Network.TLS.State
import Network.TLS.Struct
import Network.TLS.Struct13
import Network.TLS.Types

-- TLS 1.3 or later
processClientHello13
Expand Down Expand Up @@ -65,7 +66,8 @@ processClientHello13 sparams ctx CH{..} = do
mshare <- findKeyShare keyShares serverGroups
return (mshare, (usedCipher, usedHash, rtt0))
where
ciphersFilteredVersion = filter ((`elem` chCiphers) . cipherID) serverCiphers
elemCipher c = CipherId (cipherID c) `elem` chCiphers
ciphersFilteredVersion = filter elemCipher serverCiphers
serverCiphers =
filter
(cipherAllowedForVersion TLS13)
Expand Down Expand Up @@ -113,7 +115,7 @@ sendHRR ctx (usedCipher, _, _) CH{..} = do
[ ExtensionRaw EID_KeyShare serverKeyShare
, ExtensionRaw EID_SupportedVersions selectedVersion
]
hrr = ServerHello13 hrrRandom chSession (cipherID usedCipher) extensions
hrr = ServerHello13 hrrRandom chSession (CipherId $ cipherID usedCipher) extensions
usingHState ctx $ setTLS13HandshakeMode HelloRetryRequest
runPacketFlight ctx $ do
loadPacket13 ctx $ Handshake13 [hrr]
Expand Down
6 changes: 3 additions & 3 deletions tls/Network/TLS/Handshake/Server/ServerHello12.hs
Original file line number Diff line number Diff line change
Expand Up @@ -78,7 +78,7 @@ recoverSessionData ctx CH{..} = do

validateSession
:: Context
-> [CipherID]
-> [CipherId]
-> Maybe HostName
-> Bool
-> Maybe SessionData
Expand All @@ -90,7 +90,7 @@ validateSession ctx ciphers sni ems m@(Just sd)
-- uses the same server_name than full handshake so the same
-- credentials (and thus ciphers) are available.
| TLS12 < sessionVersion sd = return Nothing -- fixme
| sessionCipher sd `notElem` ciphers =
| CipherId (sessionCipher sd) `notElem` ciphers =
throwCore $
Error_Protocol "new cipher is diffrent from the old one" IllegalParameter
| isJust sni && sessionClientSNI sd /= sni = do
Expand Down Expand Up @@ -298,7 +298,7 @@ makeServerHello sparams ctx usedCipher mcred chExts session = do
TLS12
srand
session
(cipherID usedCipher)
(CipherId (cipherID usedCipher))
(compressionID nullCompression)
shExts

Expand Down
2 changes: 1 addition & 1 deletion tls/Network/TLS/Handshake/Server/ServerHello13.hs
Original file line number Diff line number Diff line change
Expand Up @@ -233,7 +233,7 @@ sendServerHello13 sparams ctx clientKeyShare (usedCipher, usedHash, rtt0) CH{..}
toExtensionRaw (KeyShareServerHello keyShare)
: toExtensionRaw (SupportedVersionsServerHello TLS13)
: extensions
helo = ServerHello13 srand chSession (cipherID usedCipher) extensions'
helo = ServerHello13 srand chSession (CipherId (cipherID usedCipher)) extensions'
loadPacket13 ctx $ Handshake13 [helo]

sendCertAndVerify cred@(certChain, _) hashSig = do
Expand Down
8 changes: 4 additions & 4 deletions tls/Network/TLS/Packet.hs
Original file line number Diff line number Diff line change
Expand Up @@ -167,7 +167,7 @@ decodeClientHello = do
ver <- getBinaryVersion
random <- getClientRandom32
session <- getSession
ciphers <- map CipherID <$> getWords16
ciphers <- map CipherId <$> getWords16
compressions <- getWords8
r <- remaining
exts <-
Expand All @@ -184,7 +184,7 @@ decodeServerHello = do
ver <- getBinaryVersion
random <- getServerRandom32
session <- getSession
cipherid <- CipherID <$> getWord16
cipherid <- CipherId <$> getWord16
compressionid <- getWord8
r <- remaining
exts <-
Expand Down Expand Up @@ -319,15 +319,15 @@ encodeHandshake' (ClientHello version random compressionIDs CH{..}) = runPut $ d
putBinaryVersion version
putClientRandom32 random
putSession chSession
putWords16 $ map getCipherID chCiphers
putWords16 $ map fromCipherId chCiphers
putWords8 compressionIDs
putExtensions chExtensions
return ()
encodeHandshake' (ServerHello version random session cipherid compressionID exts) = runPut $ do
putBinaryVersion version
putServerRandom32 random
putSession session
putWord16 $ getCipherID cipherid
putWord16 $ fromCipherId cipherid
putWord8 compressionID
putExtensions exts
return ()
Expand Down
4 changes: 2 additions & 2 deletions tls/Network/TLS/Packet13.hs
Original file line number Diff line number Diff line change
Expand Up @@ -42,7 +42,7 @@ encodeHandshake13' (ServerHello13 random session cipherId exts) = runPut $ do
putBinaryVersion TLS12
putServerRandom32 random
putSession session
putWord16 $ getCipherID cipherId
putWord16 $ fromCipherId cipherId
putWord8 0 -- compressionID nullCompression
putExtensions exts
encodeHandshake13' (EncryptedExtensions13 exts) = runPut $ putExtensions exts
Expand Down Expand Up @@ -105,7 +105,7 @@ decodeServerHello13 = do
_ver <- getBinaryVersion
random <- getServerRandom32
session <- getSession
cipherid <- CipherID <$> getWord16
cipherid <- CipherId <$> getWord16
_comp <- getWord8
exts <- fromIntegral <$> getWord16 >>= getExtensions
return $ ServerHello13 random session cipherid exts
Expand Down
4 changes: 2 additions & 2 deletions tls/Network/TLS/Struct.hs
Original file line number Diff line number Diff line change
Expand Up @@ -392,7 +392,7 @@ instance Show ClientKeyXchgAlgorithmData where

data CH = CH
{ chSession :: Session
, chCiphers :: [CipherID]
, chCiphers :: [CipherId]
, chExtensions :: [ExtensionRaw]
}
deriving (Show, Eq)
Expand All @@ -411,7 +411,7 @@ data Handshake
Version
ServerRandom
Session
CipherID
CipherId
CompressionID
[ExtensionRaw]
| Certificate TLSCertificateChain
Expand Down
2 changes: 1 addition & 1 deletion tls/Network/TLS/Struct13.hs
Original file line number Diff line number Diff line change
Expand Up @@ -27,7 +27,7 @@ type TicketNonce = ByteString

-- fixme: convert Word32 to proper data type
data Handshake13
= ServerHello13 ServerRandom Session CipherID [ExtensionRaw]
= ServerHello13 ServerRandom Session CipherId [ExtensionRaw]
| NewSessionTicket13 Second Word32 TicketNonce SessionIDorTicket [ExtensionRaw]
| EndOfEarlyData13
| EncryptedExtensions13 [ExtensionRaw]
Expand Down
15 changes: 7 additions & 8 deletions tls/Network/TLS/Types/Cipher.hs
Original file line number Diff line number Diff line change
Expand Up @@ -4,7 +4,6 @@

module Network.TLS.Types.Cipher where

import Codec.Serialise
import Crypto.Cipher.Types (AuthTag)
import Data.IORef
import GHC.Generics
Expand All @@ -18,16 +17,18 @@ import Network.TLS.Types.Version
----------------------------------------------------------------

-- | Cipher identification
newtype CipherID = CipherID {getCipherID :: Word16}
type CipherID = Word16

newtype CipherId = CipherId {fromCipherId :: Word16}
deriving (Eq, Ord, Enum, Num, Integral, Real, Read, Generic)

instance Show CipherID where
show (CipherID 0x00FF) = "TLS_EMPTY_RENEGOTIATION_INFO_SCSV"
show (CipherID n) = case find eqID dict of
instance Show CipherId where
show (CipherId 0x00FF) = "TLS_EMPTY_RENEGOTIATION_INFO_SCSV"
show (CipherId n) = case find eqID dict of
Just c -> cipherName c
Nothing -> printf "0x%04X" n
where
eqID c = cipherID c == CipherID n
eqID c = cipherID c == n
dict = unsafePerformIO $ readIORef globalCipherDict

-- "ciphersuite" is designed extensible.
Expand Down Expand Up @@ -117,5 +118,3 @@ newtype BulkStream = BulkStream (ByteString -> (ByteString, BulkStream))

type BulkAEAD =
BulkNonce -> ByteString -> BulkAdditionalData -> (ByteString, AuthTag)

instance Serialise CipherID
Loading

0 comments on commit b247932

Please sign in to comment.