{-# LANGUAGE PatternGuards #-}
module Network.TLS.Handshake.Random (
serverRandom
, clientRandom
, hrrRandom
, isHelloRetryRequest
, isDowngraded
) where
import qualified Data.ByteString as B
import Network.TLS.Context.Internal
import Network.TLS.Struct
serverRandom :: Context -> Version -> [Version] -> IO ServerRandom
serverRandom :: Context -> Version -> [Version] -> IO ServerRandom
serverRandom Context
ctx Version
chosenVer [Version]
suppVers
| Version
TLS13 forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [Version]
suppVers = case Version
chosenVer of
Version
TLS13 -> ByteString -> ServerRandom
ServerRandom forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Context -> Int -> IO ByteString
getStateRNG Context
ctx Int
32
Version
TLS12 -> ByteString -> ServerRandom
ServerRandom forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ByteString -> IO ByteString
genServRand ByteString
suffix12
Version
_ -> ByteString -> ServerRandom
ServerRandom forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ByteString -> IO ByteString
genServRand ByteString
suffix11
| Version
TLS12 forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [Version]
suppVers = case Version
chosenVer of
Version
TLS13 -> ByteString -> ServerRandom
ServerRandom forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Context -> Int -> IO ByteString
getStateRNG Context
ctx Int
32
Version
TLS12 -> ByteString -> ServerRandom
ServerRandom forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Context -> Int -> IO ByteString
getStateRNG Context
ctx Int
32
Version
_ -> ByteString -> ServerRandom
ServerRandom forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ByteString -> IO ByteString
genServRand ByteString
suffix11
| Bool
otherwise = ByteString -> ServerRandom
ServerRandom forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Context -> Int -> IO ByteString
getStateRNG Context
ctx Int
32
where
genServRand :: ByteString -> IO ByteString
genServRand ByteString
suff = do
ByteString
pref <- Context -> Int -> IO ByteString
getStateRNG Context
ctx Int
24
forall (m :: * -> *) a. Monad m => a -> m a
return (ByteString
pref ByteString -> ByteString -> ByteString
`B.append` ByteString
suff)
isDowngraded :: Version -> [Version] -> ServerRandom -> Bool
isDowngraded :: Version -> [Version] -> ServerRandom -> Bool
isDowngraded Version
ver [Version]
suppVers (ServerRandom ByteString
sr)
| Version
ver forall a. Ord a => a -> a -> Bool
<= Version
TLS12
, Version
TLS13 forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [Version]
suppVers = ByteString
suffix12 ByteString -> ByteString -> Bool
`B.isSuffixOf` ByteString
sr
Bool -> Bool -> Bool
|| ByteString
suffix11 ByteString -> ByteString -> Bool
`B.isSuffixOf` ByteString
sr
| Version
ver forall a. Ord a => a -> a -> Bool
<= Version
TLS11
, Version
TLS12 forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [Version]
suppVers = ByteString
suffix11 ByteString -> ByteString -> Bool
`B.isSuffixOf` ByteString
sr
| Bool
otherwise = Bool
False
suffix12 :: B.ByteString
suffix12 :: ByteString
suffix12 = [Word8] -> ByteString
B.pack [Word8
0x44, Word8
0x4F, Word8
0x57, Word8
0x4E, Word8
0x47, Word8
0x52, Word8
0x44, Word8
0x01]
suffix11 :: B.ByteString
suffix11 :: ByteString
suffix11 = [Word8] -> ByteString
B.pack [Word8
0x44, Word8
0x4F, Word8
0x57, Word8
0x4E, Word8
0x47, Word8
0x52, Word8
0x44, Word8
0x00]
clientRandom :: Context -> IO ClientRandom
clientRandom :: Context -> IO ClientRandom
clientRandom Context
ctx = ByteString -> ClientRandom
ClientRandom forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Context -> Int -> IO ByteString
getStateRNG Context
ctx Int
32
hrrRandom :: ServerRandom
hrrRandom :: ServerRandom
hrrRandom = ByteString -> ServerRandom
ServerRandom forall a b. (a -> b) -> a -> b
$ [Word8] -> ByteString
B.pack [
Word8
0xCF, Word8
0x21, Word8
0xAD, Word8
0x74, Word8
0xE5, Word8
0x9A, Word8
0x61, Word8
0x11
, Word8
0xBE, Word8
0x1D, Word8
0x8C, Word8
0x02, Word8
0x1E, Word8
0x65, Word8
0xB8, Word8
0x91
, Word8
0xC2, Word8
0xA2, Word8
0x11, Word8
0x16, Word8
0x7A, Word8
0xBB, Word8
0x8C, Word8
0x5E
, Word8
0x07, Word8
0x9E, Word8
0x09, Word8
0xE2, Word8
0xC8, Word8
0xA8, Word8
0x33, Word8
0x9C
]
isHelloRetryRequest :: ServerRandom -> Bool
isHelloRetryRequest :: ServerRandom -> Bool
isHelloRetryRequest = (forall a. Eq a => a -> a -> Bool
== ServerRandom
hrrRandom)