Skip to content

Commit

Permalink
pretty print for CipherID
Browse files Browse the repository at this point in the history
  • Loading branch information
kazu-yamamoto committed Dec 19, 2024
1 parent 0114ab4 commit e228669
Show file tree
Hide file tree
Showing 8 changed files with 45 additions and 34 deletions.
38 changes: 19 additions & 19 deletions tls/Network/TLS/Extra/Cipher.hs
Original file line number Diff line number Diff line change
Expand Up @@ -73,7 +73,7 @@ import qualified Data.ByteString as B

import Data.Tuple (swap)
import Network.TLS.Cipher
import Network.TLS.Types (Version (..))
import Network.TLS.Types (CipherID (..), Version (..))

import Crypto.Cipher.AES
import qualified Crypto.Cipher.ChaChaPoly1305 as ChaChaPoly1305
Expand Down Expand Up @@ -435,7 +435,7 @@ bulk_aes128ccm8_13 = bulk_aes128ccm8{bulkIVSize = 12, bulkExplicitIV = 0}
cipher_DHE_RSA_WITH_AES_128_GCM_SHA256 :: Cipher
cipher_DHE_RSA_WITH_AES_128_GCM_SHA256 =
Cipher
{ cipherID = 0x009E
{ cipherID = CipherID 0x009E
, cipherName = "TLS_DHE_RSA_WITH_AES_128_GCM_SHA256"
, cipherBulk = bulk_aes128gcm
, cipherHash = SHA256
Expand All @@ -455,7 +455,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 = 0x009F
{ cipherID = CipherID 0x009F
, cipherName = "TLS_DHE_RSA_WITH_AES_256_GCM_SHA384"
, cipherBulk = bulk_aes256gcm
, cipherHash = SHA384
Expand All @@ -478,7 +478,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 = 0x1301
{ cipherID = CipherID 0x1301
, cipherName = "TLS_AES_128_GCM_SHA256"
, cipherBulk = bulk_aes128gcm_13
, cipherHash = SHA256
Expand All @@ -498,7 +498,7 @@ cipher_TLS13_AES128GCM_SHA256 = cipher13_AES_128_GCM_SHA256
cipher13_AES_256_GCM_SHA384 :: Cipher
cipher13_AES_256_GCM_SHA384 =
Cipher
{ cipherID = 0x1302
{ cipherID = CipherID 0x1302
, cipherName = "TLS_AES_256_GCM_SHA384"
, cipherBulk = bulk_aes256gcm_13
, cipherHash = SHA384
Expand All @@ -518,7 +518,7 @@ cipher_TLS13_AES256GCM_SHA384 = cipher13_AES_256_GCM_SHA384
cipher13_CHACHA20_POLY1305_SHA256 :: Cipher
cipher13_CHACHA20_POLY1305_SHA256 =
Cipher
{ cipherID = 0x1303
{ cipherID = CipherID 0x1303
, cipherName = "TLS_CHACHA20_POLY1305_SHA256"
, cipherBulk = bulk_chacha20poly1305
, cipherHash = SHA256
Expand All @@ -538,7 +538,7 @@ cipher_TLS13_CHACHA20POLY1305_SHA256 = cipher13_CHACHA20_POLY1305_SHA256
cipher13_AES_128_CCM_SHA256 :: Cipher
cipher13_AES_128_CCM_SHA256 =
Cipher
{ cipherID = 0x1304
{ cipherID = CipherID 0x1304
, cipherName = "TLS_AES_128_CCM_SHA256"
, cipherBulk = bulk_aes128ccm_13
, cipherHash = SHA256
Expand All @@ -558,7 +558,7 @@ cipher_TLS13_AES128CCM_SHA256 = cipher13_AES_128_CCM_SHA256
cipher13_TLS_AES_128_CCM_8_SHA256 :: Cipher
cipher13_TLS_AES_128_CCM_8_SHA256 =
Cipher
{ cipherID = 0x1305
{ cipherID = CipherID 0x1305
, cipherName = "TLS_AES_128_CCM_8_SHA256"
, cipherBulk = bulk_aes128ccm8_13
, cipherHash = SHA256
Expand All @@ -581,7 +581,7 @@ cipher_TLS13_AES128CCM8_SHA256 = cipher13_TLS_AES_128_CCM_8_SHA256
cipher_ECDHE_ECDSA_WITH_AES_128_GCM_SHA256 :: Cipher
cipher_ECDHE_ECDSA_WITH_AES_128_GCM_SHA256 =
Cipher
{ cipherID = 0xC02B
{ cipherID = CipherID 0xC02B
, cipherName = "TLS_ECDHE_ECDSA_WITH_AES_128_GCM_SHA256"
, cipherBulk = bulk_aes128gcm
, cipherHash = SHA256
Expand All @@ -601,7 +601,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 = 0xC02C
{ cipherID = CipherID 0xC02C
, cipherName = "TLS_ECDHE_ECDSA_WITH_AES_256_GCM_SHA384"
, cipherBulk = bulk_aes256gcm
, cipherHash = SHA384
Expand All @@ -621,7 +621,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 = 0xC02F
{ cipherID = CipherID 0xC02F
, cipherName = "TLS_ECDHE_RSA_WITH_AES_128_GCM_SHA256"
, cipherBulk = bulk_aes128gcm
, cipherHash = SHA256
Expand All @@ -641,7 +641,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 = 0xC030
{ cipherID = CipherID 0xC030
, cipherName = "TLS_ECDHE_RSA_WITH_AES_256_GCM_SHA384"
, cipherBulk = bulk_aes256gcm
, cipherHash = SHA384
Expand All @@ -664,7 +664,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 = 0xC0AC
{ cipherID = CipherID 0xC0AC
, cipherName = "TLS_ECDHE_ECDSA_WITH_AES_128_CCM"
, cipherBulk = bulk_aes128ccm
, cipherHash = SHA256
Expand All @@ -684,7 +684,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 = 0xC0AD
{ cipherID = CipherID 0xC0AD
, cipherName = "TLS_ECDHE_ECDSA_WITH_AES_256_CCM"
, cipherBulk = bulk_aes256ccm
, cipherHash = SHA256
Expand All @@ -704,7 +704,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 = 0xC0AE
{ cipherID = CipherID 0xC0AE
, cipherName = "TLS_ECDHE_ECDSA_WITH_AES_128_CCM_8"
, cipherBulk = bulk_aes128ccm8
, cipherHash = SHA256
Expand All @@ -724,7 +724,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 = 0xC0AF
{ cipherID = CipherID 0xC0AF
, cipherName = "TLS_ECDHE_ECDSA_WITH_AES_256_CCM_8"
, cipherBulk = bulk_aes256ccm8
, cipherHash = SHA256
Expand All @@ -747,7 +747,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 = 0xCCA8
{ cipherID = CipherID 0xCCA8
, cipherName = "TLS_ECDHE_RSA_WITH_CHACHA20_POLY1305_SHA256"
, cipherBulk = bulk_chacha20poly1305
, cipherHash = SHA256
Expand All @@ -767,7 +767,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 = 0xCCA9
{ cipherID = CipherID 0xCCA9
, cipherName = "TLS_ECDHE_ECDSA_WITH_CHACHA20_POLY1305_SHA256"
, cipherBulk = bulk_chacha20poly1305
, cipherHash = SHA256
Expand All @@ -787,7 +787,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 = 0xCCAA
{ cipherID = CipherID 0xCCAA
, cipherName = "TLS_DHE_RSA_WITH_CHACHA20_POLY1305_SHA256"
, cipherBulk = bulk_chacha20poly1305
, cipherHash = SHA256
Expand Down
3 changes: 2 additions & 1 deletion tls/Network/TLS/Handshake/Server/ClientHello.hs
Original file line number Diff line number Diff line change
Expand Up @@ -13,6 +13,7 @@ import Network.TLS.Measurement
import Network.TLS.Parameters
import Network.TLS.State
import Network.TLS.Struct
import Network.TLS.Types

processClientHello
:: ServerParams -> Context -> Handshake -> IO (Version, CH)
Expand Down Expand Up @@ -51,7 +52,7 @@ processClientHello sparams ctx clientHello@(ClientHello legacyVersion cran compr
-- TLS_FALLBACK_SCSV: {0x56, 0x00}
when
( supportedFallbackScsv (ctxSupported ctx)
&& (0x5600 `elem` chCiphers)
&& (CipherID 0x5600 `elem` chCiphers)
&& legacyVersion < TLS12
)
$ throwCore
Expand Down
4 changes: 2 additions & 2 deletions tls/Network/TLS/Handshake/Server/ClientHello12.hs
Original file line number Diff line number Diff line change
Expand Up @@ -18,7 +18,7 @@ import Network.TLS.Imports
import Network.TLS.Parameters
import Network.TLS.State
import Network.TLS.Struct
import Network.TLS.Types (Role (..))
import Network.TLS.Types (CipherID (..), Role (..))

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

Expand Down Expand Up @@ -49,7 +49,7 @@ checkSesecureRenegotiation :: Context -> CH -> IO ()
checkSesecureRenegotiation ctx CH{..} = do
-- RFC 5746: secure renegotiation
-- TLS_EMPTY_RENEGOTIATION_INFO_SCSV: {0x00, 0xFF}
when (0xff `elem` chCiphers) $
when (CipherID 0xff `elem` chCiphers) $
usingState_ ctx $
setSecureRenegotiation True
case extensionLookup EID_SecureRenegotiation chExtensions of
Expand Down
9 changes: 5 additions & 4 deletions tls/Network/TLS/Packet.hs
Original file line number Diff line number Diff line change
Expand Up @@ -72,6 +72,7 @@ import Network.TLS.Crypto
import Network.TLS.Imports
import Network.TLS.MAC
import Network.TLS.Struct
import Network.TLS.Types
import Network.TLS.Util.ASN1
import Network.TLS.Wire

Expand Down Expand Up @@ -165,7 +166,7 @@ decodeClientHello = do
ver <- getBinaryVersion
random <- getClientRandom32
session <- getSession
ciphers <- getWords16
ciphers <- map CipherID <$> getWords16
compressions <- getWords8
r <- remaining
exts <-
Expand All @@ -183,7 +184,7 @@ decodeServerHello = do
ver <- getBinaryVersion
random <- getServerRandom32
session <- getSession
cipherid <- getWord16
cipherid <- CipherID <$> getWord16
compressionid <- getWord8
r <- remaining
exts <-
Expand Down Expand Up @@ -318,15 +319,15 @@ encodeHandshake' (ClientHello version random compressionIDs CH{..}) = runPut $ d
putBinaryVersion version
putClientRandom32 random
putSession chSession
putWords16 chCiphers
putWords16 $ map getCipherID chCiphers
putWords8 compressionIDs
putExtensions chExtensions
return ()
encodeHandshake' (ServerHello version random session cipherid compressionID exts) = runPut $ do
putBinaryVersion version
putServerRandom32 random
putSession session
putWord16 cipherid
putWord16 $ getCipherID 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 cipherId
putWord16 $ getCipherID 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 <- getWord16
cipherid <- CipherID <$> getWord16
_comp <- getWord8
exts <- fromIntegral <$> getWord16 >>= getExtensions
return $ ServerHello13 random session cipherid exts
Expand Down
9 changes: 7 additions & 2 deletions tls/Network/TLS/Types.hs
Original file line number Diff line number Diff line change
Expand Up @@ -14,7 +14,7 @@ module Network.TLS.Types (
SessionFlag (..),
CertReqContext,
TLS13TicketInfo (..),
CipherID,
CipherID (..),
CompressionID,
Role (..),
invertRole,
Expand Down Expand Up @@ -46,6 +46,7 @@ import Network.Socket (HostName)
import Network.TLS.Crypto (Group, Hash (..), hash)
import Network.TLS.Imports
import Network.TLS.Util.Serialization
import Text.Printf

type Second = Word32
type Millisecond = Word64
Expand Down Expand Up @@ -129,7 +130,10 @@ data TLS13TicketInfo = TLS13TicketInfo
deriving (Show, Eq, Generic)

-- | Cipher identification
type CipherID = Word16
newtype CipherID = CipherID {getCipherID :: Word16} deriving (Eq, Generic)

instance Show CipherID where
show (CipherID n) = printf "0x%04X" n

-- | Compression identification
type CompressionID = Word8
Expand Down Expand Up @@ -199,6 +203,7 @@ bigNumFromInteger i = BigNum $ i2osp i

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

instance Serialise CipherID
instance Serialise Version
instance Serialise TLS13TicketInfo
instance Serialise SessionFlag
Expand Down
7 changes: 5 additions & 2 deletions tls/test/Arbitrary.hs
Original file line number Diff line number Diff line change
Expand Up @@ -70,6 +70,9 @@ instance Arbitrary CertificateType where
, CertificateType_ECDSA_Sign
]

instance Arbitrary CipherID where
arbitrary = CipherID <$> arbitrary

instance Arbitrary Handshake where
arbitrary =
oneof
Expand Down Expand Up @@ -127,8 +130,8 @@ instance Arbitrary Handshake13 where

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

arbitraryCiphersIDs :: Gen [Word16]
arbitraryCiphersIDs = choose (0, 200) >>= vector
arbitraryCiphersIDs :: Gen [CipherID]
arbitraryCiphersIDs = map CipherID <$> (choose (0, 200) >>= vector)

arbitraryCompressionIDs :: Gen [Word8]
arbitraryCompressionIDs = choose (0, 200) >>= vector
Expand Down
5 changes: 3 additions & 2 deletions tls/util/Common.hs
Original file line number Diff line number Diff line change
Expand Up @@ -23,6 +23,7 @@ import Data.X509.CertificateStore
import Network.TLS hiding (HostName)
import Network.TLS.Extra.Cipher
import Network.TLS.Extra.FFDHE
import Network.TLS.Internal
import Numeric (showHex)
import System.Exit
import System.X509
Expand Down Expand Up @@ -67,7 +68,7 @@ readNumber s
readCiphers :: String -> Maybe [CipherID]
readCiphers s =
case lookup s namedCiphersuites of
Nothing -> (: []) `fmap` readNumber s
Nothing -> (: []) `fmap` (CipherID <$> readNumber s)
just -> just

readDHParams :: String -> IO (Maybe DHParams)
Expand All @@ -91,7 +92,7 @@ printCiphers = do
++ " = "
++ pad 5 (show $ cipherID c)
++ " 0x"
++ showHex (cipherID c) ""
++ showHex (getCipherID (cipherID c)) ""
)
putStrLn ""
putStrLn "Ciphersuites"
Expand Down

0 comments on commit e228669

Please sign in to comment.