{-# OPTIONS_GHC -Wno-ambiguous-fields -Wno-incomplete-uni-patterns #-}
module Test.Client where
import API.Brig
import qualified API.Brig as API
import API.BrigCommon
import API.Gundeck
import Control.Lens hiding ((.=))
import Control.Monad.Codensity
import Control.Monad.Reader
import Data.Aeson hiding ((.=))
import Data.ProtoLens.Labels ()
import Data.Time.Clock.POSIX
import Data.Time.Clock.System
import Data.Time.Format
import SetupHelpers
import Testlib.Prelude
import Testlib.ResourcePool
testClientLastActive :: (HasCallStack) => App ()
testClientLastActive :: HasCallStack => App ()
testClientLastActive = do
alice <- Domain -> CreateUser -> App Value
forall domain.
(HasCallStack, MakesValue domain) =>
domain -> CreateUser -> App Value
randomUser Domain
OwnDomain CreateUser
forall a. Default a => a
def
c0 <- addClient alice def >>= getJSON 201
cid <- c0 %. "id" & asString
tm0 <- fromMaybe Null <$> lookupField c0 "last_active"
tm0 `shouldMatch` Null
now <- systemSeconds <$> liftIO getSystemTime
void $ getNotifications alice def {client = Just cid}
c1 <- getClient alice cid >>= getJSON 200
tm1 <- c1 %. "last_active" & asString
ts1 <-
round @Double
. realToFrac
. utcTimeToPOSIXSeconds
<$> parseTimeM False defaultTimeLocale "%Y-%m-%dT%H:%M:%SZ" tm1
assertBool "last_active is earlier than expected" $ ts1 >= now
testListClientsIfBackendIsOffline :: (HasCallStack) => App ()
testListClientsIfBackendIsOffline :: HasCallStack => App ()
testListClientsIfBackendIsOffline = do
resourcePool <- (Env -> ResourcePool BackendResource)
-> App (ResourcePool BackendResource)
forall r (m :: * -> *) a. MonadReader r m => (r -> a) -> m a
asks (.resourcePool)
ownDomain <- asString OwnDomain
otherDomain <- asString OtherDomain
[ownUser1, ownUser2] <- createAndConnectUsers [OwnDomain, OtherDomain]
ownClient1 <- objId $ bindResponse (API.addClient ownUser1 def) $ getJSON 201
ownClient2 <- objId $ bindResponse (API.addClient ownUser2 def) $ getJSON 201
ownUser1Id <- objId ownUser1
ownUser2Id <- objId ownUser2
let expectedResponse =
[Pair] -> Value
object
[ String
ownDomain String -> Value -> Pair
forall a. ToJSON a => String -> a -> Pair
.= [Pair] -> Value
object [String
ownUser1Id String -> [Value] -> Pair
forall a. ToJSON a => String -> a -> Pair
.= [[Pair] -> Value
object [String
"id" String -> String -> Pair
forall a. ToJSON a => String -> a -> Pair
.= String
ownClient1]]],
String
otherDomain String -> Value -> Pair
forall a. ToJSON a => String -> a -> Pair
.= [Pair] -> Value
object [String
ownUser2Id String -> [Value] -> Pair
forall a. ToJSON a => String -> a -> Pair
.= [[Pair] -> Value
object [String
"id" String -> String -> Pair
forall a. ToJSON a => String -> a -> Pair
.= String
ownClient2]]]
]
bindResponse (listUsersClients ownUser1 [ownUser1, ownUser2]) $ \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
"qualified_user_map" App Value -> Value -> App ()
forall a b.
(MakesValue a, MakesValue b, HasCallStack) =>
a -> b -> App ()
`shouldMatch` Value
expectedResponse
runCodensity (acquireResources 1 resourcePool) $ \[BackendResource
downBackend] -> do
rndUsrId <- App String
HasCallStack => App String
randomId
let downUser = ([Pair] -> Value
object [String
"domain" String -> String -> Pair
forall a. ToJSON a => String -> a -> Pair
.= BackendResource
downBackend.berDomain, String
"id" String -> String -> Pair
forall a. ToJSON a => String -> a -> Pair
.= String
rndUsrId])
bindResponse (listUsersClients ownUser1 [ownUser1, ownUser2, downUser]) $ \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
"qualified_user_map" App Value -> Value -> App ()
forall a b.
(MakesValue a, MakesValue b, HasCallStack) =>
a -> b -> App ()
`shouldMatch` Value
expectedResponse
testCreateClientWithCapabilities :: App ()
testCreateClientWithCapabilities :: App ()
testCreateClientWithCapabilities = do
let allCapabilities :: [String]
allCapabilities = [String
"legalhold-implicit-consent", String
"consumable-notifications"]
alice <- Domain -> CreateUser -> App Value
forall domain.
(HasCallStack, MakesValue domain) =>
domain -> CreateUser -> App Value
randomUser Domain
OwnDomain CreateUser
forall a. Default a => a
def
addClient alice def {acapabilities = Just allCapabilities} `bindResponse` \Response
resp -> do
Response
resp.status Int -> Int -> App ()
forall a. (MakesValue a, HasCallStack) => a -> Int -> App ()
`shouldMatchInt` Int
201
Response
resp.json App Value -> String -> App Value
forall a. (HasCallStack, MakesValue a) => a -> String -> App Value
%. String
"capabilities" App Value -> [String] -> App ()
forall a b.
(MakesValue a, MakesValue b, HasCallStack) =>
a -> b -> App ()
`shouldMatchSet` [String]
allCapabilities
getSelfClients alice `bindResponse` \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
"0.capabilities" App Value -> [String] -> App ()
forall a b.
(MakesValue a, MakesValue b, HasCallStack) =>
a -> b -> App ()
`shouldMatchSet` [String]
allCapabilities
testUpdateClientWithConsumableNotificationsCapability :: App ()
testUpdateClientWithConsumableNotificationsCapability :: App ()
testUpdateClientWithConsumableNotificationsCapability = do
domain <- Domain -> App String
forall a. (HasCallStack, MakesValue a) => a -> App String
asString Domain
OwnDomain
let consumeCapability = String
"consumable-notifications"
alice <- randomUser domain def
aliceId <- alice %. "id" & asString
cid <-
addClient alice def {acapabilities = Nothing} `bindResponse` \Response
resp -> do
Response
resp.status Int -> Int -> App ()
forall a. (MakesValue a, HasCallStack) => a -> Int -> App ()
`shouldMatchInt` Int
201
Response
resp.json App Value -> String -> App Value
forall a. (HasCallStack, MakesValue a) => a -> String -> App Value
%. String
"id" App Value -> (App Value -> App String) -> App String
forall a b. a -> (a -> b) -> b
& App Value -> App String
forall a. (HasCallStack, MakesValue a) => a -> App String
asString
let cli =
ClientIdentity
{ domain :: String
domain = String
domain,
user :: String
user = String
aliceId,
client :: String
client = String
cid
}
updateClient cli def {capabilities = Just [consumeCapability]} >>= assertSuccess
getSelfClients alice `bindResponse` \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
"0.capabilities" App Value -> [String] -> App ()
forall a b.
(MakesValue a, MakesValue b, HasCallStack) =>
a -> b -> App ()
`shouldMatch` [String
consumeCapability]
testGetClientCapabilitiesV7 :: App ()
testGetClientCapabilitiesV7 :: App ()
testGetClientCapabilitiesV7 = do
let allCapabilities :: [String]
allCapabilities = [String
"legalhold-implicit-consent", String
"consumable-notifications"]
alice <- Domain -> CreateUser -> App Value
forall domain.
(HasCallStack, MakesValue domain) =>
domain -> CreateUser -> App Value
randomUser Domain
OwnDomain CreateUser
forall a. Default a => a
def
addClient alice def {acapabilities = Just allCapabilities} `bindResponse` \Response
resp -> do
Response
resp.status Int -> Int -> App ()
forall a. (MakesValue a, HasCallStack) => a -> Int -> App ()
`shouldMatchInt` Int
201
Response
resp.json App Value -> String -> App Value
forall a. (HasCallStack, MakesValue a) => a -> String -> App Value
%. String
"capabilities" App Value -> [String] -> App ()
forall a b.
(MakesValue a, MakesValue b, HasCallStack) =>
a -> b -> App ()
`shouldMatchSet` [String]
allCapabilities
getSelfClients alice `bindResponse` \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
"0.capabilities" App Value -> [String] -> App ()
forall a b.
(MakesValue a, MakesValue b, HasCallStack) =>
a -> b -> App ()
`shouldMatchSet` [String]
allCapabilities
withAPIVersion 7 $ getSelfClients alice `bindResponse` \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
"0.capabilities" App Value -> [String] -> App ()
forall a b.
(MakesValue a, MakesValue b, HasCallStack) =>
a -> b -> App ()
`shouldMatchSet` [String
"legalhold-implicit-consent"]
withAPIVersion 6 $ getSelfClients alice `bindResponse` \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
"0.capabilities.capabilities" App Value -> [String] -> App ()
forall a b.
(MakesValue a, MakesValue b, HasCallStack) =>
a -> b -> App ()
`shouldMatchSet` [String
"legalhold-implicit-consent"]