Skip to content

Commit

Permalink
configure ratchet version via agent config, test matrix
Browse files Browse the repository at this point in the history
  • Loading branch information
epoberezkin committed Oct 20, 2022
1 parent b4d1c3c commit b87d5d0
Show file tree
Hide file tree
Showing 6 changed files with 68 additions and 39 deletions.
36 changes: 17 additions & 19 deletions src/Simplex/Messaging/Agent.hs
Original file line number Diff line number Diff line change
Expand Up @@ -403,28 +403,26 @@ newConn c connId asyncMode enableNtfs cMode =

newConnSrv :: AgentMonad m => AgentClient -> ConnId -> Bool -> Bool -> SConnectionMode c -> SMPServer -> m (ConnId, ConnectionRequestUri c)
newConnSrv c connId asyncMode enableNtfs cMode srv = do
clientVRange <- asks $ smpClientVRange . config
(rq, qUri) <- newRcvQueue c srv clientVRange
connId' <- setUpConn asyncMode rq
AgentConfig {smpClientVRange, smpAgentVRange, e2eEncryptVRange} <- asks config
(rq, qUri) <- newRcvQueue c srv smpClientVRange
connId' <- setUpConn asyncMode rq $ maxVersion smpAgentVRange
addSubscription c rq connId'
when enableNtfs $ do
ns <- asks ntfSupervisor
atomically $ sendNtfSubCommand ns (connId', NSCCreate)
aVRange <- asks $ smpAgentVRange . config
let crData = ConnReqUriData simplexChat aVRange [qUri]
let crData = ConnReqUriData simplexChat smpAgentVRange [qUri]
case cMode of
SCMContact -> pure (connId', CRContactUri crData)
SCMInvitation -> do
(pk1, pk2, e2eRcvParams) <- liftIO $ CR.generateE2EParams CR.e2eEncryptVersion
(pk1, pk2, e2eRcvParams) <- liftIO . CR.generateE2EParams $ maxVersion e2eEncryptVRange
withStore' c $ \db -> createRatchetX3dhKeys db connId' pk1 pk2
pure (connId', CRInvitationUri crData $ toVersionRangeT e2eRcvParams CR.e2eEncryptVRange)
pure (connId', CRInvitationUri crData $ toVersionRangeT e2eRcvParams e2eEncryptVRange)
where
setUpConn True rq = do
setUpConn True rq _ = do
withStore c $ \db -> updateNewConnRcv db connId rq
pure connId
setUpConn False rq = do
setUpConn False rq connAgentVersion = do
g <- asks idsDrg
connAgentVersion <- asks $ maxVersion . smpAgentVRange . config
let cData = ConnData {connId, connAgentVersion, enableNtfs, duplexHandshake = Nothing} -- connection mode is determined by the accepting agent
withStore c $ \db -> createRcvConn db g cData rq cMode

Expand All @@ -438,16 +436,15 @@ joinConn c connId asyncMode enableNtfs cReq cInfo = do

joinConnSrv :: AgentMonad m => AgentClient -> ConnId -> Bool -> Bool -> ConnectionRequestUri c -> ConnInfo -> SMPServer -> m ConnId
joinConnSrv c connId asyncMode enableNtfs (CRInvitationUri (ConnReqUriData _ agentVRange (qUri :| _)) e2eRcvParamsUri) cInfo srv = do
aVRange <- asks $ smpAgentVRange . config
clientVRange <- asks $ smpClientVRange . config
case ( qUri `compatibleVersion` clientVRange,
e2eRcvParamsUri `compatibleVersion` CR.e2eEncryptVRange,
agentVRange `compatibleVersion` aVRange
AgentConfig {smpClientVRange, smpAgentVRange, e2eEncryptVRange} <- asks config
case ( qUri `compatibleVersion` smpClientVRange,
e2eRcvParamsUri `compatibleVersion` e2eEncryptVRange,
agentVRange `compatibleVersion` smpAgentVRange
) of
(Just qInfo, Just (Compatible e2eRcvParams@(CR.E2ERatchetParams _ _ rcDHRr)), Just aVersion@(Compatible connAgentVersion)) -> do
(pk1, pk2, e2eSndParams) <- liftIO . CR.generateE2EParams $ version e2eRcvParams
(_, rcDHRs) <- liftIO C.generateKeyPair'
let rc = CR.initSndRatchet rcDHRr rcDHRs $ CR.x3dhSnd pk1 pk2 e2eRcvParams
let rc = CR.initSndRatchet e2eEncryptVRange rcDHRr rcDHRs $ CR.x3dhSnd pk1 pk2 e2eRcvParams
sq <- newSndQueue qInfo
let duplexHS = connAgentVersion /= 1
cData = ConnData {connId, connAgentVersion, enableNtfs, duplexHandshake = Just duplexHS}
Expand Down Expand Up @@ -1397,16 +1394,17 @@ processSMPTransmission c@AgentClient {smpClients, subQ} (srv, v, sessId, rId, cm
smpConfirmation :: C.APublicVerifyKey -> C.PublicKeyX25519 -> Maybe (CR.E2ERatchetParams 'C.X448) -> ByteString -> Version -> Version -> m ()
smpConfirmation senderKey e2ePubKey e2eEncryption encConnInfo smpClientVersion agentVersion = do
logServer "<--" c srv rId "MSG <CONF>"
AgentConfig {smpAgentVRange, smpClientVRange} <- asks config
AgentConfig {smpClientVRange, smpAgentVRange, e2eEncryptVRange} <- asks config
unless
(agentVersion `isCompatible` smpAgentVRange && smpClientVersion `isCompatible` smpClientVRange)
(throwError $ AGENT A_VERSION)
case status of
New -> case (conn, e2eEncryption) of
-- party initiating connection
(RcvConnection {}, Just e2eSndParams) -> do
(RcvConnection {}, Just e2eSndParams@(CR.E2ERatchetParams e2eVersion _ _)) -> do
unless (e2eVersion `isCompatible` e2eEncryptVRange) (throwError $ AGENT A_VERSION)
(pk1, rcDHRs) <- withStore c (`getRatchetX3dhKeys` connId)
let rc = CR.initRcvRatchet rcDHRs $ CR.x3dhRcv pk1 rcDHRs e2eSndParams
let rc = CR.initRcvRatchet e2eEncryptVRange rcDHRs $ CR.x3dhRcv pk1 rcDHRs e2eSndParams
(agentMsgBody_, rc', skipped) <- liftError cryptoError $ CR.rcDecrypt rc M.empty encConnInfo
case (agentMsgBody_, skipped) of
(Right agentMsgBody, CR.SMDNoChange) ->
Expand Down
3 changes: 3 additions & 0 deletions src/Simplex/Messaging/Agent/Env/SQLite.hs
Original file line number Diff line number Diff line change
Expand Up @@ -43,6 +43,7 @@ import qualified Simplex.Messaging.Agent.Store.SQLite.Migrations as Migrations
import Simplex.Messaging.Client
import Simplex.Messaging.Client.Agent ()
import qualified Simplex.Messaging.Crypto as C
import Simplex.Messaging.Crypto.Ratchet (supportedE2EEncryptVRange)
import Simplex.Messaging.Notifications.Types
import Simplex.Messaging.Protocol (NtfServer, supportedSMPClientVRange)
import Simplex.Messaging.TMap (TMap)
Expand Down Expand Up @@ -93,6 +94,7 @@ data AgentConfig = AgentConfig
caCertificateFile :: FilePath,
privateKeyFile :: FilePath,
certificateFile :: FilePath,
e2eEncryptVRange :: VersionRange,
smpAgentVRange :: VersionRange,
smpClientVRange :: VersionRange
}
Expand Down Expand Up @@ -138,6 +140,7 @@ defaultAgentConfig =
caCertificateFile = "/etc/opt/simplex-agent/ca.crt",
privateKeyFile = "/etc/opt/simplex-agent/agent.key",
certificateFile = "/etc/opt/simplex-agent/agent.crt",
e2eEncryptVRange = supportedE2EEncryptVRange,
smpAgentVRange = supportedSMPAgentVRange,
smpClientVRange = supportedSMPClientVRange
}
Expand Down
20 changes: 10 additions & 10 deletions src/Simplex/Messaging/Crypto/Ratchet.hs
Original file line number Diff line number Diff line change
Expand Up @@ -41,11 +41,11 @@ import Simplex.Messaging.Parsers (blobFieldDecoder, parseE, parseE')
import Simplex.Messaging.Util (tryE)
import Simplex.Messaging.Version

e2eEncryptVersion :: Version
e2eEncryptVersion = 2
currentE2EEncryptVersion :: Version
currentE2EEncryptVersion = 2

e2eEncryptVRange :: VersionRange
e2eEncryptVRange = mkVersionRange 1 e2eEncryptVersion
supportedE2EEncryptVRange :: VersionRange
supportedE2EEncryptVRange = mkVersionRange 1 currentE2EEncryptVersion

data E2ERatchetParams (a :: Algorithm)
= E2ERatchetParams Version (PublicKey a) (PublicKey a)
Expand Down Expand Up @@ -216,12 +216,12 @@ instance FromField MessageKey where fromField = blobFieldDecoder smpDecode
-- Please note that sPKey is not stored, and its public part together with random salt
-- is sent to the recipient.
initSndRatchet ::
forall a. (AlgorithmI a, DhAlgorithm a) => PublicKey a -> PrivateKey a -> RatchetInitParams -> Ratchet a
initSndRatchet rcDHRr rcDHRs RatchetInitParams {assocData, ratchetKey, sndHK, rcvNextHK} = do
forall a. (AlgorithmI a, DhAlgorithm a) => VersionRange -> PublicKey a -> PrivateKey a -> RatchetInitParams -> Ratchet a
initSndRatchet rcVersion rcDHRr rcDHRs RatchetInitParams {assocData, ratchetKey, sndHK, rcvNextHK} = do
-- state.RK, state.CKs, state.NHKs = KDF_RK_HE(SK, DH(state.DHRs, state.DHRr))
let (rcRK, rcCKs, rcNHKs) = rootKdf ratchetKey rcDHRr rcDHRs
in Ratchet
{ rcVersion = e2eEncryptVRange,
{ rcVersion,
rcAD = assocData,
rcDHRs,
rcRK,
Expand All @@ -239,10 +239,10 @@ initSndRatchet rcDHRr rcDHRs RatchetInitParams {assocData, ratchetKey, sndHK, rc
-- Please note that the public part of rcDHRs was sent to the sender
-- as part of the connection request and random salt was received from the sender.
initRcvRatchet ::
forall a. (AlgorithmI a, DhAlgorithm a) => PrivateKey a -> RatchetInitParams -> Ratchet a
initRcvRatchet rcDHRs RatchetInitParams {assocData, ratchetKey, sndHK, rcvNextHK} =
forall a. (AlgorithmI a, DhAlgorithm a) => VersionRange -> PrivateKey a -> RatchetInitParams -> Ratchet a
initRcvRatchet rcVersion rcDHRs RatchetInitParams {assocData, ratchetKey, sndHK, rcvNextHK} =
Ratchet
{ rcVersion = e2eEncryptVRange,
{ rcVersion,
rcAD = assocData,
rcDHRs,
rcRK = ratchetKey,
Expand Down
2 changes: 1 addition & 1 deletion tests/AgentTests/ConnectionRequestTests.hs
Original file line number Diff line number Diff line change
Expand Up @@ -62,7 +62,7 @@ testE2ERatchetParams :: E2ERatchetParamsUri 'C.X448
testE2ERatchetParams = E2ERatchetParamsUri (mkVersionRange 1 1) testDhPubKey testDhPubKey

testE2ERatchetParams12 :: E2ERatchetParamsUri 'C.X448
testE2ERatchetParams12 = E2ERatchetParamsUri e2eEncryptVRange testDhPubKey testDhPubKey
testE2ERatchetParams12 = E2ERatchetParamsUri supportedE2EEncryptVRange testDhPubKey testDhPubKey

connectionRequest :: AConnectionRequestUri
connectionRequest =
Expand Down
25 changes: 18 additions & 7 deletions tests/AgentTests/DoubleRatchetTests.hs
Original file line number Diff line number Diff line change
Expand Up @@ -46,6 +46,9 @@ doubleRatchetTests = do
it "should agree the same ratchet parameters" $ do
testX3dh C.SX25519
testX3dh C.SX448
it "should agree the same ratchet parameters with version 1" $ do
testX3dhV1 C.SX25519
testX3dhV1 C.SX448

paddedMsgLen :: Int
paddedMsgLen = 100
Expand All @@ -56,7 +59,7 @@ fullMsgLen = 1 + fullHeaderLen + C.authTagSize + paddedMsgLen
testMessageHeader :: Expectation
testMessageHeader = do
(k, _) <- C.generateKeyPair' @X25519
let hdr = MsgHeader {msgMaxVersion = e2eEncryptVersion, msgDHRs = k, msgPN = 0, msgNs = 0}
let hdr = MsgHeader {msgMaxVersion = currentE2EEncryptVersion, msgDHRs = k, msgPN = 0, msgNs = 0}
parseAll (smpP @(MsgHeader 'X25519)) (smpEncode hdr) `shouldBe` Right hdr

pattern Decrypted :: ByteString -> Either CryptoError (Either CryptoError ByteString)
Expand Down Expand Up @@ -168,8 +171,16 @@ testEncodeDecode x = do

testX3dh :: forall a. (AlgorithmI a, DhAlgorithm a) => C.SAlgorithm a -> IO ()
testX3dh _ = do
(pkBob1, pkBob2, e2eBob) <- generateE2EParams @a e2eEncryptVersion
(pkAlice1, pkAlice2, e2eAlice) <- generateE2EParams @a e2eEncryptVersion
(pkBob1, pkBob2, e2eBob) <- generateE2EParams @a currentE2EEncryptVersion
(pkAlice1, pkAlice2, e2eAlice) <- generateE2EParams @a currentE2EEncryptVersion
let paramsBob = x3dhSnd pkBob1 pkBob2 e2eAlice
paramsAlice = x3dhRcv pkAlice1 pkAlice2 e2eBob
paramsAlice `shouldBe` paramsBob

testX3dhV1 :: forall a. (AlgorithmI a, DhAlgorithm a) => C.SAlgorithm a -> IO ()
testX3dhV1 _ = do
(pkBob1, pkBob2, e2eBob) <- generateE2EParams @a 1
(pkAlice1, pkAlice2, e2eAlice) <- generateE2EParams @a 1
let paramsBob = x3dhSnd pkBob1 pkBob2 e2eAlice
paramsAlice = x3dhRcv pkAlice1 pkAlice2 e2eBob
paramsAlice `shouldBe` paramsBob
Expand All @@ -189,13 +200,13 @@ withRatchets test = do

initRatchets :: (AlgorithmI a, DhAlgorithm a) => IO (Ratchet a, Ratchet a)
initRatchets = do
(pkBob1, pkBob2, e2eBob) <- generateE2EParams e2eEncryptVersion
(pkAlice1, pkAlice2, e2eAlice) <- generateE2EParams e2eEncryptVersion
(pkBob1, pkBob2, e2eBob) <- generateE2EParams currentE2EEncryptVersion
(pkAlice1, pkAlice2, e2eAlice) <- generateE2EParams currentE2EEncryptVersion
let paramsBob = x3dhSnd pkBob1 pkBob2 e2eAlice
paramsAlice = x3dhRcv pkAlice1 pkAlice2 e2eBob
(_, pkBob3) <- C.generateKeyPair'
let bob = initSndRatchet (C.publicKey pkAlice2) pkBob3 paramsBob
alice = initRcvRatchet pkAlice2 paramsAlice
let bob = initSndRatchet supportedE2EEncryptVRange (C.publicKey pkAlice2) pkBob3 paramsBob
alice = initRcvRatchet supportedE2EEncryptVRange pkAlice2 paramsAlice
pure (alice, bob)

encrypt_ :: AlgorithmI a => (Ratchet a, SkippedMsgKeys) -> ByteString -> IO (Either CryptoError (ByteString, Ratchet a, SkippedMsgDiff))
Expand Down
21 changes: 19 additions & 2 deletions tests/AgentTests/FunctionalAPITests.hs
Original file line number Diff line number Diff line change
Expand Up @@ -58,17 +58,27 @@ pattern Msg :: MsgBody -> ACommand 'Agent
pattern Msg msgBody <- MSG MsgMeta {integrity = MsgOk} _ msgBody

smpCfgV1 :: ProtocolClientConfig
smpCfgV1 = (smpCfg agentCfg) {smpServerVRange = mkVersionRange 1 1}
smpCfgV1 = (smpCfg agentCfg) {smpServerVRange = vr11}

agentCfgV1 :: AgentConfig
agentCfgV1 = agentCfg {smpAgentVRange = mkVersionRange 1 1, smpClientVRange = mkVersionRange 1 1, smpCfg = smpCfgV1}
agentCfgV1 = agentCfg {smpAgentVRange = vr11, smpClientVRange = vr11, e2eEncryptVRange = vr11, smpCfg = smpCfgV1}

agentCfgRatchetV1 :: AgentConfig
agentCfgRatchetV1 = agentCfg {e2eEncryptVRange = vr11}

vr11 :: VersionRange
vr11 = mkVersionRange 1 1

functionalAPITests :: ATransport -> Spec
functionalAPITests t = do
describe "Establishing duplex connection" $
testMatrix2 t runAgentClientTest
describe "Establishing duplex connection v2, different Ratchet versions" $
testRatchetMatrix2 t runAgentClientTest
describe "Establish duplex connection via contact address" $
testMatrix2 t runAgentClientContactTest
describe "Establish duplex connection via contact address v2, different Ratchet versions" $
testRatchetMatrix2 t runAgentClientContactTest
describe "Establishing connection asynchronously" $ do
it "should connect with initiating client going offline" $
withSmpServer t testAsyncInitiatingOffline
Expand Down Expand Up @@ -113,6 +123,13 @@ testMatrix2 t runTest = do
it "v1 to v2" $ withSmpServer t $ runTestCfg2 agentCfgV1 agentCfg 4 runTest
it "v2 to v1" $ withSmpServer t $ runTestCfg2 agentCfg agentCfgV1 4 runTest

testRatchetMatrix2 :: ATransport -> (AgentClient -> AgentClient -> AgentMsgId -> IO ()) -> Spec
testRatchetMatrix2 t runTest = do
it "ratchet v2" $ withSmpServer t $ runTestCfg2 agentCfg agentCfg 3 runTest
it "ratchet v1" $ withSmpServer t $ runTestCfg2 agentCfgRatchetV1 agentCfgRatchetV1 3 runTest
it "ratchets v1 to v2" $ withSmpServer t $ runTestCfg2 agentCfgRatchetV1 agentCfg 3 runTest
it "ratchets v2 to v1" $ withSmpServer t $ runTestCfg2 agentCfg agentCfgRatchetV1 3 runTest

runTestCfg2 :: AgentConfig -> AgentConfig -> AgentMsgId -> (AgentClient -> AgentClient -> AgentMsgId -> IO ()) -> IO ()
runTestCfg2 aliceCfg bobCfg baseMsgId runTest = do
alice <- getSMPAgentClient aliceCfg initAgentServers
Expand Down

0 comments on commit b87d5d0

Please sign in to comment.