module Test.FeatureFlags.CellsInternal where
import qualified API.GalleyInternal as Internal
import SetupHelpers
import Test.Cells (getMessage, watchCellsEventsForTeam)
import Test.FeatureFlags.Util
import Testlib.Prelude
testCellsInternalEvent :: (HasCallStack) => App ()
testCellsInternalEvent :: HasCallStack => App ()
testCellsInternalEvent = 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
q <- watchCellsEventsForTeam tid def
let quota = String
"234723984"
update = String -> String -> CellsInternalConfig -> Value
mkFt String
"enabled" String
"unlocked" CellsInternalConfig
defConf {quota}
setFeature InternalAPI alice tid "cellsInternal" update >>= assertSuccess
event <- getMessage q %. "payload.0"
event %. "name" `shouldMatch` "cellsInternal"
event %. "team" `shouldMatch` tid
event %. "type" `shouldMatch` "feature-config.update"
event %. "data.lockStatus" `shouldMatch` "unlocked"
event %. "data.status" `shouldMatch` "enabled"
event %. "data.config.backend.url" `shouldMatch` "https://cells-beta.wire.com"
event %. "data.config.collabora.edition" `shouldMatch` "COOL"
event %. "data.config.storage.teamQuotaBytes" `shouldMatch` quota
testCellsInternal :: (HasCallStack) => App ()
testCellsInternal :: HasCallStack => App ()
testCellsInternal = 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
withWebSocket alice $ \WebSocket
ws -> do
[Value] -> (Value -> App ()) -> App ()
forall (t :: * -> *) (f :: * -> *) a b.
(Foldable t, Applicative f) =>
t a -> (a -> f b) -> f ()
for_ [Value]
validCellsInternalUpdates ((Value -> App ()) -> App ()) -> (Value -> App ()) -> App ()
forall a b. (a -> b) -> a -> b
$ HasCallStack =>
APIAccess -> WebSocket -> String -> String -> Value -> App ()
APIAccess -> WebSocket -> String -> String -> Value -> App ()
setFlag APIAccess
InternalAPI WebSocket
ws String
tid String
"cellsInternal"
[Value] -> (Value -> App Value) -> App ()
forall (t :: * -> *) (f :: * -> *) a b.
(Foldable t, Applicative f) =>
t a -> (a -> f b) -> f ()
for_ [Value]
invalidCellsInternalUpdates ((Value -> App Value) -> App ()) -> (Value -> App Value) -> App ()
forall a b. (a -> b) -> a -> b
$ APIAccess -> Value -> String -> String -> Value -> App Response
setFeature APIAccess
InternalAPI Value
alice String
tid String
"cellsInternal" (Value -> App Response)
-> (Response -> App Value) -> Value -> App Value
forall (m :: * -> *) a b c.
Monad m =>
(a -> m b) -> (b -> m c) -> a -> m c
>=> HasCallStack => Int -> Response -> App Value
Int -> Response -> App Value
getJSON Int
400
setFeature PublicAPI alice tid "cellsInternal" enabled `bindResponse` \Response
resp -> do
Response
resp.status Int -> Int -> App ()
forall a. (MakesValue a, HasCallStack) => a -> Int -> App ()
`shouldMatchInt` Int
404
Response
resp.json App Value -> String -> App Value
forall a. (HasCallStack, MakesValue a) => a -> String -> App Value
%. String
"label" App Value -> String -> App ()
forall a b.
(MakesValue a, MakesValue b, HasCallStack) =>
a -> b -> App ()
`shouldMatch` String
"no-endpoint"
validCellsInternalUpdates :: [Value]
validCellsInternalUpdates :: [Value]
validCellsInternalUpdates =
[ String -> String -> CellsInternalConfig -> Value
mkFt String
"enabled" String
"unlocked" CellsInternalConfig
defConf,
String -> String -> CellsInternalConfig -> Value
mkFt String
"enabled" String
"unlocked" CellsInternalConfig
defConf {collabora = "NO"},
String -> String -> CellsInternalConfig -> Value
mkFt String
"enabled" String
"unlocked" CellsInternalConfig
defConf {collabora = "COOL"},
String -> String -> CellsInternalConfig -> Value
mkFt String
"enabled" String
"unlocked" CellsInternalConfig
defConf {url = "https://wire.com"},
String -> String -> CellsInternalConfig -> Value
mkFt String
"enabled" String
"unlocked" CellsInternalConfig
defConf {quota = "92346832946243"}
]
invalidCellsInternalUpdates :: [Value]
invalidCellsInternalUpdates :: [Value]
invalidCellsInternalUpdates =
[ String -> String -> CellsInternalConfig -> Value
mkFt String
"enabled" String
"unlocked" CellsInternalConfig
defConf {collabora = "FOO"},
String -> String -> CellsInternalConfig -> Value
mkFt String
"enabled" String
"unlocked" CellsInternalConfig
defConf {url = "http://wire.com"},
String -> String -> CellsInternalConfig -> Value
mkFt String
"enabled" String
"unlocked" CellsInternalConfig
defConf {quota = "-92346832946243"},
String -> String -> CellsInternalConfig -> Value
mkFt String
"enabled" String
"unlocked" CellsInternalConfig
defConf {quota = "1 TB"},
String -> String -> CellsInternalConfig -> Value
mkFt String
"disabled" String
"unlocked" CellsInternalConfig
defConf
]
mkFt :: String -> String -> CellsInternalConfig -> Value
mkFt :: String -> String -> CellsInternalConfig -> Value
mkFt String
s String
ls CellsInternalConfig
c =
[Pair] -> Value
object
[ String
"lockStatus" String -> String -> Pair
forall a. ToJSON a => String -> a -> Pair
.= String
ls,
String
"status" String -> String -> Pair
forall a. ToJSON a => String -> a -> Pair
.= String
s,
String
"ttl" String -> String -> Pair
forall a. ToJSON a => String -> a -> Pair
.= String
"unlimited",
String
"config"
String -> Value -> Pair
forall a. ToJSON a => String -> a -> Pair
.= [Pair] -> Value
object
[ String
"backend" String -> Value -> Pair
forall a. ToJSON a => String -> a -> Pair
.= [Pair] -> Value
object [String
"url" String -> String -> Pair
forall a. ToJSON a => String -> a -> Pair
.= CellsInternalConfig
c.url],
String
"collabora" String -> Value -> Pair
forall a. ToJSON a => String -> a -> Pair
.= [Pair] -> Value
object [String
"edition" String -> String -> Pair
forall a. ToJSON a => String -> a -> Pair
.= CellsInternalConfig
c.collabora],
String
"storage" String -> Value -> Pair
forall a. ToJSON a => String -> a -> Pair
.= [Pair] -> Value
object [String
"teamQuotaBytes" String -> String -> Pair
forall a. ToJSON a => String -> a -> Pair
.= CellsInternalConfig
c.quota]
]
]
defConf :: CellsInternalConfig
defConf :: CellsInternalConfig
defConf =
CellsInternalConfig
{ url :: String
url = String
"https://cells-beta.wire.com",
collabora :: String
collabora = String
"COOL",
quota :: String
quota = String
"1000000000000"
}
testPatchCellsInternal :: (HasCallStack) => App ()
testPatchCellsInternal :: HasCallStack => App ()
testPatchCellsInternal = do
[Value] -> (Value -> App ()) -> App ()
forall (t :: * -> *) (f :: * -> *) a b.
(Foldable t, Applicative f) =>
t a -> (a -> f b) -> f ()
for_ [Value]
validCellsInternalUpdates ((Value -> App ()) -> App ()) -> (Value -> App ()) -> App ()
forall a b. (a -> b) -> a -> b
$ Domain -> String -> Value -> App ()
forall domain.
(HasCallStack, MakesValue domain) =>
domain -> String -> Value -> App ()
checkPatch Domain
OwnDomain String
"cellsInternal"
(_, tid, _) <- Domain -> Int -> App (Value, String, [Value])
forall domain.
(HasCallStack, MakesValue domain) =>
domain -> Int -> App (Value, String, [Value])
createTeam Domain
OwnDomain Int
0
for_ (mkFt "enabled" "locked" defConf : invalidCellsInternalUpdates)
$ Internal.patchTeamFeature OwnDomain tid "cellsInternal"
>=> assertStatus 400
data CellsInternalConfig = CellsInternalConfig
{ CellsInternalConfig -> String
url :: String,
CellsInternalConfig -> String
collabora :: String,
CellsInternalConfig -> String
quota :: String
}