module Test.FeatureFlags.AllowedGlobalOperations where
import qualified API.Galley as Public
import qualified API.GalleyInternal as Internal
import SetupHelpers
import Test.FeatureFlags.Util
import Testlib.Prelude
testAllowedGlobalOperations :: (HasCallStack) => TaggedBool "isSet" -> App ()
testAllowedGlobalOperations :: HasCallStack => TaggedBool "isSet" -> App ()
testAllowedGlobalOperations (TaggedBool Bool
isSet) = do
let setting :: Value
setting =
[Pair] -> Value
object
[ String
"status" String -> String -> Pair
forall a. ToJSON a => String -> a -> Pair
.= String
"disabled",
String
"config"
String -> Value -> Pair
forall a. ToJSON a => String -> a -> Pair
.= [Pair] -> Value
object
[String
"mlsConversationReset" String -> Bool -> Pair
forall a. ToJSON a => String -> a -> Pair
.= Bool
True]
]
defSetting :: Value
defSetting =
[Pair] -> Value
object
[ String
"status" String -> String -> Pair
forall a. ToJSON a => String -> a -> Pair
.= String
"enabled",
String
"config"
String -> Value -> Pair
forall a. ToJSON a => String -> a -> Pair
.= [Pair] -> Value
object [String
"mlsConversationReset" String -> Bool -> Pair
forall a. ToJSON a => String -> a -> Pair
.= Bool
False]
]
let galleyConf :: ServiceOverrides
galleyConf =
if Bool
isSet
then ServiceOverrides
forall a. Default a => a
def {galleyCfg = setField "settings.featureFlags.allowedGlobalOperations" $ setting}
else ServiceOverrides
forall a. Default a => a
def {galleyCfg = removeField "settings.featureFlags.allowedGlobalOperations"}
ServiceOverrides -> (HasCallStack => String -> App ()) -> App ()
forall a.
HasCallStack =>
ServiceOverrides -> (HasCallStack => String -> App a) -> App a
withModifiedBackend ServiceOverrides
galleyConf
((HasCallStack => String -> App ()) -> App ())
-> (HasCallStack => String -> App ()) -> App ()
forall a b. (a -> b) -> a -> b
$ \String
domain -> do
(admin, tid, _) <- String -> Int -> App (Value, String, [Value])
forall domain.
(HasCallStack, MakesValue domain) =>
domain -> Int -> App (Value, String, [Value])
createTeam String
domain Int
0
expected <-
if isSet
then setting & setField "lockStatus" "locked" & setField "ttl" "unlimited"
else defSetting & setField "lockStatus" "locked" & setField "ttl" "unlimited"
checkFeature "allowedGlobalOperations" admin tid expected
Public.setTeamFeatureConfig admin tid "allowedGlobalOperations" (object ["status" .= "enabled"])
`bindResponse` \Response
resp -> do
Response
resp.status Int -> Int -> App ()
forall a. (MakesValue a, HasCallStack) => a -> Int -> App ()
`shouldMatchInt` Int
404
req <- baseRequest admin Galley Unversioned $ joinHttpPath ["i", "teams", tid, "features", "allowedGlobalOperations", "unlocked"]
bindResponse (submit "PUT" $ req) $ \Response
resp ->
Response
resp.status Int -> Int -> App ()
forall a. (MakesValue a, HasCallStack) => a -> Int -> App ()
`shouldMatchInt` Int
404
Internal.setTeamFeatureStatus admin tid "allowedGlobalOperations" "enabled"
`bindResponse` \Response
resp -> do
Response
resp.status Int -> Int -> App ()
forall a. (MakesValue a, HasCallStack) => a -> Int -> App ()
`shouldMatchInt` Int
404
personalUser <- randomUser domain def
bindResponse (Public.getFeatureConfigs personalUser) $ \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
"allowedGlobalOperations" App Value -> Value -> App ()
forall a b.
(MakesValue a, MakesValue b, HasCallStack) =>
a -> b -> App ()
`shouldMatch` Value
expected