module Test.FeatureFlags.ConferenceCalling where

import Test.FeatureFlags.Util
import Testlib.Prelude

testPatchConferenceCalling :: (HasCallStack) => App ()
testPatchConferenceCalling :: HasCallStack => App ()
testPatchConferenceCalling = do
  Domain -> String -> Value -> App ()
forall domain.
(HasCallStack, MakesValue domain) =>
domain -> String -> Value -> App ()
checkPatch Domain
OwnDomain String
"conferenceCalling"
    (Value -> App ()) -> Value -> App ()
forall a b. (a -> b) -> a -> b
$ [Pair] -> Value
object [String
"lockStatus" String -> String -> Pair
forall a. ToJSON a => String -> a -> Pair
.= String
"locked"]
  Domain -> String -> Value -> App ()
forall domain.
(HasCallStack, MakesValue domain) =>
domain -> String -> Value -> App ()
checkPatch Domain
OwnDomain String
"conferenceCalling"
    (Value -> App ()) -> Value -> App ()
forall a b. (a -> b) -> a -> b
$ [Pair] -> Value
object [String
"status" String -> String -> Pair
forall a. ToJSON a => String -> a -> Pair
.= String
"disabled"]
  Domain -> String -> Value -> App ()
forall domain.
(HasCallStack, MakesValue domain) =>
domain -> String -> Value -> App ()
checkPatch Domain
OwnDomain String
"conferenceCalling"
    (Value -> App ()) -> Value -> App ()
forall a b. (a -> b) -> a -> b
$ [Pair] -> Value
object [String
"lockStatus" String -> String -> Pair
forall a. ToJSON a => String -> a -> Pair
.= String
"locked", String
"status" String -> String -> Pair
forall a. ToJSON a => String -> a -> Pair
.= String
"disabled"]
  Domain -> String -> Value -> App ()
forall domain.
(HasCallStack, MakesValue domain) =>
domain -> String -> Value -> App ()
checkPatch Domain
OwnDomain String
"conferenceCalling"
    (Value -> App ()) -> Value -> App ()
forall a b. (a -> b) -> a -> b
$ [Pair] -> Value
object
      [ String
"lockStatus" String -> String -> Pair
forall a. ToJSON a => String -> a -> Pair
.= String
"unlocked",
        String
"config" String -> Value -> Pair
forall a. ToJSON a => String -> a -> Pair
.= [Pair] -> Value
object [String
"useSFTForOneToOneCalls" String -> Value -> Pair
forall a. ToJSON a => String -> a -> Pair
.= Bool -> Value
forall a. ToJSON a => a -> Value
toJSON Bool
True]
      ]

testConferenceCalling :: (HasCallStack) => APIAccess -> App ()
testConferenceCalling :: HasCallStack => APIAccess -> App ()
testConferenceCalling APIAccess
access = do
  Domain -> APIAccess -> FeatureTests -> App ()
forall domain.
(HasCallStack, MakesValue domain) =>
domain -> APIAccess -> FeatureTests -> App ()
runFeatureTests Domain
OwnDomain APIAccess
access
    (FeatureTests -> App ()) -> FeatureTests -> App ()
forall a b. (a -> b) -> a -> b
$ String -> FeatureTests
mkFeatureTests String
"conferenceCalling"
    FeatureTests -> (FeatureTests -> FeatureTests) -> FeatureTests
forall a b. a -> (a -> b) -> b
& Value -> FeatureTests -> FeatureTests
addUpdate (ConfCalling -> Value
confCalling ConfCalling
forall a. Default a => a
def {sft = toJSON True})
    FeatureTests -> (FeatureTests -> FeatureTests) -> FeatureTests
forall a b. a -> (a -> b) -> b
& Value -> FeatureTests -> FeatureTests
addUpdate (ConfCalling -> Value
confCalling ConfCalling
forall a. Default a => a
def {sft = toJSON False})
    FeatureTests -> (FeatureTests -> FeatureTests) -> FeatureTests
forall a b. a -> (a -> b) -> b
& Value -> FeatureTests -> FeatureTests
addInvalidUpdate (ConfCalling -> Value
confCalling ConfCalling
forall a. Default a => a
def {sft = toJSON (0 :: Int)})