Skip to content

Commit

Permalink
first step to redesign session ticket.
Browse files Browse the repository at this point in the history
  • Loading branch information
kazu-yamamoto committed May 29, 2017
1 parent ee1959f commit 43e34d0
Show file tree
Hide file tree
Showing 2 changed files with 9 additions and 22 deletions.
20 changes: 5 additions & 15 deletions core/Network/TLS/Handshake/Common13.hs
Original file line number Diff line number Diff line change
Expand Up @@ -4,8 +4,6 @@ module Network.TLS.Handshake.Common13 where

import Control.Applicative
import Control.Monad
import qualified Crypto.PubKey.RSA.PKCS15 as R
import qualified Crypto.PubKey.RSA.Types as R
import qualified Data.ByteArray as BA
import Data.ByteString (ByteString)
import qualified Data.ByteString as B
Expand Down Expand Up @@ -121,19 +119,11 @@ sign ctx hs privKey target = usingState_ ctx $ do

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

encryptSessionData :: PubKey -> SessionData -> IO (Either R.Error SessionLabel)
encryptSessionData (PubKeyRSA rsaPub) sdata = R.encrypt rsaPub $ encodeSessionData sdata
encryptSessionData _ _ = error "encryptSessionData"

decryptSessionData :: PrivKey -> SessionLabel -> IO (Either R.Error SessionData)
decryptSessionData (PrivKeyRSA rsaPriv) ticket = do
ebs <- R.decryptSafer rsaPriv ticket
case ebs of
Right bs -> case decodeSessionData bs of
Just sdata -> return $ Right sdata
Nothing -> return $ Left R.MessageNotRecognized -- fixme
Left e -> return $ Left e
decryptSessionData _ _ = error "decryptSessionData"
encryptSessionData :: SessionData -> Maybe SessionLabel
encryptSessionData sdata = Just $ encodeSessionData sdata

decryptSessionData :: SessionLabel -> Maybe SessionData
decryptSessionData ticket = decodeSessionData ticket

encodeSessionData :: SessionData -> ByteString
encodeSessionData (SessionData ver cid comp msni rsecret mgroup mlife) = runPut $ do
Expand Down
11 changes: 4 additions & 7 deletions core/Network/TLS/Handshake/Server.hs
Original file line number Diff line number Diff line change
Expand Up @@ -56,8 +56,6 @@ import Network.TLS.Handshake.State13
import Network.TLS.KeySchedule
import Network.TLS.Handshake.Common13

import qualified Data.X509 as X

-- Put the server context in handshake mode.
--
-- Expect to receive as first packet a client hello handshake message
Expand Down Expand Up @@ -679,9 +677,9 @@ doHandshake13 sparams (certChain, privKey) ctx chosenVersion usedCipher exts use
choosePSK = case extensionLookup extensionID_PreSharedKey exts >>= extensionDecode MsgTClientHello of
Just (PreSharedKeyClientHello (PskIdentity ticket obfAge:_) bnds@(bnd:_)) -> do
let len = sum (map (\x -> B.length x + 1) bnds) + 2
esdata <- decryptSessionData privKey ticket
esdata = decryptSessionData ticket
case esdata of
Right sdata -> do
Just sdata -> do
let Just tinfo = sessionTicketInfo sdata
age = revealObfuscatedAge obfAge tinfo
tripTime <- getTripTime tinfo
Expand All @@ -692,7 +690,7 @@ doHandshake13 sparams (certChain, privKey) ctx chosenVersion usedCipher exts use
return (psk, Just (bnd,0::Int,len))
else
throwCore $ Error_Protocol ("PSK validation failed", True, HandshakeFailure)
Left _ -> return (zero, Nothing)
_ -> return (zero, Nothing)
_ -> return (zero, Nothing)

rtt0 = case extensionLookup extensionID_EarlyData exts >>= extensionDecode MsgTClientHello of
Expand Down Expand Up @@ -761,11 +759,10 @@ doHandshake13 sparams (certChain, privKey) ctx chosenVersion usedCipher exts use
serverName <- usingState_ ctx getClientSNI
tinfo <- createTLS13TicketInfo life (Left ctx)
let sdata = SessionData chosenVersion (cipherID usedCipher) 0 serverName resumptionSecret (Just grp) (Just tinfo)
Right ticket <- encryptSessionData pubKey sdata -- fixme
Just ticket = encryptSessionData sdata -- fixme
return (ticket, ageAdd tinfo)
where
grp = keyShareEntryGroup clientKeyShare
pubKey = X.certPubKey $ X.signedObject $ X.getSigned $ getCertificateChainLeaf certChain
createNewSessionTicket life add ticket = NewSessionTicket13 life add ticket extensions
where
tedi = extensionEncode $ TicketEarlyDataInfo 2048 -- 2 KiB: fixme hard coding
Expand Down

0 comments on commit 43e34d0

Please sign in to comment.