Skip to content

Commit

Permalink
Test remote commit bundles
Browse files Browse the repository at this point in the history
  • Loading branch information
pcapriotti committed Sep 15, 2022
1 parent e06f921 commit c51e32f
Show file tree
Hide file tree
Showing 2 changed files with 62 additions and 4 deletions.
64 changes: 60 additions & 4 deletions services/galley/test/integration/API/MLS.hs
Original file line number Diff line number Diff line change
@@ -1,5 +1,6 @@
{-# LANGUAGE RecordWildCards #-}
{-# OPTIONS_GHC -Wno-incomplete-uni-patterns #-}

-- This file is part of the Wire Server implementation.
--
-- Copyright (C) 2022 Wire Swiss GmbH <[email protected]>
Expand All @@ -16,7 +17,6 @@
--
-- You should have received a copy of the GNU Affero General Public License along
-- with this program. If not, see <https://www.gnu.org/licenses/>.
{-# OPTIONS_GHC -Wwarn #-}

module API.MLS (tests) where

Expand Down Expand Up @@ -103,6 +103,7 @@ tests s =
test s "add user with some non-MLS clients" testAddUserWithProteusClients,
test s "send a stale commit" testStaleCommit,
test s "add remote user to a conversation" testAddRemoteUser,
test s "add remote user with a commit bundle" testAddRemoteUserWithBundle,
test s "return error when commit is locked" testCommitLock,
test s "add user to a conversation with proposal + commit" testAddUserBareProposalCommit,
test s "post commit that references a unknown proposal" testUnknownProposalRefCommit,
Expand Down Expand Up @@ -296,10 +297,19 @@ testAddUserWithBundle = do
[alice, bob] <- createAndConnectUsers [Nothing, Nothing]

qcnv <- runMLSTest $ do
[alice1, bob1, bob2] <- traverse createMLSClient [alice, bob, bob]
traverse_ uploadNewKeyPackage [bob1, bob2]
(alice1 : bobClients) <- traverse createMLSClient [alice, bob, bob]
traverse_ uploadNewKeyPackage bobClients
(_, qcnv) <- setupMLSGroup alice1
events <- createAddCommit alice1 [bob] >>= sendAndConsumeCommitBundle
commit <- createAddCommit alice1 [bob]
welcome <- assertJust (mpWelcome commit)

events <- mlsBracket bobClients $ \wss -> do
events <- sendAndConsumeCommitBundle commit
for_ (zip bobClients wss) $ \(c, ws) ->
WS.assertMatch (5 # Second) ws $
wsAssertMLSWelcome (cidQualifiedUser c) welcome
pure events

event <- assertOne events
liftIO $ assertJoinEvent qcnv alice [bob] roleNameWireMember event
pure qcnv
Expand Down Expand Up @@ -585,6 +595,52 @@ testAddRemoteUser = do
event <- assertOne events
assertJoinEvent qcnv alice [bob] roleNameWireMember event

testAddRemoteUserWithBundle :: TestM ()
testAddRemoteUserWithBundle = do
users@[alice, bob] <- createAndConnectUsers [Nothing, Just "bob.example.com"]
(events, reqs, qcnv) <- runMLSTest $ do
[alice1, bob1] <- traverse createMLSClient users
(_, qcnv) <- setupMLSGroup alice1

let mock req = case frRPC req of
"on-conversation-updated" -> pure (Aeson.encode ())
"on-new-remote-conversation" -> pure (Aeson.encode EmptyResponse)
"get-mls-clients" ->
pure
. Aeson.encode
. Set.fromList
. map (flip ClientInfo True . ciClient)
$ [bob1]
"mls-welcome" -> pure (Aeson.encode EmptyResponse)
ms -> assertFailure ("unmocked endpoint called: " <> cs ms)

commit <- createAddCommit alice1 [bob]
(events, reqs) <-
withTempMockFederator' mock $
sendAndConsumeCommitBundle commit
pure (events, reqs, qcnv)

liftIO $ do
req <- assertOne $ filter ((== "on-conversation-updated") . frRPC) reqs
frTargetDomain req @?= qDomain bob
bdy <- case Aeson.eitherDecode (frBody req) of
Right b -> pure b
Left e -> assertFailure $ "Could not parse on-conversation-updated request body: " <> e
cuOrigUserId bdy @?= alice
cuConvId bdy @?= qUnqualified qcnv
cuAlreadyPresentUsers bdy @?= [qUnqualified bob]
cuAction bdy
@?= SomeConversationAction
SConversationJoinTag
ConversationJoin
{ cjUsers = pure bob,
cjRole = roleNameWireMember
}

liftIO $ do
event <- assertOne events
assertJoinEvent qcnv alice [bob] roleNameWireMember event

testCommitLock :: TestM ()
testCommitLock = do
users <- createAndConnectUsers (replicate 4 Nothing)
Expand Down
2 changes: 2 additions & 0 deletions services/galley/test/integration/API/MLS/Util.hs
Original file line number Diff line number Diff line change
Expand Up @@ -794,6 +794,8 @@ sendAndConsumeCommitBundle mp = do
. bytes (encodeMLS' bundle)
)
<!! const 201 === statusCode
consumeMessage mp
traverse_ consumeWelcome (mpWelcome mp)

-- increment epoch and add new clients
State.modify $ \mls ->
Expand Down

0 comments on commit c51e32f

Please sign in to comment.