Skip to content

Commit

Permalink
Test: A provider creation helper
Browse files Browse the repository at this point in the history
  • Loading branch information
mdimjasevic committed Dec 20, 2023
1 parent 2d7fe9a commit 4b62f5d
Show file tree
Hide file tree
Showing 2 changed files with 36 additions and 22 deletions.
25 changes: 25 additions & 0 deletions integration/test/SetupHelpers.hs
Original file line number Diff line number Diff line change
Expand Up @@ -245,3 +245,28 @@ getOne2OneConversation user1 user2 cnvState = do
qIds <- for others (%. "qualified_id")
pure $ qIds == users && t
head <$> filterM (isWith [user2]) l

-- | Create a provider, get an activation code, activate the provider and log it
-- in. The return value is the created provider.
setupProvider ::
( HasCallStack,
MakesValue user
) =>
user ->
NewProvider ->
App Value
setupProvider u np@(NewProvider {..}) = do
dom <- objDomain u
provider <- newProvider u np
pass <- provider %. "password" & asString
(key, code) <- do
pair <-
getProviderActivationCodeInternal dom newProviderEmail `bindResponse` \resp -> do
resp.status `shouldMatchInt` 200
resp.json
k <- pair %. "key" & asString
c <- pair %. "code" & asString
pure (k, c)
activateProvider dom key code
void $ loginProvider dom newProviderEmail pass
pure provider
33 changes: 11 additions & 22 deletions integration/test/Test/Services.hs
Original file line number Diff line number Diff line change
Expand Up @@ -18,7 +18,6 @@
module Test.Services where

import API.Brig
import API.BrigInternal
import API.Common
import SetupHelpers
import Testlib.Prelude
Expand All @@ -28,26 +27,16 @@ testUpdateServiceUpdateAcceptHeader = do
let dom = OwnDomain
email <- randomEmail
alice <- randomUser dom def
provider <- newProvider alice def {newProviderEmail = email}
providerId <- provider %. "id" & asString
pass <- provider %. "password" & asString
(key, code) <- do
pair <-
getProviderActivationCodeInternal dom email `bindResponse` \resp -> do
resp.status `shouldMatchInt` 200
resp.json
k <- pair %. "key" & asString
c <- pair %. "code" & asString
pure (k, c)
activateProvider dom key code
void $ loginProvider dom email pass
service <- newService dom providerId def
serviceId <- service %. "id"
provider <- setupProvider alice def {newProviderEmail = email}
pId <- provider %. "id" & asString
service <- newService dom pId def
sIs <- service %. "id"
void $
updateService
dom
providerId
serviceId
(Just "application/json")
(Just "brand new service")
updateService dom pId sIs (Just "application/json") (Just "brand new service")
>>= getBody 200
void $
updateService dom pId sIs (Just "text/plain") (Just "even newer service")
>>= getBody 200
void $
updateService dom pId sIs Nothing (Just "really old service")
>>= getBody 200

0 comments on commit 4b62f5d

Please sign in to comment.