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
(Value
admin, String
tid, [Value]
_) <- String -> Int -> App (Value, String, [Value])
forall domain.
(HasCallStack, MakesValue domain) =>
domain -> Int -> App (Value, String, [Value])
createTeam String
domain Int
0
Value
expected <-
if Bool
isSet
then Value
setting Value -> (Value -> App Value) -> App Value
forall a b. a -> (a -> b) -> b
& String -> String -> Value -> App Value
forall a b.
(HasCallStack, MakesValue a, ToJSON b) =>
String -> b -> a -> App Value
setField String
"lockStatus" String
"locked" App Value -> (App Value -> App Value) -> App Value
forall a b. a -> (a -> b) -> b
& String -> String -> App Value -> App Value
forall a b.
(HasCallStack, MakesValue a, ToJSON b) =>
String -> b -> a -> App Value
setField String
"ttl" String
"unlimited"
else Value
defSetting Value -> (Value -> App Value) -> App Value
forall a b. a -> (a -> b) -> b
& String -> String -> Value -> App Value
forall a b.
(HasCallStack, MakesValue a, ToJSON b) =>
String -> b -> a -> App Value
setField String
"lockStatus" String
"locked" App Value -> (App Value -> App Value) -> App Value
forall a b. a -> (a -> b) -> b
& String -> String -> App Value -> App Value
forall a b.
(HasCallStack, MakesValue a, ToJSON b) =>
String -> b -> a -> App Value
setField String
"ttl" String
"unlimited"
String -> Value -> String -> Value -> App ()
forall user tid.
(HasCallStack, MakesValue user, MakesValue tid) =>
String -> user -> tid -> Value -> App ()
checkFeature String
"allowedGlobalOperations" Value
admin String
tid Value
expected
Value -> String -> String -> Value -> App Response
forall user team featureName payload.
(HasCallStack, MakesValue user, MakesValue team,
MakesValue featureName, MakesValue payload) =>
user -> team -> featureName -> payload -> App Response
Public.setTeamFeatureConfig Value
admin String
tid String
"allowedGlobalOperations" ([Pair] -> Value
object [String
"status" String -> String -> Pair
forall a. ToJSON a => String -> a -> Pair
.= String
"enabled"])
App Response -> (Response -> App ()) -> App ()
forall a.
HasCallStack =>
App Response -> (Response -> App a) -> App a
`bindResponse` \Response
resp -> do
Response
resp.status Int -> Int -> App ()
forall a. (MakesValue a, HasCallStack) => a -> Int -> App ()
`shouldMatchInt` Int
404
Request
req <- Value -> Service -> Versioned -> String -> App Request
forall user.
(HasCallStack, MakesValue user) =>
user -> Service -> Versioned -> String -> App Request
baseRequest Value
admin Service
Galley Versioned
Unversioned (String -> App Request) -> String -> App Request
forall a b. (a -> b) -> a -> b
$ [String] -> String
joinHttpPath [String
"i", String
"teams", String
tid, String
"features", String
"allowedGlobalOperations", String
"unlocked"]
App Response -> (Response -> App ()) -> App ()
forall a.
HasCallStack =>
App Response -> (Response -> App a) -> App a
bindResponse (String -> Request -> App Response
submit String
"PUT" (Request -> App Response) -> Request -> App Response
forall a b. (a -> b) -> a -> b
$ Request
req) ((Response -> App ()) -> App ()) -> (Response -> App ()) -> App ()
forall a b. (a -> b) -> a -> b
$ \Response
resp ->
Response
resp.status Int -> Int -> App ()
forall a. (MakesValue a, HasCallStack) => a -> Int -> App ()
`shouldMatchInt` Int
404
Value -> String -> String -> String -> App Response
forall domain team.
(HasCallStack, MakesValue domain, MakesValue team) =>
domain -> team -> String -> String -> App Response
Internal.setTeamFeatureStatus Value
admin String
tid String
"allowedGlobalOperations" String
"enabled"
App Response -> (Response -> App ()) -> App ()
forall a.
HasCallStack =>
App Response -> (Response -> App a) -> App a
`bindResponse` \Response
resp -> do
Response
resp.status Int -> Int -> App ()
forall a. (MakesValue a, HasCallStack) => a -> Int -> App ()
`shouldMatchInt` Int
404
Value
personalUser <- String -> CreateUser -> App Value
forall domain.
(HasCallStack, MakesValue domain) =>
domain -> CreateUser -> App Value
randomUser String
domain CreateUser
forall a. Default a => a
def
App Response -> (Response -> App ()) -> App ()
forall a.
HasCallStack =>
App Response -> (Response -> App a) -> App a
bindResponse (Value -> App Response
forall user.
(HasCallStack, MakesValue user) =>
user -> App Response
Public.getFeatureConfigs Value
personalUser) ((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
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