Skip to content

Commit

Permalink
Welcome notification bug (#3907)
Browse files Browse the repository at this point in the history
* Add failing test reproducing the issue

* Only create one welcome notification per user

* Add CHANGELOG entry

* Lint

* Test notifications for both clients
  • Loading branch information
pcapriotti committed Mar 11, 2024
1 parent 4991a55 commit 9a881d5
Show file tree
Hide file tree
Showing 4 changed files with 45 additions and 2 deletions.
1 change: 1 addition & 0 deletions changelog.d/3-bug-fixes/welcome-notifications
Original file line number Diff line number Diff line change
@@ -0,0 +1 @@
Fix bug where welcome notifications were generated for each client instead of for each user
1 change: 1 addition & 0 deletions integration/integration.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -128,6 +128,7 @@ library
Test.MLS
Test.MLS.KeyPackage
Test.MLS.Message
Test.MLS.Notifications
Test.MLS.One2One
Test.MLS.SubConversation
Test.MLS.Unreachable
Expand Down
30 changes: 30 additions & 0 deletions integration/test/Test/MLS/Notifications.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,30 @@
module Test.MLS.Notifications where

import API.Gundeck
import MLS.Util
import Notifications
import SetupHelpers
import Testlib.Prelude

testWelcomeNotification :: HasCallStack => App ()
testWelcomeNotification = do
[alice, bob] <- createAndConnectUsers [OwnDomain, OtherDomain]
[alice1, alice2, bob1, bob2] <- traverse (createMLSClient def) [alice, alice, bob, bob]
traverse_ uploadNewKeyPackage [alice2, bob1, bob2]

void $ createNewGroup alice1
notif <- withWebSocket bob $ \ws -> do
void $ createAddCommit alice1 [alice, bob] >>= sendAndConsumeCommitBundle
awaitMatch isWelcomeNotif ws

notifId <- notif %. "id" & asString

for_ [bob1, bob2] $ \cid ->
getNotifications
bob
def
{ since = Just notifId,
client = Just cid.client,
size = Just 10000
}
>>= getJSON 200
15 changes: 13 additions & 2 deletions services/galley/src/Galley/API/MLS/Welcome.hs
Original file line number Diff line number Diff line change
Expand Up @@ -26,13 +26,16 @@ import Data.Aeson qualified as A
import Data.Domain
import Data.Id
import Data.Json.Util
import Data.List1
import Data.Map qualified as Map
import Data.Qualified
import Data.Time
import Galley.API.Push
import Galley.Effects.ExternalAccess
import Galley.Effects.FederatorAccess
import Galley.Effects.GundeckAccess
import Imports
import Gundeck.Types.Push.V2 (RecipientClients (..))
import Imports hiding (cs)
import Network.Wai.Utilities.JSONResponse
import Polysemy
import Polysemy.Input
Expand Down Expand Up @@ -87,9 +90,17 @@ sendLocalWelcomes ::
Local [(UserId, ClientId)] ->
Sem r ()
sendLocalWelcomes qcnv qusr con now welcome lclients = do
-- only create one notification per user
let rcpts =
map (\(u, cs) -> Recipient u (RecipientClientsSome (List1 cs)))
. Map.assocs
. foldr
(\(u, c) -> Map.insertWith (<>) u (pure c))
mempty
$ tUnqualified lclients
let e = Event qcnv Nothing qusr now $ EdMLSWelcome welcome.raw
runMessagePush lclients (Just qcnv) $
newMessagePush mempty con defMessageMetadata (tUnqualified lclients) e
newMessagePush mempty con defMessageMetadata rcpts e

sendRemoteWelcomes ::
( Member FederatorAccess r,
Expand Down

0 comments on commit 9a881d5

Please sign in to comment.