module Test.FeatureFlags.LegalHold where
import qualified API.Galley as Public
import qualified API.GalleyInternal as Internal
import Control.Monad.Codensity (Codensity (runCodensity))
import Control.Monad.Reader
import SetupHelpers
import Test.FeatureFlags.Util
import Testlib.Prelude
import Testlib.ResourcePool (acquireResources)
testLegalholdDisabledByDefault :: (HasCallStack) => App ()
testLegalholdDisabledByDefault :: HasCallStack => App ()
testLegalholdDisabledByDefault = do
let put :: domain -> team -> a -> App ()
put domain
uid team
tid a
st = domain -> team -> String -> Value -> App Response
forall domain team featureName payload.
(HasCallStack, MakesValue domain, MakesValue team,
MakesValue featureName, MakesValue payload) =>
domain -> team -> featureName -> payload -> App Response
Internal.setTeamFeatureConfig domain
uid team
tid String
"legalhold" ([Pair] -> Value
object [String
"status" String -> a -> Pair
forall a. ToJSON a => String -> a -> Pair
.= a
st]) 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
let patch :: domain -> team -> String -> App ()
patch domain
uid team
tid String
st = domain -> team -> String -> String -> App Response
forall domain team.
(HasCallStack, MakesValue domain, MakesValue team) =>
domain -> team -> String -> String -> App Response
Internal.setTeamFeatureStatus domain
uid team
tid String
"legalhold" String
st 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
[Value -> String -> String -> App ()]
-> ((Value -> String -> String -> App ()) -> App ()) -> App ()
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
t a -> (a -> m b) -> m ()
forM_ [Value -> String -> String -> App ()
forall {domain} {team} {a}.
(MakesValue domain, MakesValue team, ToJSON a) =>
domain -> team -> a -> App ()
put, Value -> String -> String -> App ()
forall {domain} {team}.
(MakesValue domain, MakesValue team) =>
domain -> team -> String -> App ()
patch] (((Value -> String -> String -> App ()) -> App ()) -> App ())
-> ((Value -> String -> String -> App ()) -> App ()) -> App ()
forall a b. (a -> b) -> a -> b
$ \Value -> String -> String -> App ()
setFeatureStatus -> do
ServiceOverrides -> (HasCallStack => String -> App ()) -> App ()
forall a.
HasCallStack =>
ServiceOverrides -> (HasCallStack => String -> App a) -> App a
withModifiedBackend
ServiceOverrides
forall a. Default a => a
def {galleyCfg = setField "settings.featureFlags.legalhold" "disabled-by-default"}
((HasCallStack => String -> App ()) -> App ())
-> (HasCallStack => String -> App ()) -> App ()
forall a b. (a -> b) -> a -> b
$ \String
domain -> do
(Value
owner, String
tid, Value
m : [Value]
_) <- String -> Int -> App (Value, String, [Value])
forall domain.
(HasCallStack, MakesValue domain) =>
domain -> Int -> App (Value, String, [Value])
createTeam String
domain Int
2
Value
nonMember <- String -> CreateUser -> App Value
forall domain.
(HasCallStack, MakesValue domain) =>
domain -> CreateUser -> App Value
randomUser String
domain CreateUser
forall a. Default a => a
def
HasCallStack => Response -> App ()
Response -> App ()
assertForbidden (Response -> App ()) -> App Response -> App ()
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< Value -> String -> String -> App Response
forall user tid.
(HasCallStack, MakesValue user, MakesValue tid) =>
user -> tid -> String -> App Response
Public.getTeamFeature Value
nonMember String
tid String
"legalhold"
String -> Value -> String -> Value -> App ()
forall user tid.
(HasCallStack, MakesValue user, MakesValue tid) =>
String -> user -> tid -> Value -> App ()
checkFeature String
"legalhold" Value
m String
tid Value
disabled
Value -> String -> String -> App ()
setFeatureStatus Value
owner String
tid String
"enabled"
String -> Value -> String -> Value -> App ()
forall user tid.
(HasCallStack, MakesValue user, MakesValue tid) =>
String -> user -> tid -> Value -> App ()
checkFeature String
"legalhold" Value
owner String
tid Value
enabled
Value -> String -> String -> App ()
setFeatureStatus Value
owner String
tid String
"disabled"
String -> Value -> String -> Value -> App ()
forall user tid.
(HasCallStack, MakesValue user, MakesValue tid) =>
String -> user -> tid -> Value -> App ()
checkFeature String
"legalhold" Value
owner String
tid Value
disabled
testLegalholdDisabledPermanently :: (HasCallStack) => App ()
testLegalholdDisabledPermanently :: HasCallStack => App ()
testLegalholdDisabledPermanently = do
let cfgLhDisabledPermanently :: ServiceOverrides
cfgLhDisabledPermanently =
ServiceOverrides
forall a. Default a => a
def
{ galleyCfg = setField "settings.featureFlags.legalhold" "disabled-permanently"
}
cfgLhDisabledByDefault :: ServiceOverrides
cfgLhDisabledByDefault =
ServiceOverrides
forall a. Default a => a
def
{ galleyCfg = setField "settings.featureFlags.legalhold" "disabled-by-default"
}
ResourcePool BackendResource
resourcePool <- (Env -> ResourcePool BackendResource)
-> App (ResourcePool BackendResource)
forall r (m :: * -> *) a. MonadReader r m => (r -> a) -> m a
asks (.resourcePool)
Codensity App [BackendResource]
-> forall b. ([BackendResource] -> App b) -> App b
forall k (m :: k -> *) a.
Codensity m a -> forall (b :: k). (a -> m b) -> m b
runCodensity (Int
-> ResourcePool BackendResource -> Codensity App [BackendResource]
forall (m :: * -> *) a.
(Ord a, MonadIO m, MonadMask m, HasCallStack) =>
Int -> ResourcePool a -> Codensity m [a]
acquireResources Int
1 ResourcePool BackendResource
resourcePool) (([BackendResource] -> App ()) -> App ())
-> ([BackendResource] -> App ()) -> App ()
forall a b. (a -> b) -> a -> b
$ \[BackendResource
testBackend] -> do
let domain :: String
domain = BackendResource
testBackend.berDomain
Codensity App String -> forall b. (String -> App b) -> App b
forall k (m :: k -> *) a.
Codensity m a -> forall (b :: k). (a -> m b) -> m b
runCodensity (HasCallStack =>
BackendResource -> ServiceOverrides -> Codensity App String
BackendResource -> ServiceOverrides -> Codensity App String
startDynamicBackend BackendResource
testBackend ServiceOverrides
cfgLhDisabledPermanently) ((String -> App ()) -> App ()) -> (String -> App ()) -> App ()
forall a b. (a -> b) -> a -> b
$ \String
_ -> do
(Value
owner, String
tid, [Value]
_) <- String -> Int -> App (Value, String, [Value])
forall domain.
(HasCallStack, MakesValue domain) =>
domain -> Int -> App (Value, String, [Value])
createTeam String
domain Int
1
String -> Value -> String -> Value -> App ()
forall user tid.
(HasCallStack, MakesValue user, MakesValue tid) =>
String -> user -> tid -> Value -> App ()
checkFeature String
"legalhold" Value
owner String
tid Value
disabled
HasCallStack => Int -> Response -> App ()
Int -> Response -> App ()
assertStatus Int
403 (Response -> App ()) -> App Response -> App ()
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< String -> String -> String -> String -> App Response
forall domain team.
(HasCallStack, MakesValue domain, MakesValue team) =>
domain -> team -> String -> String -> App Response
Internal.setTeamFeatureStatus String
domain String
tid String
"legalhold" String
"enabled"
HasCallStack => Int -> Response -> App ()
Int -> Response -> App ()
assertStatus Int
403 (Response -> App ()) -> App Response -> App ()
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< String -> String -> String -> Value -> App Response
forall domain team featureName payload.
(HasCallStack, MakesValue domain, MakesValue team,
MakesValue featureName, MakesValue payload) =>
domain -> team -> featureName -> payload -> App Response
Internal.setTeamFeatureConfig String
domain String
tid String
"legalhold" ([Pair] -> Value
object [String
"status" String -> String -> Pair
forall a. ToJSON a => String -> a -> Pair
.= String
"enabled"])
(Value
owner, String
tid) <- Codensity App String -> forall b. (String -> App b) -> App b
forall k (m :: k -> *) a.
Codensity m a -> forall (b :: k). (a -> m b) -> m b
runCodensity (HasCallStack =>
BackendResource -> ServiceOverrides -> Codensity App String
BackendResource -> ServiceOverrides -> Codensity App String
startDynamicBackend BackendResource
testBackend ServiceOverrides
cfgLhDisabledByDefault) ((String -> App (Value, String)) -> App (Value, String))
-> (String -> App (Value, String)) -> App (Value, String)
forall a b. (a -> b) -> a -> b
$ \String
_ -> do
(Value
owner, String
tid, [Value]
_) <- String -> Int -> App (Value, String, [Value])
forall domain.
(HasCallStack, MakesValue domain) =>
domain -> Int -> App (Value, String, [Value])
createTeam String
domain Int
1
String -> Value -> String -> Value -> App ()
forall user tid.
(HasCallStack, MakesValue user, MakesValue tid) =>
String -> user -> tid -> Value -> App ()
checkFeature String
"legalhold" Value
owner String
tid Value
disabled
HasCallStack => Response -> App ()
Response -> App ()
assertSuccess (Response -> App ()) -> App Response -> App ()
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< String -> String -> String -> String -> App Response
forall domain team.
(HasCallStack, MakesValue domain, MakesValue team) =>
domain -> team -> String -> String -> App Response
Internal.setTeamFeatureStatus String
domain String
tid String
"legalhold" String
"enabled"
String -> Value -> String -> Value -> App ()
forall user tid.
(HasCallStack, MakesValue user, MakesValue tid) =>
String -> user -> tid -> Value -> App ()
checkFeature String
"legalhold" Value
owner String
tid Value
enabled
(Value, String) -> App (Value, String)
forall a. a -> App a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Value
owner, String
tid)
Codensity App String -> forall b. (String -> App b) -> App b
forall k (m :: k -> *) a.
Codensity m a -> forall (b :: k). (a -> m b) -> m b
runCodensity (HasCallStack =>
BackendResource -> ServiceOverrides -> Codensity App String
BackendResource -> ServiceOverrides -> Codensity App String
startDynamicBackend BackendResource
testBackend ServiceOverrides
cfgLhDisabledPermanently) ((String -> App ()) -> App ()) -> (String -> App ()) -> App ()
forall a b. (a -> b) -> a -> b
$ \String
_ -> do
String -> Value -> String -> Value -> App ()
forall user tid.
(HasCallStack, MakesValue user, MakesValue tid) =>
String -> user -> tid -> Value -> App ()
checkFeature String
"legalhold" Value
owner String
tid Value
disabled
testLegalholdWhitelistTeamsAndImplicitConsent :: (HasCallStack) => App ()
testLegalholdWhitelistTeamsAndImplicitConsent :: HasCallStack => App ()
testLegalholdWhitelistTeamsAndImplicitConsent = do
let cfgLhWhitelistTeamsAndImplicitConsent :: ServiceOverrides
cfgLhWhitelistTeamsAndImplicitConsent =
ServiceOverrides
forall a. Default a => a
def
{ galleyCfg = setField "settings.featureFlags.legalhold" "whitelist-teams-and-implicit-consent"
}
cfgLhDisabledByDefault :: ServiceOverrides
cfgLhDisabledByDefault =
ServiceOverrides
forall a. Default a => a
def
{ galleyCfg = setField "settings.featureFlags.legalhold" "disabled-by-default"
}
ResourcePool BackendResource
resourcePool <- (Env -> ResourcePool BackendResource)
-> App (ResourcePool BackendResource)
forall r (m :: * -> *) a. MonadReader r m => (r -> a) -> m a
asks (.resourcePool)
Codensity App [BackendResource]
-> forall b. ([BackendResource] -> App b) -> App b
forall k (m :: k -> *) a.
Codensity m a -> forall (b :: k). (a -> m b) -> m b
runCodensity (Int
-> ResourcePool BackendResource -> Codensity App [BackendResource]
forall (m :: * -> *) a.
(Ord a, MonadIO m, MonadMask m, HasCallStack) =>
Int -> ResourcePool a -> Codensity m [a]
acquireResources Int
1 ResourcePool BackendResource
resourcePool) (([BackendResource] -> App ()) -> App ())
-> ([BackendResource] -> App ()) -> App ()
forall a b. (a -> b) -> a -> b
$ \[BackendResource
testBackend] -> do
let domain :: String
domain = BackendResource
testBackend.berDomain
(Value
owner, String
tid) <- Codensity App String -> forall b. (String -> App b) -> App b
forall k (m :: k -> *) a.
Codensity m a -> forall (b :: k). (a -> m b) -> m b
runCodensity (HasCallStack =>
BackendResource -> ServiceOverrides -> Codensity App String
BackendResource -> ServiceOverrides -> Codensity App String
startDynamicBackend BackendResource
testBackend ServiceOverrides
cfgLhWhitelistTeamsAndImplicitConsent) ((String -> App (Value, String)) -> App (Value, String))
-> (String -> App (Value, String)) -> App (Value, String)
forall a b. (a -> b) -> a -> b
$ \String
_ -> do
(Value
owner, String
tid, [Value]
_) <- String -> Int -> App (Value, String, [Value])
forall domain.
(HasCallStack, MakesValue domain) =>
domain -> Int -> App (Value, String, [Value])
createTeam String
domain Int
1
String -> Value -> String -> Value -> App ()
forall user tid.
(HasCallStack, MakesValue user, MakesValue tid) =>
String -> user -> tid -> Value -> App ()
checkFeature String
"legalhold" Value
owner String
tid Value
disabled
String -> Value -> App Response
forall uid tid.
(HasCallStack, MakesValue uid, MakesValue tid) =>
tid -> uid -> App Response
Internal.legalholdWhitelistTeam String
tid 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
String -> Value -> String -> Value -> App ()
forall user tid.
(HasCallStack, MakesValue user, MakesValue tid) =>
String -> user -> tid -> Value -> App ()
checkFeature String
"legalhold" Value
owner String
tid Value
enabled
HasCallStack => Int -> Response -> App ()
Int -> Response -> App ()
assertStatus Int
403 (Response -> App ()) -> App Response -> App ()
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< String -> String -> String -> String -> App Response
forall domain team.
(HasCallStack, MakesValue domain, MakesValue team) =>
domain -> team -> String -> String -> App Response
Internal.setTeamFeatureStatus String
domain String
tid String
"legalhold" String
"disabled"
HasCallStack => Int -> Response -> App ()
Int -> Response -> App ()
assertStatus Int
403 (Response -> App ()) -> App Response -> App ()
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< String -> String -> String -> Value -> App Response
forall domain team featureName payload.
(HasCallStack, MakesValue domain, MakesValue team,
MakesValue featureName, MakesValue payload) =>
domain -> team -> featureName -> payload -> App Response
Internal.setTeamFeatureConfig String
domain String
tid String
"legalhold" ([Pair] -> Value
object [String
"status" String -> String -> Pair
forall a. ToJSON a => String -> a -> Pair
.= String
"disabled"])
String -> Value -> String -> Value -> App ()
forall user tid.
(HasCallStack, MakesValue user, MakesValue tid) =>
String -> user -> tid -> Value -> App ()
checkFeature String
"legalhold" Value
owner String
tid Value
enabled
(Value, String) -> App (Value, String)
forall a. a -> App a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Value
owner, String
tid)
Codensity App String -> forall b. (String -> App b) -> App b
forall k (m :: k -> *) a.
Codensity m a -> forall (b :: k). (a -> m b) -> m b
runCodensity (HasCallStack =>
BackendResource -> ServiceOverrides -> Codensity App String
BackendResource -> ServiceOverrides -> Codensity App String
startDynamicBackend BackendResource
testBackend ServiceOverrides
cfgLhDisabledByDefault) ((String -> App ()) -> App ()) -> (String -> App ()) -> App ()
forall a b. (a -> b) -> a -> b
$ \String
_ -> do
String -> Value -> String -> Value -> App ()
forall user tid.
(HasCallStack, MakesValue user, MakesValue tid) =>
String -> user -> tid -> Value -> App ()
checkFeature String
"legalhold" Value
owner String
tid Value
disabled
HasCallStack => Response -> App ()
Response -> App ()
assertSuccess (Response -> App ()) -> App Response -> App ()
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< String -> String -> String -> String -> App Response
forall domain team.
(HasCallStack, MakesValue domain, MakesValue team) =>
domain -> team -> String -> String -> App Response
Internal.setTeamFeatureStatus String
domain String
tid String
"legalhold" String
"disabled"
String -> Value -> String -> Value -> App ()
forall user tid.
(HasCallStack, MakesValue user, MakesValue tid) =>
String -> user -> tid -> Value -> App ()
checkFeature String
"legalhold" Value
owner String
tid Value
disabled
Codensity App String -> forall b. (String -> App b) -> App b
forall k (m :: k -> *) a.
Codensity m a -> forall (b :: k). (a -> m b) -> m b
runCodensity (HasCallStack =>
BackendResource -> ServiceOverrides -> Codensity App String
BackendResource -> ServiceOverrides -> Codensity App String
startDynamicBackend BackendResource
testBackend ServiceOverrides
cfgLhWhitelistTeamsAndImplicitConsent) ((String -> App ()) -> App ()) -> (String -> App ()) -> App ()
forall a b. (a -> b) -> a -> b
$ \String
_ -> do
String -> Value -> String -> Value -> App ()
forall user tid.
(HasCallStack, MakesValue user, MakesValue tid) =>
String -> user -> tid -> Value -> App ()
checkFeature String
"legalhold" Value
owner String
tid Value
enabled
testExposeInvitationURLsToTeamAdminConfig :: (HasCallStack) => App ()
testExposeInvitationURLsToTeamAdminConfig :: HasCallStack => App ()
testExposeInvitationURLsToTeamAdminConfig = do
let cfgExposeInvitationURLsTeamAllowlist :: b -> ServiceOverrides
cfgExposeInvitationURLsTeamAllowlist b
tids =
ServiceOverrides
forall a. Default a => a
def
{ galleyCfg = setField "settings.exposeInvitationURLsTeamAllowlist" tids
}
ResourcePool BackendResource
resourcePool <- (Env -> ResourcePool BackendResource)
-> App (ResourcePool BackendResource)
forall r (m :: * -> *) a. MonadReader r m => (r -> a) -> m a
asks (.resourcePool)
Codensity App [BackendResource]
-> forall b. ([BackendResource] -> App b) -> App b
forall k (m :: k -> *) a.
Codensity m a -> forall (b :: k). (a -> m b) -> m b
runCodensity (Int
-> ResourcePool BackendResource -> Codensity App [BackendResource]
forall (m :: * -> *) a.
(Ord a, MonadIO m, MonadMask m, HasCallStack) =>
Int -> ResourcePool a -> Codensity m [a]
acquireResources Int
1 ResourcePool BackendResource
resourcePool) (([BackendResource] -> App ()) -> App ())
-> ([BackendResource] -> App ()) -> App ()
forall a b. (a -> b) -> a -> b
$ \[BackendResource
testBackend] -> do
let domain :: String
domain = BackendResource
testBackend.berDomain
testNoAllowlistEntry :: (HasCallStack) => App (Value, String)
testNoAllowlistEntry :: HasCallStack => App (Value, String)
testNoAllowlistEntry = Codensity App String -> forall b. (String -> App b) -> App b
forall k (m :: k -> *) a.
Codensity m a -> forall (b :: k). (a -> m b) -> m b
runCodensity (HasCallStack =>
BackendResource -> ServiceOverrides -> Codensity App String
BackendResource -> ServiceOverrides -> Codensity App String
startDynamicBackend BackendResource
testBackend (ServiceOverrides -> Codensity App String)
-> ServiceOverrides -> Codensity App String
forall a b. (a -> b) -> a -> b
$ [String] -> ServiceOverrides
forall {b}. ToJSON b => b -> ServiceOverrides
cfgExposeInvitationURLsTeamAllowlist ([] :: [String])) ((String -> App (Value, String)) -> App (Value, String))
-> (String -> App (Value, String)) -> App (Value, String)
forall a b. (a -> b) -> a -> b
$ \String
_ -> do
(Value
owner, String
tid, [Value]
_) <- String -> Int -> App (Value, String, [Value])
forall domain.
(HasCallStack, MakesValue domain) =>
domain -> Int -> App (Value, String, [Value])
createTeam String
domain Int
1
String -> Value -> String -> Value -> App ()
forall user tid.
(HasCallStack, MakesValue user, MakesValue tid) =>
String -> user -> tid -> Value -> App ()
checkFeature String
"exposeInvitationURLsToTeamAdmin" Value
owner String
tid Value
disabledLocked
HasCallStack => Response -> App ()
Response -> App ()
assertSuccess (Response -> App ()) -> App Response -> App ()
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< String -> String -> String -> String -> App Response
forall domain team.
(HasCallStack, MakesValue domain, MakesValue team) =>
domain -> team -> String -> String -> App Response
Internal.setTeamFeatureStatus String
domain String
tid String
"exposeInvitationURLsToTeamAdmin" String
"enabled"
String -> Value -> String -> Value -> App ()
forall user tid.
(HasCallStack, MakesValue user, MakesValue tid) =>
String -> user -> tid -> Value -> App ()
checkFeature String
"exposeInvitationURLsToTeamAdmin" Value
owner String
tid Value
disabledLocked
HasCallStack => Int -> Response -> App ()
Int -> Response -> App ()
assertStatus Int
409 (Response -> App ()) -> App Response -> App ()
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< Value -> String -> String -> Value -> App Response
forall domain team featureName payload.
(HasCallStack, MakesValue domain, MakesValue team,
MakesValue featureName, MakesValue payload) =>
domain -> team -> featureName -> payload -> App Response
Public.setTeamFeatureConfig Value
owner String
tid String
"exposeInvitationURLsToTeamAdmin" ([Pair] -> Value
object [String
"status" String -> String -> Pair
forall a. ToJSON a => String -> a -> Pair
.= String
"enabled"])
HasCallStack => Response -> App ()
Response -> App ()
assertSuccess (Response -> App ()) -> App Response -> App ()
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< String -> String -> String -> String -> App Response
forall domain team.
(HasCallStack, MakesValue domain, MakesValue team) =>
domain -> team -> String -> String -> App Response
Internal.setTeamFeatureStatus String
domain String
tid String
"exposeInvitationURLsToTeamAdmin" String
"disabled"
(Value, String) -> App (Value, String)
forall a. a -> App a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Value
owner, String
tid)
(Value
owner, String
tid) <- App (Value, String)
HasCallStack => App (Value, String)
testNoAllowlistEntry
Codensity App String -> forall b. (String -> App b) -> App b
forall k (m :: k -> *) a.
Codensity m a -> forall (b :: k). (a -> m b) -> m b
runCodensity (HasCallStack =>
BackendResource -> ServiceOverrides -> Codensity App String
BackendResource -> ServiceOverrides -> Codensity App String
startDynamicBackend BackendResource
testBackend (ServiceOverrides -> Codensity App String)
-> ServiceOverrides -> Codensity App String
forall a b. (a -> b) -> a -> b
$ [String] -> ServiceOverrides
forall {b}. ToJSON b => b -> ServiceOverrides
cfgExposeInvitationURLsTeamAllowlist [String
tid]) ((String -> App ()) -> App ()) -> (String -> App ()) -> App ()
forall a b. (a -> b) -> a -> b
$ \String
_ -> do
String -> Value -> String -> Value -> App ()
forall user tid.
(HasCallStack, MakesValue user, MakesValue tid) =>
String -> user -> tid -> Value -> App ()
checkFeature String
"exposeInvitationURLsToTeamAdmin" Value
owner String
tid Value
disabled
HasCallStack => Response -> App ()
Response -> App ()
assertSuccess (Response -> App ()) -> App Response -> App ()
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< String -> String -> String -> String -> App Response
forall domain team.
(HasCallStack, MakesValue domain, MakesValue team) =>
domain -> team -> String -> String -> App Response
Internal.setTeamFeatureStatus String
domain String
tid String
"exposeInvitationURLsToTeamAdmin" String
"enabled"
String -> Value -> String -> Value -> App ()
forall user tid.
(HasCallStack, MakesValue user, MakesValue tid) =>
String -> user -> tid -> Value -> App ()
checkFeature String
"exposeInvitationURLsToTeamAdmin" Value
owner String
tid Value
enabled
HasCallStack => Response -> App ()
Response -> App ()
assertSuccess (Response -> App ()) -> App Response -> App ()
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< String -> String -> String -> String -> App Response
forall domain team.
(HasCallStack, MakesValue domain, MakesValue team) =>
domain -> team -> String -> String -> App Response
Internal.setTeamFeatureStatus String
domain String
tid String
"exposeInvitationURLsToTeamAdmin" String
"disabled"
String -> Value -> String -> Value -> App ()
forall user tid.
(HasCallStack, MakesValue user, MakesValue tid) =>
String -> user -> tid -> Value -> App ()
checkFeature String
"exposeInvitationURLsToTeamAdmin" Value
owner String
tid Value
disabled
HasCallStack => Response -> App ()
Response -> App ()
assertSuccess (Response -> App ()) -> App Response -> App ()
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< String -> String -> String -> String -> App Response
forall domain team.
(HasCallStack, MakesValue domain, MakesValue team) =>
domain -> team -> String -> String -> App Response
Internal.setTeamFeatureStatus String
domain String
tid String
"exposeInvitationURLsToTeamAdmin" String
"enabled"
String -> Value -> String -> Value -> App ()
forall user tid.
(HasCallStack, MakesValue user, MakesValue tid) =>
String -> user -> tid -> Value -> App ()
checkFeature String
"exposeInvitationURLsToTeamAdmin" Value
owner String
tid Value
enabled
App (Value, String) -> App ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void App (Value, String)
HasCallStack => App (Value, String)
testNoAllowlistEntry