Skip to content

Commit

Permalink
Make ConversationUpdate request versioned
Browse files Browse the repository at this point in the history
  • Loading branch information
pcapriotti committed Feb 6, 2024
1 parent 91c5c36 commit 73f2140
Show file tree
Hide file tree
Showing 6 changed files with 41 additions and 7 deletions.
10 changes: 6 additions & 4 deletions libs/wire-api-federation/src/Wire/API/Federation/API.hs
Original file line number Diff line number Diff line change
Expand Up @@ -24,13 +24,14 @@ module Wire.API.Federation.API
HasUnsafeFedEndpoint,
fedClient,
fedQueueClient,
toBundle,
sendBundle,
fedClientIn,
unsafeFedClientIn,
module Wire.API.MakesFederatedCall,

-- * Re-exports
Component (..),
makeConversationUpdateBundle,
)
where

Expand All @@ -46,6 +47,7 @@ import Servant.Client.Core
import Wire.API.Federation.API.Brig
import Wire.API.Federation.API.Cargohold
import Wire.API.Federation.API.Galley
import Wire.API.Federation.API.Util
import Wire.API.Federation.BackendNotifications
import Wire.API.Federation.Client
import Wire.API.Federation.Component
Expand Down Expand Up @@ -95,11 +97,11 @@ fedClientIn ::
Client m api
fedClientIn = clientIn (Proxy @api) (Proxy @m)

fedQueueClientFromBundle ::
sendBundle ::
KnownComponent c =>
PayloadBundle c ->
FedQueueClient c ()
fedQueueClientFromBundle bundle = do
sendBundle bundle = do
env <- ask
let msg =
newMsg
Expand All @@ -123,7 +125,7 @@ fedQueueClient ::
) =>
Payload tag ->
FedQueueClient c ()
fedQueueClient payload = fedQueueClientFromBundle =<< makeBundle @tag payload
fedQueueClient payload = sendBundle =<< makeBundle @tag payload

-- | Like 'fedClientIn', but doesn't propagate a 'CallsFed' constraint. Intended
-- to be used in test situations only.
Expand Down
29 changes: 29 additions & 0 deletions libs/wire-api-federation/src/Wire/API/Federation/API/Util.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,29 @@
-- This file is part of the Wire Server implementation.
--
-- Copyright (C) 2023 Wire Swiss GmbH <opensource@wire.com>
--
-- This program is free software: you can redistribute it and/or modify it under
-- the terms of the GNU Affero General Public License as published by the Free
-- Software Foundation, either version 3 of the License, or (at your option) any
-- later version.
--
-- This program is distributed in the hope that it will be useful, but WITHOUT
-- ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS
-- FOR A PARTICULAR PURPOSE. See the GNU Affero General Public License for more
-- details.
--
-- 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/>.

module Wire.API.Federation.API.Util where

import Imports
import Wire.API.Federation.API.Galley.Notifications
import Wire.API.Federation.BackendNotifications
import Wire.API.Federation.Component

makeConversationUpdateBundle ::
ConversationUpdate ->
FedQueueClient 'Galley (PayloadBundle 'Galley)
makeConversationUpdateBundle update =
(<>) <$> makeBundle update <*> makeBundle (conversationUpdateToV0 update)
Original file line number Diff line number Diff line change
Expand Up @@ -27,7 +27,7 @@ class IsNotificationTag k where

class HasNotificationEndpoint t where
-- | The type of the payload for this endpoint
type Payload t :: Type
type Payload t = (p :: Type) | p -> t

-- | The central path component of a notification endpoint, e.g.,
-- "on-conversation-updated".
Expand Down
1 change: 1 addition & 0 deletions libs/wire-api-federation/wire-api-federation.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -23,6 +23,7 @@ library
Wire.API.Federation.API.Common
Wire.API.Federation.API.Galley
Wire.API.Federation.API.Galley.Notifications
Wire.API.Federation.API.Util
Wire.API.Federation.BackendNotifications
Wire.API.Federation.Client
Wire.API.Federation.Component
Expand Down
4 changes: 3 additions & 1 deletion services/galley/src/Galley/API/Action.hs
Original file line number Diff line number Diff line change
Expand Up @@ -897,7 +897,9 @@ notifyConversationAction tag quid notifyOrigDomain con lconv targets action = do
-- because quid's backend will update local state and notify its users
-- itself using the ConversationUpdate returned by this function
if notifyOrigDomain || tDomain ruids /= qDomain quid
then fedQueueClient @'OnConversationUpdatedTag update $> Nothing
then do
makeConversationUpdateBundle update >>= sendBundle
pure Nothing
else pure (Just update)

-- notify local participants and bots
Expand Down
2 changes: 1 addition & 1 deletion services/galley/src/Galley/API/Util.hs
Original file line number Diff line number Diff line change
Expand Up @@ -865,7 +865,7 @@ registerRemoteConversationMemberships now lusr lc = deleteOnUnreachable $ do
joined

r <- enqueueNotificationsConcurrentlyBuckets Q.Persistent joinedCoupled $ \z ->
fedQueueClient @'OnConversationUpdatedTag (convUpdateJoin z)
makeConversationUpdateBundle (convUpdateJoin z) >>= sendBundle
either throw (void . pure) r
where
creator :: Maybe UserId
Expand Down

0 comments on commit 73f2140

Please sign in to comment.