module Test.FeatureFlags.User where
import qualified API.BrigInternal as I
import API.Galley
import qualified API.GalleyInternal as I
import SetupHelpers
import Testlib.Prelude
testFeatureConferenceCallingForUser :: App ()
testFeatureConferenceCallingForUser :: App ()
testFeatureConferenceCallingForUser = do
(alice, tid, _) <- Domain -> Int -> App (Value, String, [Value])
forall domain.
(HasCallStack, MakesValue domain) =>
domain -> Int -> App (Value, String, [Value])
createTeam Domain
OwnDomain Int
0
bob <- randomUser OwnDomain def
let featureName = String
"conferenceCalling"
let patch =
[Pair] -> Value
object
[ String
"lockStatus" String -> String -> Pair
forall a. ToJSON a => String -> a -> Pair
.= String
"unlocked",
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
"useSFTForOneToOneCalls" String -> Bool -> Pair
forall a. ToJSON a => String -> a -> Pair
.= Bool
True]
]
assertSuccess =<< I.patchTeamFeatureConfig OwnDomain tid featureName patch
for_ [alice, bob] $ \Value
u -> do
App ByteString -> App ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void
(App ByteString -> App ()) -> App ByteString -> App ()
forall a b. (a -> b) -> a -> b
$ Value -> String -> Value -> App Response
forall user config.
(HasCallStack, MakesValue user, MakesValue config) =>
user -> String -> config -> App Response
I.putFeatureForUser
Value
u
String
featureName
( [Pair] -> Value
object
[ String
"status" String -> String -> Pair
forall a. ToJSON a => String -> a -> Pair
.= String
"disabled"
]
)
App Response -> (Response -> App ByteString) -> App ByteString
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 ByteString
Int -> Response -> App ByteString
getBody Int
200
Value -> String -> App Response
forall user.
(HasCallStack, MakesValue user) =>
user -> String -> App Response
I.getFeatureForUser Value
u String
featureName 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
200
config <- Response
resp.json
config %. "status" `shouldMatch` "disabled"
config %. "config.useSFTForOneToOneCalls" `shouldMatch` False
do
getFeaturesForUser alice `bindResponse` \Response
resp -> do
Response
resp.status Int -> Int -> App ()
forall a. (MakesValue a, HasCallStack) => a -> Int -> App ()
`shouldMatchInt` Int
200
config <- Response
resp.json App Value -> String -> App Value
forall a. (HasCallStack, MakesValue a) => a -> String -> App Value
%. String
featureName
config %. "status" `shouldMatch` "enabled"
config %. "config.useSFTForOneToOneCalls" `shouldMatch` True
do
void $ I.deleteFeatureForUser alice featureName >>= getBody 200
getFeaturesForUser alice `bindResponse` \Response
resp -> do
Response
resp.status Int -> Int -> App ()
forall a. (MakesValue a, HasCallStack) => a -> Int -> App ()
`shouldMatchInt` Int
200
config <- Response
resp.json App Value -> String -> App Value
forall a. (HasCallStack, MakesValue a) => a -> String -> App Value
%. String
featureName
config %. "status" `shouldMatch` "enabled"
config %. "config.useSFTForOneToOneCalls" `shouldMatch` True
do
getFeaturesForUser bob `bindResponse` \Response
resp -> do
Response
resp.status Int -> Int -> App ()
forall a. (MakesValue a, HasCallStack) => a -> Int -> App ()
`shouldMatchInt` Int
200
config <- Response
resp.json App Value -> String -> App Value
forall a. (HasCallStack, MakesValue a) => a -> String -> App Value
%. String
featureName
config %. "status" `shouldMatch` "disabled"
config %. "config.useSFTForOneToOneCalls" `shouldMatch` False
do
void $ I.deleteFeatureForUser bob featureName >>= getBody 200
getFeaturesForUser bob `bindResponse` \Response
resp -> do
Response
resp.status Int -> Int -> App ()
forall a. (MakesValue a, HasCallStack) => a -> Int -> App ()
`shouldMatchInt` Int
200
config <- Response
resp.json App Value -> String -> App Value
forall a. (HasCallStack, MakesValue a) => a -> String -> App Value
%. String
featureName
config %. "status" `shouldMatch` "disabled"
config %. "config.useSFTForOneToOneCalls" `shouldMatch` False