{-# OPTIONS -Wno-ambiguous-fields #-}
module Test.MLS.Services where
import API.Brig
import API.GalleyInternal (patchTeamFeatureConfig)
import SetupHelpers
import Testlib.JSON
import Testlib.Prelude
testWhitelistUpdatePermissions :: (HasCallStack) => App ()
testWhitelistUpdatePermissions :: HasCallStack => App ()
testWhitelistUpdatePermissions = do
(owner, tid, []) <- Domain -> Int -> App (Value, String, [Value])
forall domain.
(HasCallStack, MakesValue domain) =>
domain -> Int -> App (Value, String, [Value])
createTeam Domain
OwnDomain Int
1
admin <- createTeamMember owner def {role = "admin"}
provider <- make <$> setupProvider owner def
providerId <- provider %. "id" & asString
service <- make <$> newService OwnDomain providerId def
do
uid <- randomUser OwnDomain def
serviceId <- service %. "id" & asString
np <-
make
$ object
[ "id" .= serviceId,
"provider" .= providerId,
"whitelisted" .= True
]
bindResponse (postServiceWhitelist uid tid np) $ \Response
resp -> do
Response
resp.status Int -> Int -> App ()
forall a. (MakesValue a, HasCallStack) => a -> Int -> App ()
`shouldMatchInt` Int
403
(Response
resp.jsonBody Maybe Value -> String -> App Value
forall a. (HasCallStack, MakesValue a) => a -> String -> App Value
%. String
"label") App Value -> Maybe String -> App ()
forall a b.
(MakesValue a, MakesValue b, HasCallStack) =>
a -> b -> App ()
`shouldMatch` String -> Maybe String
forall a. a -> Maybe a
Just String
"insufficient-permissions"
do
serviceId <- service %. "id" & asString
np <-
make
$ object
[ "id" .= serviceId,
"provider" .= providerId,
"whitelisted" .= True
]
postServiceWhitelist admin tid np >>= assertStatus 200
mlsConfig <-
make
$ object
[ "config"
.= object
[ "allowedCipherSuites" .= [1 :: Int],
"defaultCipherSuite" .= (1 :: Int),
"defaultProtocol" .= "mls",
"protocolToggleUsers" .= ([] :: [String]),
"supportedProtocols" .= ["mls", "proteus"]
],
"status" .= "enabled",
"ttl" .= "unlimited"
]
patchTeamFeatureConfig OwnDomain tid "mls" mlsConfig >>= assertStatus 200
do
uid <- randomUser OwnDomain def
serviceId <- service %. "id" & asString
np <-
make
$ object
[ "id" .= serviceId,
"provider" .= providerId,
"whitelisted" .= True
]
bindResponse (postServiceWhitelist uid tid np) $ \Response
resp -> do
Response
resp.status Int -> Int -> App ()
forall a. (MakesValue a, HasCallStack) => a -> Int -> App ()
`shouldMatchInt` Int
409
(Response
resp.jsonBody Maybe Value -> String -> App Value
forall a. (HasCallStack, MakesValue a) => a -> String -> App Value
%. String
"label") App Value -> Maybe String -> App ()
forall a b.
(MakesValue a, MakesValue b, HasCallStack) =>
a -> b -> App ()
`shouldMatch` String -> Maybe String
forall a. a -> Maybe a
Just String
"mls-services-not-allowed"
do
serviceId <- service %. "id" & asString
np <-
make
$ object
[ "id" .= serviceId,
"provider" .= providerId,
"whitelisted" .= True
]
postServiceWhitelist admin tid np >>= \Response
resp -> do
Response
resp.status Int -> Int -> App ()
forall a. (MakesValue a, HasCallStack) => a -> Int -> App ()
`shouldMatchInt` Int
409
(Response
resp.jsonBody Maybe Value -> String -> App Value
forall a. (HasCallStack, MakesValue a) => a -> String -> App Value
%. String
"label") App Value -> Maybe String -> App ()
forall a b.
(MakesValue a, MakesValue b, HasCallStack) =>
a -> b -> App ()
`shouldMatch` String -> Maybe String
forall a. a -> Maybe a
Just String
"mls-services-not-allowed"