Skip to content

Commit

Permalink
[WPB-3799] cannot fetch conversation details after connection request (
Browse files Browse the repository at this point in the history
  • Loading branch information
battermann authored Aug 24, 2023
1 parent 119fe8a commit bec112a
Show file tree
Hide file tree
Showing 9 changed files with 182 additions and 2 deletions.
1 change: 1 addition & 0 deletions changelog.d/5-internal/pr-3538
Original file line number Diff line number Diff line change
@@ -0,0 +1 @@
Additional integration test for federated connections
6 changes: 6 additions & 0 deletions integration/default.nix
Original file line number Diff line number Diff line change
Expand Up @@ -15,8 +15,10 @@
, Cabal
, case-insensitive
, containers
, cryptonite
, data-default
, directory
, errors
, exceptions
, extra
, filepath
Expand All @@ -28,6 +30,7 @@
, lens
, lens-aeson
, lib
, memory
, mime
, monad-control
, mtl
Expand Down Expand Up @@ -76,8 +79,10 @@ mkDerivation {
bytestring-conversion
case-insensitive
containers
cryptonite
data-default
directory
errors
exceptions
extra
filepath
Expand All @@ -87,6 +92,7 @@ mkDerivation {
kan-extensions
lens
lens-aeson
memory
mime
monad-control
mtl
Expand Down
4 changes: 4 additions & 0 deletions integration/integration.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -118,6 +118,7 @@ library
Testlib.HTTP
Testlib.JSON
Testlib.ModService
Testlib.One2One
Testlib.Options
Testlib.Ports
Testlib.Prekeys
Expand All @@ -142,8 +143,10 @@ library
, bytestring-conversion
, case-insensitive
, containers
, cryptonite
, data-default
, directory
, errors
, exceptions
, extra
, filepath
Expand All @@ -153,6 +156,7 @@ library
, kan-extensions
, lens
, lens-aeson
, memory
, mime
, monad-control
, mtl
Expand Down
8 changes: 7 additions & 1 deletion integration/test/API/Brig.hs
Original file line number Diff line number Diff line change
@@ -1,6 +1,7 @@
module API.Brig where

import API.Common
import Data.Aeson qualified as Aeson
import Data.ByteString.Base64 qualified as Base64
import Data.Foldable
import Data.Function
Expand Down Expand Up @@ -218,7 +219,12 @@ putConnection userFrom userTo status = do
baseRequest userFrom Brig Versioned $
joinHttpPath ["/connections", userToDomain, userToId]
statusS <- asString status
submit "POST" (req & addJSONObject ["status" .= statusS])
submit "PUT" (req & addJSONObject ["status" .= statusS])

getConnections :: (HasCallStack, MakesValue user) => user -> App Response
getConnections user = do
req <- baseRequest user Brig Versioned "/list-connections"
submit "POST" (req & addJSONObject ["size" .= Aeson.Number 500])

uploadKeyPackage :: ClientIdentity -> ByteString -> App Response
uploadKeyPackage cid kp = do
Expand Down
11 changes: 11 additions & 0 deletions integration/test/API/BrigInternal.hs
Original file line number Diff line number Diff line change
Expand Up @@ -150,3 +150,14 @@ refreshIndex domain = do
req <- baseRequest domain Brig Unversioned "i/index/refresh"
res <- submit "POST" req
res.status `shouldMatchInt` 200

connectWithRemoteUser :: (MakesValue userFrom, MakesValue userTo) => userFrom -> userTo -> App ()
connectWithRemoteUser userFrom userTo = do
userFromId <- objId userFrom
qUserTo <- make userTo
let body = ["tag" .= "CreateConnectionForTest", "user" .= userFromId, "other" .= qUserTo]
req <-
baseRequest userFrom Brig Unversioned $
joinHttpPath ["i", "connections", "connection-update"]
res <- submit "PUT" (req & addJSONObject body)
res.status `shouldMatchInt` 200
27 changes: 27 additions & 0 deletions integration/test/API/Nginz.hs
Original file line number Diff line number Diff line change
Expand Up @@ -6,3 +6,30 @@ getSystemSettingsUnAuthorized :: (HasCallStack, MakesValue domain) => domain ->
getSystemSettingsUnAuthorized domain = do
req <- baseRequest domain Nginz Versioned "/system/settings/unauthorized"
submit "GET" req

login :: (HasCallStack, MakesValue domain, MakesValue email, MakesValue password) => domain -> email -> password -> App Response
login domain email pw = do
req <- rawBaseRequest domain Nginz Unversioned "/login"
emailStr <- make email >>= asString
pwStr <- make pw >>= asString
submit "POST" (req & addJSONObject ["email" .= emailStr, "password" .= pwStr, "label" .= "auth"])

access :: (HasCallStack, MakesValue domain, MakesValue cookie) => domain -> cookie -> App Response
access domain cookie = do
req <- rawBaseRequest domain Nginz Unversioned "/access"
cookieStr <- make cookie >>= asString
submit "POST" (req & setCookie cookieStr)

logout :: (HasCallStack, MakesValue domain, MakesValue cookie, MakesValue token) => domain -> cookie -> token -> App Response
logout d c t = do
req <- rawBaseRequest d Nginz Unversioned "/access/logout"
cookie <- make c & asString
token <- make t & asString
submit "POST" (req & setCookie cookie & addHeader "Authorization" ("Bearer " <> token))

getConversation :: (HasCallStack, MakesValue user, MakesValue qcnv, MakesValue token) => user -> qcnv -> token -> App Response
getConversation user qcnv t = do
(domain, cnv) <- objQid qcnv
token <- make t & asString
req <- rawBaseRequest user Nginz Versioned (joinHttpPath ["conversations", domain, cnv])
submit "GET" (req & addHeader "Authorization" ("Bearer " <> token))
21 changes: 20 additions & 1 deletion integration/test/Test/Conversation.hs
Original file line number Diff line number Diff line change
Expand Up @@ -3,7 +3,7 @@

module Test.Conversation where

import API.Brig (getConnection)
import API.Brig (getConnection, getConnections, postConnection)
import API.BrigInternal
import API.Galley
import API.GalleyInternal
Expand All @@ -13,6 +13,7 @@ import Control.Concurrent (threadDelay)
import Data.Aeson qualified as Aeson
import GHC.Stack
import SetupHelpers
import Testlib.One2One (generateRemoteAndConvIdWithDomain)
import Testlib.Prelude

testDynamicBackendsFullyConnectedWhenAllowAll :: HasCallStack => App ()
Expand Down Expand Up @@ -443,3 +444,21 @@ testAddingUserNonFullyConnectedFederation = do
bindResponse (addMembers alice conv [bobId, charlieId]) $ \resp -> do
resp.status `shouldMatchInt` 409
resp.json %. "non_federating_backends" `shouldMatchSet` [other, dynBackend]

testGetOneOnOneConvInStatusSentFromRemote :: App ()
testGetOneOnOneConvInStatusSentFromRemote = do
d1User <- randomUser OwnDomain def
let shouldBeLocal = True
(d2Usr, d2ConvId) <- generateRemoteAndConvIdWithDomain OtherDomain (not shouldBeLocal) d1User
bindResponse (postConnection d1User d2Usr) $ \r -> do
r.status `shouldMatchInt` 201
r.json %. "status" `shouldMatch` "sent"
bindResponse (listConversationIds d1User def) $ \r -> do
r.status `shouldMatchInt` 200
convIds <- r.json %. "qualified_conversations" & asList
filter ((==) d2ConvId) convIds `shouldMatch` [d2ConvId]
bindResponse (getConnections d1User) $ \r -> do
qConvIds <- r.json %. "connections" & asList >>= traverse (%. "qualified_conversation")
filter ((==) d2ConvId) qConvIds `shouldMatch` [d2ConvId]
resp <- getConversation d1User d2ConvId
resp.status `shouldMatchInt` 200
4 changes: 4 additions & 0 deletions integration/test/Testlib/HTTP.hs
Original file line number Diff line number Diff line change
Expand Up @@ -70,6 +70,10 @@ addHeader :: String -> String -> HTTP.Request -> HTTP.Request
addHeader name value req =
req {HTTP.requestHeaders = (CI.mk . C8.pack $ name, C8.pack value) : HTTP.requestHeaders req}

setCookie :: String -> HTTP.Request -> HTTP.Request
setCookie c r =
addHeader "Cookie" (cs c) r

addQueryParams :: [(String, String)] -> HTTP.Request -> HTTP.Request
addQueryParams params req =
HTTP.setQueryString (map (\(k, v) -> (cs k, Just (cs v))) params) req
Expand Down
102 changes: 102 additions & 0 deletions integration/test/Testlib/One2One.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,102 @@
-- This file is part of the Wire Server implementation.
--
-- Copyright (C) 2022 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/>.

-- This is a duplicate of `Galley.Types.Conversations.One2One`
-- and is needed because we do not have access to galley code in the integration tests
module Testlib.One2One (generateRemoteAndConvIdWithDomain) where

import Control.Error (atMay)
import Crypto.Hash qualified as Crypto
import Data.Bits
import Data.ByteArray (convert)
import Data.ByteString
import Data.ByteString qualified as B
import Data.ByteString.Conversion
import Data.ByteString.Lazy qualified as L
import Data.UUID as UUID
import SetupHelpers (randomUser)
import Testlib.Prelude

generateRemoteAndConvIdWithDomain :: (MakesValue domain, MakesValue a) => domain -> Bool -> a -> App (Value, Value)
generateRemoteAndConvIdWithDomain remoteDomain shouldBeLocal lUserId = do
(localDomain, localUser) <- objQid lUserId
otherUsr <- randomUser remoteDomain def >>= objId
otherDomain <- asString remoteDomain
let (cId, cDomain) =
one2OneConvId
(fromMaybe (error "invalid UUID") (UUID.fromString localUser), localDomain)
(fromMaybe (error "invalid UUID") (UUID.fromString otherUsr), otherDomain)
isLocal = localDomain == cDomain
if shouldBeLocal == isLocal
then
pure $
( object ["id" .= (otherUsr), "domain" .= otherDomain],
object ["id" .= (UUID.toString cId), "domain" .= cDomain]
)
else generateRemoteAndConvIdWithDomain remoteDomain shouldBeLocal lUserId

one2OneConvId :: (UUID, String) -> (UUID, String) -> (UUID, String)
one2OneConvId a@(a1, dom1) b@(a2, dom2) = case compare (dom1, a1) (dom2, a2) of
GT -> one2OneConvId b a
_ ->
let c =
mconcat
[ L.toStrict (UUID.toByteString namespace),
quidToByteString a,
quidToByteString b
]
x = hash c
result =
toUuidV5
. mkV5
. fromMaybe nil
. UUID.fromByteString
. L.fromStrict
. B.take 16
$ x
domain
| fromMaybe 0 (atMay (B.unpack x) 16) .&. 0x80 == 0 = dom1
| otherwise = dom2
in (result, domain)
where
hash :: ByteString -> ByteString
hash = convert . Crypto.hash @ByteString @Crypto.SHA256

namespace :: UUID
namespace = fromWords 0x9a51edb8 0x060c0d9a 0x0c2950a8 0x5d152982

quidToByteString :: (UUID, String) -> ByteString
quidToByteString (uid, domain) = toASCIIBytes uid <> toByteString' domain

newtype UuidV5 = UuidV5 {toUuidV5 :: UUID}
deriving (Eq, Ord, Show)

mkV5 :: UUID -> UuidV5
mkV5 u = UuidV5 $
case toWords u of
(x0, x1, x2, x3) ->
fromWords
x0
(retainVersion 5 x1)
(retainVariant 2 x2)
x3
where
retainVersion :: Word32 -> Word32 -> Word32
retainVersion v x = (x .&. 0xFFFF0FFF) .|. (v `shiftL` 12)

retainVariant :: Word32 -> Word32 -> Word32
retainVariant v x = (x .&. 0x3FFFFFFF) .|. (v `shiftL` 30)

0 comments on commit bec112a

Please sign in to comment.