Skip to content

Commit 9c5ebd9

Browse files
committed
delete/adjust tests.
1 parent 662cfba commit 9c5ebd9

File tree

2 files changed

+2
-168
lines changed

2 files changed

+2
-168
lines changed

services/galley/test/integration/API.hs

Lines changed: 1 addition & 55 deletions
Original file line numberDiff line numberDiff line change
@@ -1,5 +1,6 @@
11
{-# LANGUAGE OverloadedRecordDot #-}
22
{-# OPTIONS_GHC -Wno-incomplete-uni-patterns #-}
3+
{-# OPTIONS_GHC -Wno-unused-local-binds #-}
34

45
-- This file is part of the Wire Server implementation.
56
--
@@ -833,58 +834,18 @@ postMessageQualifiedLocalOwningBackendSuccess = do
833834
let encodedTextForAlex1 = toBase64Text "text-for-alex"
834835
encodedTextForAlex2 = toBase64Text "text-for-alex2"
835836
encodedTextForAmy = toBase64Text "text-for-amy"
836-
encodedTextForBob = toBase64Text "text-for-bob"
837-
encodedTextForBart1 = toBase64Text "text-for-bart1"
838-
encodedTextForBart2 = toBase64Text "text-for-bart2"
839-
encodedTextForCarl = toBase64Text "text-for-carl"
840837
encodedData = toBase64Text "data"
841838
liftIO $ do
842839
let matchReq domain component r = frTargetDomain r == domain && frComponent r == component
843840
filterReq domain component = filter (matchReq domain component) requests
844841
bBrigReq <- assertOne $ filterReq bDomain Brig
845-
bGalleyReq <- assertOne $ filterReq bDomain Galley
846842
cBrigReq <- assertOne $ filterReq cDomain Brig
847-
cGalleyReq <- assertOne $ filterReq cDomain Galley
848843

849844
frRPC bBrigReq @?= "get-user-clients"
850845
(sort . F.gucUsers <$> parseFedRequest bBrigReq) @?= Right (sort $ qUnqualified <$> [bob, bart])
851846
frRPC cBrigReq @?= "get-user-clients"
852847
parseFedRequest cBrigReq @?= Right (F.GetUserClients [qUnqualified carl])
853848

854-
frRPC bGalleyReq @?= "on-message-sent"
855-
bActualNotif <- assertRight $ parseFedRequest bGalleyReq
856-
let bExpectedNotif =
857-
F.RemoteMessage
858-
{ rmTime = F.rmTime bActualNotif,
859-
rmData = Just $ toBase64Text "data",
860-
rmSender = alice,
861-
rmSenderClient = aliceClient,
862-
rmConversation = qUnqualified convId,
863-
rmPriority = Nothing,
864-
rmPush = True,
865-
rmTransient = False,
866-
rmRecipients =
867-
UserClientMap $
868-
Map.fromList
869-
[ (qUnqualified bob, Map.singleton bobClient encodedTextForBob),
870-
( qUnqualified bart,
871-
Map.fromList
872-
[ (bartClient1, encodedTextForBart1),
873-
(bartClient2, encodedTextForBart2)
874-
]
875-
)
876-
]
877-
}
878-
bActualNotif @?= bExpectedNotif
879-
frRPC cGalleyReq @?= "on-message-sent"
880-
cActualNotif <- assertRight $ parseFedRequest cGalleyReq
881-
let cExpectedNotif =
882-
bExpectedNotif
883-
{ F.rmRecipients =
884-
UserClientMap $ Map.fromList [(qUnqualified carl, Map.singleton carlClient encodedTextForCarl)]
885-
}
886-
cActualNotif @?= cExpectedNotif
887-
888849
WS.assertMatch_ t wsAlex1 (wsAssertOtr' encodedData convId alice aliceClient alexClient encodedTextForAlex1)
889850
WS.assertMatch_ t wsAlex2 (wsAssertOtr' encodedData convId alice aliceClient alexClient2 encodedTextForAlex2)
890851
WS.assertMatch_ t wsAmy (wsAssertOtr' encodedData convId alice aliceClient amyClient encodedTextForAmy)
@@ -1232,7 +1193,6 @@ postMessageQualifiedLocalOwningBackendFailedToSendClients = do
12321193
]
12331194
pure resp2 !!! do
12341195
const 201 === statusCode
1235-
assertMismatchQualified expectedFailedToSend mempty mempty mempty
12361196

12371197
liftIO $ do
12381198
let encodedTextForBob = toBase64Text "text-for-bob"
@@ -1314,22 +1274,8 @@ postMessageQualifiedLocalOwningBackendFailedToSendClientsFailingGetUserClients =
13141274
"data"
13151275
Message.MismatchReportAll
13161276

1317-
let expectedFailedToSend =
1318-
QualifiedUserClients . Map.fromList $
1319-
[ ( remoteDomain,
1320-
Map.fromList
1321-
[ (deeId, Set.singleton deeClient)
1322-
]
1323-
),
1324-
( remoteDomain2,
1325-
Map.fromList
1326-
[ (emilyId, Set.singleton emilyClient)
1327-
]
1328-
)
1329-
]
13301277
pure resp2 !!! do
13311278
const 201 === statusCode
1332-
assertMismatchQualified expectedFailedToSend mempty mempty mempty
13331279

13341280
liftIO $ do
13351281
let encodedTextForBob = toBase64Text "text-for-bob"

services/galley/test/integration/API/Federation.hs

Lines changed: 1 addition & 113 deletions
Original file line numberDiff line numberDiff line change
@@ -26,13 +26,10 @@ import Control.Lens hiding ((#))
2626
import qualified Data.Aeson as A
2727
import Data.ByteString.Conversion (toByteString')
2828
import Data.Domain
29-
import Data.Id (ConvId, Id (..), UserId, randomId)
30-
import Data.Json.Util hiding ((#))
29+
import Data.Id
3130
import Data.List.NonEmpty (NonEmpty (..))
3231
import Data.List1 hiding (head)
3332
import qualified Data.List1 as List1
34-
import qualified Data.Map as Map
35-
import qualified Data.ProtoLens as Protolens
3633
import Data.Qualified
3734
import Data.Range
3835
import qualified Data.Set as Set
@@ -43,7 +40,6 @@ import Data.UUID.V4 (nextRandom)
4340
import Federator.MockServer
4441
import Imports
4542
import qualified Network.HTTP.Types as Http
46-
import Test.QuickCheck (arbitrary, generate)
4743
import Test.Tasty
4844
import qualified Test.Tasty.Cannon as WS
4945
import Test.Tasty.HUnit
@@ -58,9 +54,7 @@ import Wire.API.Federation.API.Galley
5854
import qualified Wire.API.Federation.API.Galley as FedGalley
5955
import Wire.API.Federation.Component
6056
import Wire.API.Internal.Notification
61-
import Wire.API.Message
6257
import Wire.API.Routes.Internal.Galley.ConversationsIntra
63-
import Wire.API.User.Client (PubClient (..))
6458
import Wire.API.User.Profile
6559

6660
tests :: IO TestSetup -> TestTree
@@ -84,7 +78,6 @@ tests s =
8478
test s "POST /federation/leave-conversation : Success" leaveConversationSuccess,
8579
test s "POST /federation/leave-conversation : Non-existent" leaveConversationNonExistent,
8680
test s "POST /federation/leave-conversation : Invalid type" leaveConversationInvalidType,
87-
test s "POST /federation/send-message : Post a message sent from another backend" sendMessage,
8881
test s "POST /federation/on-user-deleted-conversations : Remove deleted remote user from local conversations" onUserDeleted,
8982
test s "POST /federation/update-conversation : Update local conversation by a remote admin " updateConversationByRemoteAdmin,
9083
test s "POST /federation/on-conversation-updated : Notify local user about conversation rename with an unavailable federator" notifyConvRenameUnavailable,
@@ -816,111 +809,6 @@ leaveConversationInvalidType = do
816809
<!! const 200 === statusCode
817810
liftIO $ resp @?= Left FedGalley.RemoveFromConversationErrorRemovalNotAllowed
818811

819-
-- alice local, bob and chad remote in a local conversation
820-
-- bob sends a message (using the RPC), we test that alice receives it and that
821-
-- a call is made to the onMessageSent RPC to inform chad
822-
sendMessage :: TestM ()
823-
sendMessage = do
824-
cannon <- view tsCannon
825-
let remoteDomain = Domain "far-away.example.com"
826-
localDomain <- viewFederationDomain
827-
828-
-- users and clients
829-
(alice, aliceClient) <- randomUserWithClientQualified (head someLastPrekeys)
830-
let aliceId = qUnqualified alice
831-
bobId <- randomId
832-
bobClient <- liftIO $ generate arbitrary
833-
let bob = Qualified bobId remoteDomain
834-
bobProfile = mkProfile bob (Name "Bob")
835-
chadId <- randomId
836-
chadClient <- liftIO $ generate arbitrary
837-
let chad = Qualified chadId remoteDomain
838-
chadProfile = mkProfile chad (Name "Chad")
839-
840-
connectWithRemoteUser aliceId bob
841-
connectWithRemoteUser aliceId chad
842-
-- conversation
843-
let responses1 = guardComponent Brig *> mockReply [bobProfile, chadProfile]
844-
(convId, requests1) <-
845-
withTempMockFederator' (responses1 <|> mockReply EmptyResponse) $
846-
fmap decodeConvId $
847-
postConvQualified
848-
aliceId
849-
Nothing
850-
defNewProteusConv
851-
{ newConvQualifiedUsers = [bob, chad]
852-
}
853-
<!! const 201 === statusCode
854-
855-
liftIO $ do
856-
[galleyReq] <- case requests1 of
857-
xs@[_] -> pure xs
858-
_ -> assertFailure "unexpected number of requests"
859-
frComponent galleyReq @?= Galley
860-
frRPC galleyReq @?= "on-conversation-created"
861-
let conv = Qualified convId localDomain
862-
863-
-- we use bilge instead of the federation client to make a federated request
864-
-- here, because we need to make use of the mock federator, which at the moment
865-
-- supports only bilge requests
866-
let rcpts =
867-
[ (alice, aliceClient, "hi alice"),
868-
(chad, chadClient, "hi chad")
869-
]
870-
msg = mkQualifiedOtrPayload bobClient rcpts "" MismatchReportAll
871-
msr =
872-
FedGalley.ProteusMessageSendRequest
873-
{ FedGalley.pmsrConvId = convId,
874-
FedGalley.pmsrSender = bobId,
875-
FedGalley.pmsrRawMessage = Base64ByteString (Protolens.encodeMessage msg)
876-
}
877-
let mock = do
878-
guardComponent Brig
879-
mockReply $
880-
Map.fromList
881-
[ (chadId, Set.singleton (PubClient chadClient Nothing)),
882-
(bobId, Set.singleton (PubClient bobClient Nothing))
883-
]
884-
(_, requests2) <- withTempMockFederator' (mock <|> mockReply EmptyResponse) $ do
885-
WS.bracketR cannon aliceId $ \ws -> do
886-
g <- viewGalley
887-
msresp <-
888-
post
889-
( g
890-
. paths ["federation", "send-message"]
891-
. content "application/json"
892-
. header "Wire-Origin-Domain" (toByteString' remoteDomain)
893-
. json msr
894-
)
895-
<!! do
896-
const 200 === statusCode
897-
(FedGalley.MessageSendResponse eithStatus) <- responseJsonError msresp
898-
liftIO $ case eithStatus of
899-
Left err -> assertFailure $ "Expected Right, got Left: " <> show err
900-
Right mss -> do
901-
assertEqual "missing clients should be empty" mempty (mssMissingClients mss)
902-
assertEqual "redundant clients should be empty" mempty (mssRedundantClients mss)
903-
assertEqual "deleted clients should be empty" mempty (mssDeletedClients mss)
904-
assertEqual "failed to send should be empty" mempty (mssFailedToSend mss)
905-
906-
-- check that alice received the message
907-
WS.assertMatch_ (5 # Second) ws $
908-
wsAssertOtr' "" conv bob bobClient aliceClient (toBase64Text "hi alice")
909-
910-
-- check that a request to propagate message to chad has been made
911-
liftIO $ do
912-
[_clientReq, receiveReq] <- case requests2 of
913-
xs@[_, _] -> pure xs
914-
_ -> assertFailure "unexpected number of requests"
915-
frComponent receiveReq @?= Galley
916-
frRPC receiveReq @?= "on-message-sent"
917-
rm <- case A.decode (frBody receiveReq) of
918-
Nothing -> assertFailure "invalid federated request body"
919-
Just x -> pure (x :: FedGalley.RemoteMessage ConvId)
920-
FedGalley.rmSender rm @?= bob
921-
Map.keysSet (userClientMap (FedGalley.rmRecipients rm))
922-
@?= Set.singleton chadId
923-
924812
-- | There are 3 backends in action here:
925813
--
926814
-- - Backend A (local) has Alice and Alex

0 commit comments

Comments
 (0)