{-# LANGUAGE DuplicateRecordFields #-}
{-# OPTIONS_GHC -Wno-incomplete-patterns #-}
module Test.Brig where
import API.Brig as BrigP
import qualified API.BrigInternal as BrigI
import API.Common
import API.GalleyInternal (setTeamFeatureStatus)
import API.Spar
import Control.Retry
import Data.Aeson.Types hiding ((.=))
import Data.List.Split
import Data.String.Conversions
import qualified Data.UUID as UUID
import qualified Data.UUID.V4 as UUID
import GHC.Stack
import SetupHelpers
import System.IO.Extra
import Testlib.Assertions
import Testlib.Prelude
import UnliftIO.Temporary
testCrudFederationRemotes :: (HasCallStack) => App ()
testCrudFederationRemotes :: HasCallStack => App ()
testCrudFederationRemotes = do
otherDomain <- Domain -> App String
forall a. (HasCallStack, MakesValue a) => a -> App String
asString Domain
OtherDomain
withModifiedBackend def $ \String
ownDomain -> do
let parseFedConns :: (HasCallStack) => Response -> App [Value]
parseFedConns :: HasCallStack => Response -> App [Value]
parseFedConns Response
resp =
HasCallStack => Int -> Response -> App Value
Int -> Response -> App Value
getJSON Int
200 Response
resp App Value -> String -> App Value
forall a. (HasCallStack, MakesValue a) => a -> String -> App Value
%. String
"remotes"
App Value -> (App Value -> App [Value]) -> App [Value]
forall a b. a -> (a -> b) -> b
& App Value -> App [Value]
forall a. (HasCallStack, MakesValue a) => a -> App [Value]
asList
App [Value] -> ([Value] -> App [Value]) -> App [Value]
forall a b. App a -> (a -> App b) -> App b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= (Value -> App Value) -> [Value] -> App [Value]
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> [a] -> f [b]
traverse ((Object -> Value) -> App Object -> App Value
forall a b. (a -> b) -> App a -> App b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Object -> Value
Object (App Object -> App Value)
-> (Value -> App Object) -> Value -> App Value
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Value -> App Object
forall a. (HasCallStack, MakesValue a) => a -> App Object
asObject)
addTest :: (MakesValue fedConn, Ord fedConn2, ToJSON fedConn2, MakesValue fedConn2, HasCallStack) => fedConn -> [fedConn2] -> App ()
addTest :: forall fedConn fedConn2.
(MakesValue fedConn, Ord fedConn2, ToJSON fedConn2,
MakesValue fedConn2, HasCallStack) =>
fedConn -> [fedConn2] -> App ()
addTest fedConn
fedConn [fedConn2]
want = do
App Response -> (Response -> App ()) -> App ()
forall a.
HasCallStack =>
App Response -> (Response -> App a) -> App a
bindResponse (String -> fedConn -> App Response
forall dom fedConn.
(HasCallStack, MakesValue dom, MakesValue fedConn) =>
dom -> fedConn -> App Response
BrigI.createFedConn String
ownDomain fedConn
fedConn) ((Response -> App ()) -> App ()) -> (Response -> App ()) -> App ()
forall a b. (a -> b) -> a -> b
$ \Response
res -> do
String -> App () -> App ()
forall a. String -> App a -> App a
addFailureContext (String
"res = " String -> String -> String
forall a. Semigroup a => a -> a -> a
<> Response -> String
forall a. Show a => a -> String
show Response
res) (App () -> App ()) -> App () -> App ()
forall a b. (a -> b) -> a -> b
$ Response
res.status Int -> Int -> App ()
forall a. (MakesValue a, HasCallStack) => a -> Int -> App ()
`shouldMatchInt` Int
200
res2 <- HasCallStack => Response -> App [Value]
Response -> App [Value]
parseFedConns (Response -> App [Value]) -> App Response -> App [Value]
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< String -> App Response
forall dom. (HasCallStack, MakesValue dom) => dom -> App Response
BrigI.readFedConns String
ownDomain
sort res2 `shouldMatch` sort want
updateTest :: (MakesValue fedConn, Ord fedConn2, ToJSON fedConn2, MakesValue fedConn2, HasCallStack) => String -> fedConn -> [fedConn2] -> App ()
updateTest :: forall fedConn fedConn2.
(MakesValue fedConn, Ord fedConn2, ToJSON fedConn2,
MakesValue fedConn2, HasCallStack) =>
String -> fedConn -> [fedConn2] -> App ()
updateTest String
domain fedConn
fedConn [fedConn2]
want = do
App Response -> (Response -> App ()) -> App ()
forall a.
HasCallStack =>
App Response -> (Response -> App a) -> App a
bindResponse (String -> String -> fedConn -> App Response
forall owndom fedConn.
(HasCallStack, MakesValue owndom, MakesValue fedConn) =>
owndom -> String -> fedConn -> App Response
BrigI.updateFedConn String
ownDomain String
domain fedConn
fedConn) ((Response -> App ()) -> App ()) -> (Response -> App ()) -> App ()
forall a b. (a -> b) -> a -> b
$ \Response
res -> do
String -> App () -> App ()
forall a. String -> App a -> App a
addFailureContext (String
"res = " String -> String -> String
forall a. Semigroup a => a -> a -> a
<> Response -> String
forall a. Show a => a -> String
show Response
res) (App () -> App ()) -> App () -> App ()
forall a b. (a -> b) -> a -> b
$ Response
res.status Int -> Int -> App ()
forall a. (MakesValue a, HasCallStack) => a -> Int -> App ()
`shouldMatchInt` Int
200
res2 <- HasCallStack => Response -> App [Value]
Response -> App [Value]
parseFedConns (Response -> App [Value]) -> App Response -> App [Value]
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< String -> App Response
forall dom. (HasCallStack, MakesValue dom) => dom -> App Response
BrigI.readFedConns String
ownDomain
sort res2 `shouldMatch` sort want
dom1 :: String <- (String -> String -> String
forall a. Semigroup a => a -> a -> a
<> String
".example.com") (String -> String) -> (UUID -> String) -> UUID -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. UUID -> String
UUID.toString (UUID -> String) -> App UUID -> App String
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> IO UUID -> App UUID
forall a. IO a -> App a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO IO UUID
UUID.nextRandom
let remote1, remote1' :: BrigI.FedConn
remote1 = String -> String -> Maybe [String] -> FedConn
BrigI.FedConn String
dom1 String
"no_search" Maybe [String]
forall a. Maybe a
Nothing
remote1' = FedConn
remote1 {BrigI.searchStrategy = "full_search", BrigI.restriction = Just []}
cfgRemotesExpect :: BrigI.FedConn
cfgRemotesExpect = String -> String -> Maybe [String] -> FedConn
BrigI.FedConn (String -> String
forall a b. ConvertibleStrings a b => a -> b
cs String
otherDomain) String
"full_search" Maybe [String]
forall a. Maybe a
Nothing
cfgRemotes <- parseFedConns =<< BrigI.readFedConns ownDomain
cfgRemotes `shouldMatch` ([] @Value)
addTest cfgRemotesExpect [cfgRemotesExpect]
addTest remote1 [cfgRemotesExpect, remote1]
addTest remote1 [cfgRemotesExpect, remote1]
updateTest (BrigI.domain remote1) remote1' [cfgRemotesExpect, remote1']
testCrudOAuthClient :: (HasCallStack) => App ()
testCrudOAuthClient :: HasCallStack => App ()
testCrudOAuthClient = do
user <- Domain -> CreateUser -> App Value
forall domain.
(HasCallStack, MakesValue domain) =>
domain -> CreateUser -> App Value
randomUser Domain
OwnDomain CreateUser
forall a. Default a => a
def
let appName = String
"foobar"
let url = String
"https://example.com/callback.html"
clientId <- bindResponse (BrigI.registerOAuthClient user appName url) $ \Response
resp -> do
Response
resp.status Int -> Int -> App ()
forall a. (MakesValue a, HasCallStack) => a -> Int -> App ()
`shouldMatchInt` Int
200
Response
resp.json App Value -> String -> App Value
forall a. (HasCallStack, MakesValue a) => a -> String -> App Value
%. String
"client_id"
bindResponse (BrigI.getOAuthClient user clientId) $ \Response
resp -> do
Response
resp.status Int -> Int -> App ()
forall a. (MakesValue a, HasCallStack) => a -> Int -> App ()
`shouldMatchInt` Int
200
Response
resp.json App Value -> String -> App Value
forall a. (HasCallStack, MakesValue a) => a -> String -> App Value
%. String
"application_name" App Value -> String -> App ()
forall a b.
(MakesValue a, MakesValue b, HasCallStack) =>
a -> b -> App ()
`shouldMatch` String
appName
Response
resp.json App Value -> String -> App Value
forall a. (HasCallStack, MakesValue a) => a -> String -> App Value
%. String
"redirect_url" App Value -> String -> App ()
forall a b.
(MakesValue a, MakesValue b, HasCallStack) =>
a -> b -> App ()
`shouldMatch` String
url
let newName = String
"barfoo"
let newUrl = String
"https://example.com/callback2.html"
bindResponse (BrigI.updateOAuthClient user clientId newName newUrl) $ \Response
resp -> do
Response
resp.status Int -> Int -> App ()
forall a. (MakesValue a, HasCallStack) => a -> Int -> App ()
`shouldMatchInt` Int
200
Response
resp.json App Value -> String -> App Value
forall a. (HasCallStack, MakesValue a) => a -> String -> App Value
%. String
"application_name" App Value -> String -> App ()
forall a b.
(MakesValue a, MakesValue b, HasCallStack) =>
a -> b -> App ()
`shouldMatch` String
newName
Response
resp.json App Value -> String -> App Value
forall a. (HasCallStack, MakesValue a) => a -> String -> App Value
%. String
"redirect_url" App Value -> String -> App ()
forall a b.
(MakesValue a, MakesValue b, HasCallStack) =>
a -> b -> App ()
`shouldMatch` String
newUrl
bindResponse (BrigI.deleteOAuthClient user clientId) $ \Response
resp -> do
Response
resp.status Int -> Int -> App ()
forall a. (MakesValue a, HasCallStack) => a -> Int -> App ()
`shouldMatchInt` Int
200
bindResponse (BrigI.getOAuthClient user clientId) $ \Response
resp -> do
Response
resp.status Int -> Int -> App ()
forall a. (MakesValue a, HasCallStack) => a -> Int -> App ()
`shouldMatchInt` Int
404
testCrudFederationRemoteTeams :: (HasCallStack) => App ()
testCrudFederationRemoteTeams :: HasCallStack => App ()
testCrudFederationRemoteTeams = do
(_, tid, _) <- Domain -> Int -> App (Value, String, [Value])
forall domain.
(HasCallStack, MakesValue domain) =>
domain -> Int -> App (Value, String, [Value])
createTeam Domain
OwnDomain Int
1
(_, tid2, _) <- createTeam OwnDomain 1
rd <- (\String
n -> String
n String -> String -> String
forall a. Semigroup a => a -> a -> a
<> String
".wire.com") <$> randomName
bindResponse (BrigI.addFederationRemoteTeam' OwnDomain rd tid) $ \Response
resp -> do
Response
resp.status Int -> Int -> App ()
forall a. (MakesValue a, HasCallStack) => a -> Int -> App ()
`shouldMatchInt` Int
533
void $ BrigI.createFedConn OwnDomain $ BrigI.FedConn rd "full_search" Nothing
bindResponse (BrigI.addFederationRemoteTeam' OwnDomain rd tid) $ \Response
resp -> do
Response
resp.status Int -> Int -> App ()
forall a. (MakesValue a, HasCallStack) => a -> Int -> App ()
`shouldMatchInt` Int
533
void $ BrigI.updateFedConn OwnDomain rd $ BrigI.FedConn rd "full_search" (Just [])
bindResponse (BrigI.getFederationRemoteTeams OwnDomain rd) $ \Response
resp -> do
Response
resp.status Int -> Int -> App ()
forall a. (MakesValue a, HasCallStack) => a -> Int -> App ()
`shouldMatchInt` Int
200
Response -> [String] -> App ()
checkAbsence Response
resp [String
tid, String
tid2]
BrigI.addFederationRemoteTeam OwnDomain rd tid
bindResponse (BrigI.getFederationRemoteTeams OwnDomain rd) $ \Response
resp -> do
Response
resp.status Int -> Int -> App ()
forall a. (MakesValue a, HasCallStack) => a -> Int -> App ()
`shouldMatchInt` Int
200
Response -> [String] -> App ()
checkPresence Response
resp [String
tid]
Response -> [String] -> App ()
checkAbsence Response
resp [String
tid2]
BrigI.addFederationRemoteTeam OwnDomain rd tid2
bindResponse (BrigI.getFederationRemoteTeams OwnDomain rd) $ \Response
resp -> do
Response
resp.status Int -> Int -> App ()
forall a. (MakesValue a, HasCallStack) => a -> Int -> App ()
`shouldMatchInt` Int
200
Response -> [String] -> App ()
checkPresence Response
resp [String
tid, String
tid2]
BrigI.deleteFederationRemoteTeam OwnDomain rd tid
bindResponse (BrigI.getFederationRemoteTeams OwnDomain rd) $ \Response
resp -> do
Response
resp.status Int -> Int -> App ()
forall a. (MakesValue a, HasCallStack) => a -> Int -> App ()
`shouldMatchInt` Int
200
Response -> [String] -> App ()
checkPresence Response
resp [String
tid2]
Response -> [String] -> App ()
checkAbsence Response
resp [String
tid]
BrigI.deleteFederationRemoteTeam OwnDomain rd tid2
bindResponse (BrigI.getFederationRemoteTeams OwnDomain rd) $ \Response
resp -> do
Response
resp.status Int -> Int -> App ()
forall a. (MakesValue a, HasCallStack) => a -> Int -> App ()
`shouldMatchInt` Int
200
Response -> [String] -> App ()
checkAbsence Response
resp [String
tid, String
tid2]
where
checkAbsence :: Response -> [String] -> App ()
checkAbsence :: Response -> [String] -> App ()
checkAbsence Response
resp [String]
tids = do
l <- Response
resp.json App Value -> (App Value -> App [Value]) -> App [Value]
forall a b. a -> (a -> b) -> b
& App Value -> App [Value]
forall a. (HasCallStack, MakesValue a) => a -> App [Value]
asList
remoteTeams <- forM l (\Value
e -> Value
e Value -> String -> App Value
forall a. (HasCallStack, MakesValue a) => a -> String -> App Value
%. String
"team_id" App Value -> (App Value -> App String) -> App String
forall a b. a -> (a -> b) -> b
& App Value -> App String
forall a. (HasCallStack, MakesValue a) => a -> App String
asString)
when (any (\String
t -> String
t String -> [String] -> Bool
forall a. Eq a => a -> [a] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [String]
remoteTeams) tids) $ assertFailure "Expected response to not contain any of the teams"
checkPresence :: Response -> [String] -> App ()
checkPresence :: Response -> [String] -> App ()
checkPresence Response
resp [String]
tids = do
l <- Response
resp.json App Value -> (App Value -> App [Value]) -> App [Value]
forall a b. a -> (a -> b) -> b
& App Value -> App [Value]
forall a. (HasCallStack, MakesValue a) => a -> App [Value]
asList
remoteTeams <- forM l (\Value
e -> Value
e Value -> String -> App Value
forall a. (HasCallStack, MakesValue a) => a -> String -> App Value
%. String
"team_id" App Value -> (App Value -> App String) -> App String
forall a b. a -> (a -> b) -> b
& App Value -> App String
forall a. (HasCallStack, MakesValue a) => a -> App String
asString)
when (any (\String
t -> String
t String -> [String] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`notElem` [String]
remoteTeams) tids) $ assertFailure "Expected response to contain all of the teams"
testSFTCredentials :: (HasCallStack) => App ()
testSFTCredentials :: HasCallStack => App ()
testSFTCredentials = do
let ttl :: Int
ttl = (Int
60 :: Int)
String -> (String -> Handle -> App ()) -> App ()
forall (m :: * -> *) a.
MonadUnliftIO m =>
String -> (String -> Handle -> m a) -> m a
withSystemTempFile String
"sft-secret" ((String -> Handle -> App ()) -> App ())
-> (String -> Handle -> App ()) -> App ()
forall a b. (a -> b) -> a -> b
$ \String
secretFile Handle
secretHandle -> do
IO () -> App ()
forall a. IO a -> App a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> App ()) -> IO () -> App ()
forall a b. (a -> b) -> a -> b
$ do
Handle -> String -> IO ()
hPutStr Handle
secretHandle String
"xMtZyTpu=Leb?YKCoq#BXQR:gG^UrE83dNWzFJ2VcD"
Handle -> IO ()
hClose Handle
secretHandle
ServiceOverrides -> (HasCallStack => String -> App ()) -> App ()
forall a.
HasCallStack =>
ServiceOverrides -> (HasCallStack => String -> App a) -> App a
withModifiedBackend
( ServiceOverrides
forall a. Default a => a
def
{ brigCfg =
( setField "sft.sftBaseDomain" "integration-tests.zinfra.io"
. setField "sft.sftToken.ttl" ttl
. setField "sft.sftToken.secret" secretFile
. setField "sft.sftDiscoveryIntervalSeconds" (1 :: Int)
. setField "optSettings.setSftListAllServers" "enabled"
)
}
)
((HasCallStack => String -> App ()) -> App ())
-> (HasCallStack => String -> App ()) -> App ()
forall a b. (a -> b) -> a -> b
$ \String
domain -> do
user <- String -> CreateUser -> App Value
forall domain.
(HasCallStack, MakesValue domain) =>
domain -> CreateUser -> App Value
randomUser String
domain CreateUser
forall a. Default a => a
def
sftServersAll <-
retrying
(limitRetriesByCumulativeDelay 2_000_000 $ fullJitterBackoff 50_000)
(\RetryStatus
_ [Value]
xs -> let shouldRetry :: Bool
shouldRetry = [Value] -> Bool
forall a. [a] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [Value]
xs in Bool -> App Bool
forall a. a -> App a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Bool
shouldRetry)
$ \RetryStatus
_ -> do
resp <- Value -> App Response
forall dom. (HasCallStack, MakesValue dom) => dom -> App Response
getCallsConfigV2 Value
user
resp.json %. "sft_servers_all" & asList
when (null sftServersAll) $ assertFailure "sft_servers_all empty"
for_ sftServersAll $ \Value
s -> do
cred <- Value
s Value -> String -> App Value
forall a. (HasCallStack, MakesValue a) => a -> String -> App Value
%. String
"credential" App Value -> (App Value -> App String) -> App String
forall a b. a -> (a -> b) -> b
& App Value -> App String
forall a. (HasCallStack, MakesValue a) => a -> App String
asString
when (null cred) $ assertFailure "credential missing"
usr <- s %. "username" & asString
let parts = String -> String -> [String]
forall a. Eq a => [a] -> [a] -> [[a]]
splitOn String
"." String
usr
when (length parts /= 5) $ assertFailure "username should have 5 parts"
when (take 2 (head parts) /= "d=") $ assertFailure "missing expiry time identifier"
when (take 2 (parts !! 1) /= "v=") $ assertFailure "missing version identifier"
when (take 2 (parts !! 2) /= "k=") $ assertFailure "missing key ID identifier"
when (take 2 (parts !! 3) /= "s=") $ assertFailure "missing federation identifier"
when (take 2 (parts !! 4) /= "r=") $ assertFailure "missing random data identifier"
for_ parts $ \String
part -> Bool -> App () -> App ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (String -> Int
forall a. [a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length String
part Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Int
3) (App () -> App ()) -> App () -> App ()
forall a b. (a -> b) -> a -> b
$ String -> App ()
forall a. HasCallStack => String -> App a
assertFailure (String
"value missing for " String -> String -> String
forall a. Semigroup a => a -> a -> a
<> String
part)
testSFTNoCredentials :: (HasCallStack) => App ()
testSFTNoCredentials :: HasCallStack => App ()
testSFTNoCredentials = ServiceOverrides -> (HasCallStack => String -> App ()) -> App ()
forall a.
HasCallStack =>
ServiceOverrides -> (HasCallStack => String -> App a) -> App a
withModifiedBackend
( ServiceOverrides
forall a. Default a => a
def
{ brigCfg =
( setField "sft.sftBaseDomain" "integration-tests.zinfra.io"
. setField "optSettings.setSftListAllServers" "enabled"
)
}
)
((HasCallStack => String -> App ()) -> App ())
-> (HasCallStack => String -> App ()) -> App ()
forall a b. (a -> b) -> a -> b
$ \String
domain -> do
user <- String -> CreateUser -> App Value
forall domain.
(HasCallStack, MakesValue domain) =>
domain -> CreateUser -> App Value
randomUser String
domain CreateUser
forall a. Default a => a
def
bindResponse (getCallsConfigV2 user) \Response
resp -> do
sftServersAll <- Response
resp.json App Value -> String -> App Value
forall a. (HasCallStack, MakesValue a) => a -> String -> App Value
%. String
"sft_servers_all" App Value -> (App Value -> App [Value]) -> App [Value]
forall a b. a -> (a -> b) -> b
& App Value -> App [Value]
forall a. (HasCallStack, MakesValue a) => a -> App [Value]
asList
when (null sftServersAll) $ assertFailure "sft_servers_all missing"
for_ sftServersAll $ \Value
s -> do
credM <- Value -> String -> App (Maybe Value)
forall a.
(HasCallStack, MakesValue a) =>
a -> String -> App (Maybe Value)
lookupField Value
s String
"credential"
when (isJust credM) $ assertFailure "should not generate credential"
usrM <- lookupField s "username"
when (isJust usrM) $ assertFailure "should not generate username"
testSFTFederation :: (HasCallStack) => App ()
testSFTFederation :: HasCallStack => App ()
testSFTFederation = do
ServiceOverrides -> (HasCallStack => String -> App ()) -> App ()
forall a.
HasCallStack =>
ServiceOverrides -> (HasCallStack => String -> App a) -> App a
withModifiedBackend
( ServiceOverrides
forall a. Default a => a
def
{ brigCfg =
( setField "sft.sftBaseDomain" "integration-tests.zinfra.io"
. removeField "multiSFT"
)
}
)
((HasCallStack => String -> App ()) -> App ())
-> (HasCallStack => String -> App ()) -> App ()
forall a b. (a -> b) -> a -> b
$ \String
domain -> do
user <- String -> CreateUser -> App Value
forall domain.
(HasCallStack, MakesValue domain) =>
domain -> CreateUser -> App Value
randomUser String
domain CreateUser
forall a. Default a => a
def
bindResponse (getCallsConfigV2 user) \Response
resp -> do
isFederatingM <- App Value -> String -> App (Maybe Value)
forall a.
(HasCallStack, MakesValue a) =>
a -> String -> App (Maybe Value)
lookupField Response
resp.json String
"is_federating"
when (isJust isFederatingM) $ assertFailure "is_federating should not be present"
ServiceOverrides -> (HasCallStack => String -> App ()) -> App ()
forall a.
HasCallStack =>
ServiceOverrides -> (HasCallStack => String -> App a) -> App a
withModifiedBackend
( ServiceOverrides
forall a. Default a => a
def
{ brigCfg =
( setField "sft.sftBaseDomain" "integration-tests.zinfra.io"
. setField "multiSFT" True
)
}
)
((HasCallStack => String -> App ()) -> App ())
-> (HasCallStack => String -> App ()) -> App ()
forall a b. (a -> b) -> a -> b
$ \String
domain -> do
user <- String -> CreateUser -> App Value
forall domain.
(HasCallStack, MakesValue domain) =>
domain -> CreateUser -> App Value
randomUser String
domain CreateUser
forall a. Default a => a
def
bindResponse (getCallsConfigV2 user) \Response
resp -> do
isFederating <-
App Bool -> (Value -> App Bool) -> Maybe Value -> App Bool
forall b a. b -> (a -> b) -> Maybe a -> b
maybe (String -> App Bool
forall a. HasCallStack => String -> App a
assertFailure String
"is_federating missing") Value -> App Bool
forall a. (HasCallStack, MakesValue a) => a -> App Bool
asBool
(Maybe Value -> App Bool) -> App (Maybe Value) -> App Bool
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< App Value -> String -> App (Maybe Value)
forall a.
(HasCallStack, MakesValue a) =>
a -> String -> App (Maybe Value)
lookupField Response
resp.json String
"is_federating"
unless isFederating $ assertFailure "is_federating should be true"
ServiceOverrides -> (HasCallStack => String -> App ()) -> App ()
forall a.
HasCallStack =>
ServiceOverrides -> (HasCallStack => String -> App a) -> App a
withModifiedBackend
( ServiceOverrides
forall a. Default a => a
def
{ brigCfg =
( setField "sft.sftBaseDomain" "integration-tests.zinfra.io"
. setField "multiSFT" False
)
}
)
((HasCallStack => String -> App ()) -> App ())
-> (HasCallStack => String -> App ()) -> App ()
forall a b. (a -> b) -> a -> b
$ \String
domain -> do
user <- String -> CreateUser -> App Value
forall domain.
(HasCallStack, MakesValue domain) =>
domain -> CreateUser -> App Value
randomUser String
domain CreateUser
forall a. Default a => a
def
bindResponse (getCallsConfigV2 user) \Response
resp -> do
isFederating <-
App Bool -> (Value -> App Bool) -> Maybe Value -> App Bool
forall b a. b -> (a -> b) -> Maybe a -> b
maybe (String -> App Bool
forall a. HasCallStack => String -> App a
assertFailure String
"is_federating missing") Value -> App Bool
forall a. (HasCallStack, MakesValue a) => a -> App Bool
asBool
(Maybe Value -> App Bool) -> App (Maybe Value) -> App Bool
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< App Value -> String -> App (Maybe Value)
forall a.
(HasCallStack, MakesValue a) =>
a -> String -> App (Maybe Value)
lookupField Response
resp.json String
"is_federating"
when isFederating $ assertFailure "is_federating should be false"
testDeleteEmail :: (HasCallStack) => App ()
testDeleteEmail :: HasCallStack => App ()
testDeleteEmail = do
(owner, tid, [usr]) <- Domain -> Int -> App (Value, String, [Value])
forall domain.
(HasCallStack, MakesValue domain) =>
domain -> Int -> App (Value, String, [Value])
createTeam Domain
OwnDomain Int
2
putSelf usr (PutSelf Nothing Nothing (Just "Alice") Nothing) >>= assertSuccess
email <- getSelf usr >>= getJSON 200 >>= (%. "email") >>= asString
let associateUsrWithSSO :: (HasCallStack) => App ()
associateUsrWithSSO = do
App Response -> App ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void (App Response -> App ()) -> App Response -> App ()
forall a b. (a -> b) -> a -> b
$ Value -> String -> String -> String -> App Response
forall domain team.
(HasCallStack, MakesValue domain, MakesValue team) =>
domain -> team -> String -> String -> App Response
setTeamFeatureStatus Value
owner String
tid String
"sso" String
"enabled"
Value -> App Response
forall dom. (HasCallStack, MakesValue dom) => dom -> App Response
registerTestIdPWithMeta Value
owner App Response -> (Response -> App ()) -> App ()
forall a b. App a -> (a -> App b) -> App b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= HasCallStack => Response -> App ()
Response -> App ()
assertSuccess
tok <- Value -> CreateScimToken -> App Response
forall caller.
(HasCallStack, MakesValue caller) =>
caller -> CreateScimToken -> App Response
createScimTokenV6 Value
owner CreateScimToken
forall a. Default a => a
def App Response -> (Response -> App Value) -> App Value
forall a b. App a -> (a -> App b) -> App b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= HasCallStack => Int -> Response -> App Value
Int -> Response -> App Value
getJSON Int
200 App Value -> (Value -> App Value) -> App Value
forall a b. App a -> (a -> App b) -> App b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= (Value -> String -> App Value
forall a. (HasCallStack, MakesValue a) => a -> String -> App Value
%. String
"token") App Value -> (Value -> App String) -> App String
forall a b. App a -> (a -> App b) -> App b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Value -> App String
forall a. (HasCallStack, MakesValue a) => a -> App String
asString
void $ findUsersByExternalId owner tok email
searchShouldBe :: (HasCallStack) => String -> App ()
searchShouldBe String
expected = do
Domain -> App ()
forall domain.
(HasCallStack, MakesValue domain) =>
domain -> App ()
BrigI.refreshIndex Domain
OwnDomain
App Response -> (Response -> App ()) -> App ()
forall a.
HasCallStack =>
App Response -> (Response -> App a) -> App a
bindResponse (Value -> String -> App Response
forall user.
(HasCallStack, MakesValue user) =>
user -> String -> App Response
BrigP.searchTeamWithSearchTerm Value
owner String
email) ((Response -> App ()) -> App ()) -> (Response -> App ()) -> App ()
forall a b. (a -> b) -> a -> b
$ \Response
resp -> do
Response
resp.status Int -> Int -> App ()
forall a. (MakesValue a, HasCallStack) => a -> Int -> App ()
`shouldMatchInt` Int
200
numDocs <- [Value] -> Int
forall a. [a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length ([Value] -> Int) -> App [Value] -> App Int
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Response
resp.json App Value -> String -> App Value
forall a. (HasCallStack, MakesValue a) => a -> String -> App Value
%. String
"documents" App Value -> (Value -> App [Value]) -> App [Value]
forall a b. App a -> (a -> App b) -> App b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Value -> App [Value]
forall a. (HasCallStack, MakesValue a) => a -> App [Value]
asList)
case expected of
String
"empty" -> Int
numDocs Int -> Int -> App ()
forall a. (MakesValue a, HasCallStack) => a -> Int -> App ()
`shouldMatchInt` Int
0
String
"non-empty" -> Int
numDocs Int -> Int -> App ()
forall a. (MakesValue a, HasCallStack) => a -> Int -> App ()
`shouldMatchInt` Int
1
deleteSelfEmail usr >>= assertStatus 403
searchShouldBe "non-empty"
associateUsrWithSSO
deleteSelfEmail usr >>= assertSuccess
searchShouldBe "empty"