module Test.EnterpriseLogin where
import API.BrigInternal
import API.Common
import Control.Monad.Trans.Maybe
import Testlib.Prelude
testDomainRegistrationLock :: App ()
testDomainRegistrationLock :: App ()
testDomainRegistrationLock = do
String
domain <- App String
randomDomain
HasCallStack => Int -> Response -> App ()
Int -> Response -> App ()
assertStatus Int
404 (Response -> App ()) -> App Response -> App ()
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< Domain -> String -> App Response
forall domain.
(HasCallStack, MakesValue domain) =>
domain -> String -> App Response
getDomainRegistration Domain
OwnDomain String
domain
HasCallStack => Int -> Response -> App ()
Int -> Response -> App ()
assertStatus Int
204 (Response -> App ()) -> App Response -> App ()
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< Domain -> String -> App Response
forall domain.
(HasCallStack, MakesValue domain) =>
domain -> String -> App Response
domainRegistrationLock Domain
OwnDomain String
domain
HasCallStack => Int -> Response -> App ()
Int -> Response -> App ()
assertStatus Int
204 (Response -> App ()) -> App Response -> App ()
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< Domain -> String -> App Response
forall domain.
(HasCallStack, MakesValue domain) =>
domain -> String -> App Response
domainRegistrationLock Domain
OwnDomain String
domain
App Response -> (Response -> App ()) -> App ()
forall a.
HasCallStack =>
App Response -> (Response -> App a) -> App a
bindResponse (Domain -> String -> App Response
forall domain.
(HasCallStack, MakesValue domain) =>
domain -> String -> App Response
getDomainRegistration Domain
OwnDomain String
domain) ((Response -> App ()) -> App ()) -> (Response -> App ()) -> App ()
forall a b. (a -> b) -> a -> b
$ \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
"domain" App Value -> String -> App ()
forall a b.
(MakesValue a, MakesValue b, HasCallStack) =>
a -> b -> App ()
`shouldMatch` String
domain
Response
resp.json App Value -> String -> App Value
forall a. (HasCallStack, MakesValue a) => a -> String -> App Value
%. String
"domain_redirect" App Value -> String -> App ()
forall a b.
(MakesValue a, MakesValue b, HasCallStack) =>
a -> b -> App ()
`shouldMatch` String
"locked"
Response
resp.json App Value -> String -> App Value
forall a. (HasCallStack, MakesValue a) => a -> String -> App Value
%. String
"team_invite" App Value -> String -> App ()
forall a b.
(MakesValue a, MakesValue b, HasCallStack) =>
a -> b -> App ()
`shouldMatch` String
"allowed"
HasCallStack => Int -> Response -> App ()
Int -> Response -> App ()
assertStatus Int
204 (Response -> App ()) -> App Response -> App ()
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< Domain -> String -> App Response
forall domain.
(HasCallStack, MakesValue domain) =>
domain -> String -> App Response
domainRegistrationUnlock Domain
OwnDomain String
domain
App Response -> (Response -> App ()) -> App ()
forall a.
HasCallStack =>
App Response -> (Response -> App a) -> App a
bindResponse (Domain -> String -> App Response
forall domain.
(HasCallStack, MakesValue domain) =>
domain -> String -> App Response
getDomainRegistration Domain
OwnDomain String
domain) ((Response -> App ()) -> App ()) -> (Response -> App ()) -> App ()
forall a b. (a -> b) -> a -> b
$ \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
"domain" App Value -> String -> App ()
forall a b.
(MakesValue a, MakesValue b, HasCallStack) =>
a -> b -> App ()
`shouldMatch` String
domain
Response
resp.json App Value -> String -> App Value
forall a. (HasCallStack, MakesValue a) => a -> String -> App Value
%. String
"domain_redirect" App Value -> String -> App ()
forall a b.
(MakesValue a, MakesValue b, HasCallStack) =>
a -> b -> App ()
`shouldMatch` String
"none"
Response
resp.json App Value -> String -> App Value
forall a. (HasCallStack, MakesValue a) => a -> String -> App Value
%. String
"team_invite" App Value -> String -> App ()
forall a b.
(MakesValue a, MakesValue b, HasCallStack) =>
a -> b -> App ()
`shouldMatch` String
"allowed"
testDomainRegistrationLockPreviousValueOverwritten :: App ()
testDomainRegistrationLockPreviousValueOverwritten :: App ()
testDomainRegistrationLockPreviousValueOverwritten = do
String
domain <- App String
randomDomain
HasCallStack => Int -> Response -> App ()
Int -> Response -> App ()
assertStatus Int
204 (Response -> App ()) -> App Response -> App ()
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< Domain -> String -> App Response
forall domain.
(HasCallStack, MakesValue domain) =>
domain -> String -> App Response
domainRegistrationPreAuthorize Domain
OwnDomain String
domain
App Response -> (Response -> App ()) -> App ()
forall a.
HasCallStack =>
App Response -> (Response -> App a) -> App a
bindResponse (Domain -> String -> App Response
forall domain.
(HasCallStack, MakesValue domain) =>
domain -> String -> App Response
getDomainRegistration Domain
OwnDomain String
domain) ((Response -> App ()) -> App ()) -> (Response -> App ()) -> App ()
forall a b. (a -> b) -> a -> b
$ \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
"domain" App Value -> String -> App ()
forall a b.
(MakesValue a, MakesValue b, HasCallStack) =>
a -> b -> App ()
`shouldMatch` String
domain
Response
resp.json App Value -> String -> App Value
forall a. (HasCallStack, MakesValue a) => a -> String -> App Value
%. String
"domain_redirect" App Value -> String -> App ()
forall a b.
(MakesValue a, MakesValue b, HasCallStack) =>
a -> b -> App ()
`shouldMatch` String
"pre-authorized"
HasCallStack => Int -> Response -> App ()
Int -> Response -> App ()
assertStatus Int
204 (Response -> App ()) -> App Response -> App ()
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< Domain -> String -> App Response
forall domain.
(HasCallStack, MakesValue domain) =>
domain -> String -> App Response
domainRegistrationLock Domain
OwnDomain String
domain
App Response -> (Response -> App ()) -> App ()
forall a.
HasCallStack =>
App Response -> (Response -> App a) -> App a
bindResponse (Domain -> String -> App Response
forall domain.
(HasCallStack, MakesValue domain) =>
domain -> String -> App Response
getDomainRegistration Domain
OwnDomain String
domain) ((Response -> App ()) -> App ()) -> (Response -> App ()) -> App ()
forall a b. (a -> b) -> a -> b
$ \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
"domain" App Value -> String -> App ()
forall a b.
(MakesValue a, MakesValue b, HasCallStack) =>
a -> b -> App ()
`shouldMatch` String
domain
Response
resp.json App Value -> String -> App Value
forall a. (HasCallStack, MakesValue a) => a -> String -> App Value
%. String
"domain_redirect" App Value -> String -> App ()
forall a b.
(MakesValue a, MakesValue b, HasCallStack) =>
a -> b -> App ()
`shouldMatch` String
"locked"
testDomainRegistrationUnlockErrorIfNotLocked :: App ()
testDomainRegistrationUnlockErrorIfNotLocked :: App ()
testDomainRegistrationUnlockErrorIfNotLocked = do
String
domain <- App String
randomDomain
HasCallStack => Int -> Response -> App ()
Int -> Response -> App ()
assertStatus Int
204 (Response -> App ()) -> App Response -> App ()
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< Domain -> String -> App Response
forall domain.
(HasCallStack, MakesValue domain) =>
domain -> String -> App Response
domainRegistrationPreAuthorize Domain
OwnDomain String
domain
App Response -> (Response -> App ()) -> App ()
forall a.
HasCallStack =>
App Response -> (Response -> App a) -> App a
bindResponse (Domain -> String -> App Response
forall domain.
(HasCallStack, MakesValue domain) =>
domain -> String -> App Response
getDomainRegistration Domain
OwnDomain String
domain) ((Response -> App ()) -> App ()) -> (Response -> App ()) -> App ()
forall a b. (a -> b) -> a -> b
$ \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
"domain" App Value -> String -> App ()
forall a b.
(MakesValue a, MakesValue b, HasCallStack) =>
a -> b -> App ()
`shouldMatch` String
domain
Response
resp.json App Value -> String -> App Value
forall a. (HasCallStack, MakesValue a) => a -> String -> App Value
%. String
"domain_redirect" App Value -> String -> App ()
forall a b.
(MakesValue a, MakesValue b, HasCallStack) =>
a -> b -> App ()
`shouldMatch` String
"pre-authorized"
App Response -> (Response -> App ()) -> App ()
forall a.
HasCallStack =>
App Response -> (Response -> App a) -> App a
bindResponse (Domain -> String -> App Response
forall domain.
(HasCallStack, MakesValue domain) =>
domain -> String -> App Response
domainRegistrationUnlock Domain
OwnDomain String
domain) ((Response -> App ()) -> App ()) -> (Response -> App ()) -> App ()
forall a b. (a -> b) -> a -> b
$ \Response
resp -> do
Response
resp.status Int -> Int -> App ()
forall a. (MakesValue a, HasCallStack) => a -> Int -> App ()
`shouldMatchInt` Int
403
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
"operation-forbidden-for-domain-registration-state"
testDomainRegistrationPreAuthorize :: App ()
testDomainRegistrationPreAuthorize :: App ()
testDomainRegistrationPreAuthorize = do
String
domain <- App String
randomDomain
HasCallStack => Int -> Response -> App ()
Int -> Response -> App ()
assertStatus Int
404 (Response -> App ()) -> App Response -> App ()
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< Domain -> String -> App Response
forall domain.
(HasCallStack, MakesValue domain) =>
domain -> String -> App Response
getDomainRegistration Domain
OwnDomain String
domain
HasCallStack => Int -> Response -> App ()
Int -> Response -> App ()
assertStatus Int
204 (Response -> App ()) -> App Response -> App ()
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< Domain -> String -> App Response
forall domain.
(HasCallStack, MakesValue domain) =>
domain -> String -> App Response
domainRegistrationPreAuthorize Domain
OwnDomain String
domain
HasCallStack => Int -> Response -> App ()
Int -> Response -> App ()
assertStatus Int
204 (Response -> App ()) -> App Response -> App ()
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< Domain -> String -> App Response
forall domain.
(HasCallStack, MakesValue domain) =>
domain -> String -> App Response
domainRegistrationPreAuthorize Domain
OwnDomain String
domain
App Response -> (Response -> App ()) -> App ()
forall a.
HasCallStack =>
App Response -> (Response -> App a) -> App a
bindResponse (Domain -> String -> App Response
forall domain.
(HasCallStack, MakesValue domain) =>
domain -> String -> App Response
getDomainRegistration Domain
OwnDomain String
domain) ((Response -> App ()) -> App ()) -> (Response -> App ()) -> App ()
forall a b. (a -> b) -> a -> b
$ \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
"domain" App Value -> String -> App ()
forall a b.
(MakesValue a, MakesValue b, HasCallStack) =>
a -> b -> App ()
`shouldMatch` String
domain
Response
resp.json App Value -> String -> App Value
forall a. (HasCallStack, MakesValue a) => a -> String -> App Value
%. String
"domain_redirect" App Value -> String -> App ()
forall a b.
(MakesValue a, MakesValue b, HasCallStack) =>
a -> b -> App ()
`shouldMatch` String
"pre-authorized"
Response
resp.json App Value -> String -> App Value
forall a. (HasCallStack, MakesValue a) => a -> String -> App Value
%. String
"team_invite" App Value -> String -> App ()
forall a b.
(MakesValue a, MakesValue b, HasCallStack) =>
a -> b -> App ()
`shouldMatch` String
"allowed"
testDomainRegistrationPreAuthorizeFailsIfLocked :: App ()
testDomainRegistrationPreAuthorizeFailsIfLocked :: App ()
testDomainRegistrationPreAuthorizeFailsIfLocked = do
String
domain <- App String
randomDomain
HasCallStack => Int -> Response -> App ()
Int -> Response -> App ()
assertStatus Int
204 (Response -> App ()) -> App Response -> App ()
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< Domain -> String -> App Response
forall domain.
(HasCallStack, MakesValue domain) =>
domain -> String -> App Response
domainRegistrationLock Domain
OwnDomain String
domain
App Response -> (Response -> App ()) -> App ()
forall a.
HasCallStack =>
App Response -> (Response -> App a) -> App a
bindResponse (Domain -> String -> App Response
forall domain.
(HasCallStack, MakesValue domain) =>
domain -> String -> App Response
domainRegistrationPreAuthorize Domain
OwnDomain String
domain) ((Response -> App ()) -> App ()) -> (Response -> App ()) -> App ()
forall a b. (a -> b) -> a -> b
$ \Response
resp -> do
Response
resp.status Int -> Int -> App ()
forall a. (MakesValue a, HasCallStack) => a -> Int -> App ()
`shouldMatchInt` Int
403
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
"operation-forbidden-for-domain-registration-state"
App Response -> (Response -> App ()) -> App ()
forall a.
HasCallStack =>
App Response -> (Response -> App a) -> App a
bindResponse (Domain -> String -> App Response
forall domain.
(HasCallStack, MakesValue domain) =>
domain -> String -> App Response
getDomainRegistration Domain
OwnDomain String
domain) ((Response -> App ()) -> App ()) -> (Response -> App ()) -> App ()
forall a b. (a -> b) -> a -> b
$ \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
"domain" App Value -> String -> App ()
forall a b.
(MakesValue a, MakesValue b, HasCallStack) =>
a -> b -> App ()
`shouldMatch` String
domain
Response
resp.json App Value -> String -> App Value
forall a. (HasCallStack, MakesValue a) => a -> String -> App Value
%. String
"domain_redirect" App Value -> String -> App ()
forall a b.
(MakesValue a, MakesValue b, HasCallStack) =>
a -> b -> App ()
`shouldMatch` String
"locked"
HasCallStack => Int -> Response -> App ()
Int -> Response -> App ()
assertStatus Int
204 (Response -> App ()) -> App Response -> App ()
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< Domain -> String -> App Response
forall domain.
(HasCallStack, MakesValue domain) =>
domain -> String -> App Response
domainRegistrationUnlock Domain
OwnDomain String
domain
HasCallStack => Int -> Response -> App ()
Int -> Response -> App ()
assertStatus Int
204 (Response -> App ()) -> App Response -> App ()
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< Domain -> String -> App Response
forall domain.
(HasCallStack, MakesValue domain) =>
domain -> String -> App Response
domainRegistrationPreAuthorize Domain
OwnDomain String
domain
App Response -> (Response -> App ()) -> App ()
forall a.
HasCallStack =>
App Response -> (Response -> App a) -> App a
bindResponse (Domain -> String -> App Response
forall domain.
(HasCallStack, MakesValue domain) =>
domain -> String -> App Response
getDomainRegistration Domain
OwnDomain String
domain) ((Response -> App ()) -> App ()) -> (Response -> App ()) -> App ()
forall a b. (a -> b) -> a -> b
$ \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
"domain" App Value -> String -> App ()
forall a b.
(MakesValue a, MakesValue b, HasCallStack) =>
a -> b -> App ()
`shouldMatch` String
domain
Response
resp.json App Value -> String -> App Value
forall a. (HasCallStack, MakesValue a) => a -> String -> App Value
%. String
"domain_redirect" App Value -> String -> App ()
forall a b.
(MakesValue a, MakesValue b, HasCallStack) =>
a -> b -> App ()
`shouldMatch` String
"pre-authorized"
Response
resp.json App Value -> String -> App Value
forall a. (HasCallStack, MakesValue a) => a -> String -> App Value
%. String
"team_invite" App Value -> String -> App ()
forall a b.
(MakesValue a, MakesValue b, HasCallStack) =>
a -> b -> App ()
`shouldMatch` String
"allowed"
testDomainRegistrationPreAuthorizeDoesNotAlterTeamInvite :: App ()
testDomainRegistrationPreAuthorizeDoesNotAlterTeamInvite :: App ()
testDomainRegistrationPreAuthorizeDoesNotAlterTeamInvite = do
String
domain <- App String
randomDomain
HasCallStack => Int -> Response -> App ()
Int -> Response -> App ()
assertStatus Int
404 (Response -> App ()) -> App Response -> App ()
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< Domain -> String -> App Response
forall domain.
(HasCallStack, MakesValue domain) =>
domain -> String -> App Response
getDomainRegistration Domain
OwnDomain String
domain
let update :: Value
update =
[Pair] -> Value
object
[ String
"domain_redirect" String -> String -> Pair
forall a. ToJSON a => String -> a -> Pair
.= String
"none",
String
"team_invite" String -> String -> Pair
forall a. ToJSON a => String -> a -> Pair
.= String
"team",
String
"team" String -> String -> Pair
forall a. ToJSON a => String -> a -> Pair
.= String
"3bc23f21-dc03-4922-9563-c3beedf895db"
]
HasCallStack => Int -> Response -> App ()
Int -> Response -> App ()
assertStatus Int
204 (Response -> App ()) -> App Response -> App ()
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< Domain -> String -> Value -> App Response
forall domain.
(HasCallStack, MakesValue domain) =>
domain -> String -> Value -> App Response
updateDomainRegistration Domain
OwnDomain String
domain Value
update
HasCallStack => Int -> Response -> App ()
Int -> Response -> App ()
assertStatus Int
204 (Response -> App ()) -> App Response -> App ()
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< Domain -> String -> App Response
forall domain.
(HasCallStack, MakesValue domain) =>
domain -> String -> App Response
domainRegistrationPreAuthorize Domain
OwnDomain String
domain
App Response -> (Response -> App ()) -> App ()
forall a.
HasCallStack =>
App Response -> (Response -> App a) -> App a
bindResponse (Domain -> String -> App Response
forall domain.
(HasCallStack, MakesValue domain) =>
domain -> String -> App Response
getDomainRegistration Domain
OwnDomain String
domain) ((Response -> App ()) -> App ()) -> (Response -> App ()) -> App ()
forall a b. (a -> b) -> a -> b
$ \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
"domain" App Value -> String -> App ()
forall a b.
(MakesValue a, MakesValue b, HasCallStack) =>
a -> b -> App ()
`shouldMatch` String
domain
Response
resp.json App Value -> String -> App Value
forall a. (HasCallStack, MakesValue a) => a -> String -> App Value
%. String
"domain_redirect" App Value -> String -> App ()
forall a b.
(MakesValue a, MakesValue b, HasCallStack) =>
a -> b -> App ()
`shouldMatch` String
"pre-authorized"
Response
resp.json App Value -> String -> App Value
forall a. (HasCallStack, MakesValue a) => a -> String -> App Value
%. String
"team_invite" App Value -> String -> App ()
forall a b.
(MakesValue a, MakesValue b, HasCallStack) =>
a -> b -> App ()
`shouldMatch` String
"team"
Response
resp.json App Value -> String -> App Value
forall a. (HasCallStack, MakesValue a) => a -> String -> App Value
%. String
"team" App Value -> String -> App ()
forall a b.
(MakesValue a, MakesValue b, HasCallStack) =>
a -> b -> App ()
`shouldMatch` String
"3bc23f21-dc03-4922-9563-c3beedf895db"
App Value -> String -> App (Maybe Value)
forall a.
(HasCallStack, MakesValue a) =>
a -> String -> App (Maybe Value)
lookupField Response
resp.json String
"backend" App (Maybe Value) -> Maybe Value -> App ()
forall a b.
(MakesValue a, MakesValue b, HasCallStack) =>
a -> b -> App ()
`shouldMatch` (Maybe Value
forall a. Maybe a
Nothing :: Maybe Value)
App Value -> String -> App (Maybe Value)
forall a.
(HasCallStack, MakesValue a) =>
a -> String -> App (Maybe Value)
lookupField Response
resp.json String
"backend_url" App (Maybe Value) -> Maybe Value -> App ()
forall a b.
(MakesValue a, MakesValue b, HasCallStack) =>
a -> b -> App ()
`shouldMatch` (Maybe Value
forall a. Maybe a
Nothing :: Maybe Value)
testDomainRegistrationQueriesDoNotCreateEntry :: App ()
testDomainRegistrationQueriesDoNotCreateEntry :: App ()
testDomainRegistrationQueriesDoNotCreateEntry = do
String
domain <- App String
randomDomain
HasCallStack => Int -> Response -> App ()
Int -> Response -> App ()
assertStatus Int
404 (Response -> App ()) -> App Response -> App ()
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< Domain -> String -> App Response
forall domain.
(HasCallStack, MakesValue domain) =>
domain -> String -> App Response
getDomainRegistration Domain
OwnDomain String
domain
HasCallStack => Int -> Response -> App ()
Int -> Response -> App ()
assertStatus Int
404 (Response -> App ()) -> App Response -> App ()
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< Domain -> String -> App Response
forall domain.
(HasCallStack, MakesValue domain) =>
domain -> String -> App Response
domainRegistrationUnlock Domain
OwnDomain String
domain
HasCallStack => Int -> Response -> App ()
Int -> Response -> App ()
assertStatus Int
404 (Response -> App ()) -> App Response -> App ()
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< Domain -> String -> App Response
forall domain.
(HasCallStack, MakesValue domain) =>
domain -> String -> App Response
domainRegistrationUnAuthorize Domain
OwnDomain String
domain
HasCallStack => Int -> Response -> App ()
Int -> Response -> App ()
assertStatus Int
404 (Response -> App ()) -> App Response -> App ()
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< Domain -> String -> App Response
forall domain.
(HasCallStack, MakesValue domain) =>
domain -> String -> App Response
getDomainRegistration Domain
OwnDomain String
domain
testDomainRegistrationUpdate :: App ()
testDomainRegistrationUpdate :: App ()
testDomainRegistrationUpdate = do
String
domain <- App String
randomDomain
HasCallStack => Int -> Response -> App ()
Int -> Response -> App ()
assertStatus Int
404 (Response -> App ()) -> App Response -> App ()
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< Domain -> String -> App Response
forall domain.
(HasCallStack, MakesValue domain) =>
domain -> String -> App Response
getDomainRegistration Domain
OwnDomain String
domain
HasCallStack => String -> Value -> App ()
String -> Value -> App ()
updateDomain String
domain
(Value -> App ()) -> Value -> App ()
forall a b. (a -> b) -> a -> b
$ [Pair] -> Value
object
[ String
"domain_redirect" String -> String -> Pair
forall a. ToJSON a => String -> a -> Pair
.= String
"backend",
String
"backend"
String -> Value -> Pair
forall a. ToJSON a => String -> a -> Pair
.= [Pair] -> Value
object
[ String
"config_url" String -> String -> Pair
forall a. ToJSON a => String -> a -> Pair
.= String
"https://example.com",
String
"webapp_url" String -> String -> Pair
forall a. ToJSON a => String -> a -> Pair
.= String
"https://webapp.example.com"
],
String
"team_invite" String -> String -> Pair
forall a. ToJSON a => String -> a -> Pair
.= String
"not-allowed"
]
HasCallStack => String -> Value -> App ()
String -> Value -> App ()
updateDomain String
domain
(Value -> App ()) -> Value -> App ()
forall a b. (a -> b) -> a -> b
$ [Pair] -> Value
object
[ String
"domain_redirect" String -> String -> Pair
forall a. ToJSON a => String -> a -> Pair
.= String
"sso",
String
"sso_code" String -> String -> Pair
forall a. ToJSON a => String -> a -> Pair
.= String
"f82bad56-df61-49c0-bc9a-dc45c8ee1000",
String
"team_invite" String -> String -> Pair
forall a. ToJSON a => String -> a -> Pair
.= String
"allowed"
]
HasCallStack => String -> Value -> App ()
String -> Value -> App ()
updateDomain String
domain
(Value -> App ()) -> Value -> App ()
forall a b. (a -> b) -> a -> b
$ [Pair] -> Value
object
[ String
"domain_redirect" String -> String -> Pair
forall a. ToJSON a => String -> a -> Pair
.= String
"no-registration",
String
"team_invite" String -> String -> Pair
forall a. ToJSON a => String -> a -> Pair
.= String
"team",
String
"team" String -> String -> Pair
forall a. ToJSON a => String -> a -> Pair
.= String
"3bc23f21-dc03-4922-9563-c3beedf895db"
]
where
updateDomain :: (HasCallStack) => String -> Value -> App ()
updateDomain :: HasCallStack => String -> Value -> App ()
updateDomain String
domain Value
update = do
HasCallStack => Int -> Response -> App ()
Int -> Response -> App ()
assertStatus Int
204 (Response -> App ()) -> App Response -> App ()
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< Domain -> String -> Value -> App Response
forall domain.
(HasCallStack, MakesValue domain) =>
domain -> String -> Value -> App Response
updateDomainRegistration Domain
OwnDomain String
domain Value
update
HasCallStack => Int -> Response -> App ()
Int -> Response -> App ()
assertStatus Int
204 (Response -> App ()) -> App Response -> App ()
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< Domain -> String -> Value -> App Response
forall domain.
(HasCallStack, MakesValue domain) =>
domain -> String -> Value -> App Response
updateDomainRegistration Domain
OwnDomain String
domain Value
update
App Response -> (Response -> App ()) -> App ()
forall a.
HasCallStack =>
App Response -> (Response -> App a) -> App a
bindResponse (Domain -> String -> App Response
forall domain.
(HasCallStack, MakesValue domain) =>
domain -> String -> App Response
getDomainRegistration Domain
OwnDomain String
domain) ((Response -> App ()) -> App ()) -> (Response -> App ()) -> App ()
forall a b. (a -> b) -> a -> b
$ \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
"domain" App Value -> String -> App ()
forall a b.
(MakesValue a, MakesValue b, HasCallStack) =>
a -> b -> App ()
`shouldMatch` String
domain
Response
resp.json App Value -> String -> App Value
forall a. (HasCallStack, MakesValue a) => a -> String -> App Value
%. String
"domain_redirect" App Value -> App Value -> App ()
forall a b.
(MakesValue a, MakesValue b, HasCallStack) =>
a -> b -> App ()
`shouldMatch` (Value
update Value -> String -> App Value
forall a. (HasCallStack, MakesValue a) => a -> String -> App Value
%. String
"domain_redirect")
Response
resp.json App Value -> String -> App Value
forall a. (HasCallStack, MakesValue a) => a -> String -> App Value
%. String
"team_invite" App Value -> App Value -> App ()
forall a b.
(MakesValue a, MakesValue b, HasCallStack) =>
a -> b -> App ()
`shouldMatch` (Value
update Value -> String -> App Value
forall a. (HasCallStack, MakesValue a) => a -> String -> App Value
%. String
"team_invite")
App Value -> String -> App (Maybe Value)
forall a. MakesValue a => a -> String -> App (Maybe Value)
getBackendCfgField Response
resp.json String
"config_url" App (Maybe Value) -> App (Maybe Value) -> App ()
forall a b.
(MakesValue a, MakesValue b, HasCallStack) =>
a -> b -> App ()
`shouldMatch` Value -> String -> App (Maybe Value)
forall a. MakesValue a => a -> String -> App (Maybe Value)
getBackendCfgField Value
update String
"config_url"
App Value -> String -> App (Maybe Value)
forall a. MakesValue a => a -> String -> App (Maybe Value)
getBackendCfgField Response
resp.json String
"webapp_url" App (Maybe Value) -> App (Maybe Value) -> App ()
forall a b.
(MakesValue a, MakesValue b, HasCallStack) =>
a -> b -> App ()
`shouldMatch` Value -> String -> App (Maybe Value)
forall a. MakesValue a => a -> String -> App (Maybe Value)
getBackendCfgField Value
update String
"webapp_url"
App Value -> String -> App (Maybe Value)
forall a.
(HasCallStack, MakesValue a) =>
a -> String -> App (Maybe Value)
lookupField Response
resp.json String
"sso_code" App (Maybe Value) -> App (Maybe Value) -> App ()
forall a b.
(MakesValue a, MakesValue b, HasCallStack) =>
a -> b -> App ()
`shouldMatch` Value -> String -> App (Maybe Value)
forall a.
(HasCallStack, MakesValue a) =>
a -> String -> App (Maybe Value)
lookupField Value
update String
"sso_code"
App Value -> String -> App (Maybe Value)
forall a.
(HasCallStack, MakesValue a) =>
a -> String -> App (Maybe Value)
lookupField Response
resp.json String
"team" App (Maybe Value) -> App (Maybe Value) -> App ()
forall a b.
(MakesValue a, MakesValue b, HasCallStack) =>
a -> b -> App ()
`shouldMatch` Value -> String -> App (Maybe Value)
forall a.
(HasCallStack, MakesValue a) =>
a -> String -> App (Maybe Value)
lookupField Value
update String
"team"
getBackendCfgField :: (MakesValue a) => a -> String -> App (Maybe Value)
getBackendCfgField :: forall a. MakesValue a => a -> String -> App (Maybe Value)
getBackendCfgField a
cfg String
field =
MaybeT App Value -> App (Maybe Value)
forall (m :: * -> *) a. MaybeT m a -> m (Maybe a)
runMaybeT
(MaybeT App Value -> App (Maybe Value))
-> MaybeT App Value -> App (Maybe Value)
forall a b. (a -> b) -> a -> b
$ a -> String -> MaybeT App Value
forall a.
(HasCallStack, MakesValue a) =>
a -> String -> MaybeT App Value
lookupFieldM a
cfg String
"backend"
MaybeT App Value -> (Value -> MaybeT App Value) -> MaybeT App Value
forall a b. MaybeT App a -> (a -> MaybeT App b) -> MaybeT App b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= (Value -> String -> MaybeT App Value)
-> String -> Value -> MaybeT App Value
forall a b c. (a -> b -> c) -> b -> a -> c
flip Value -> String -> MaybeT App Value
forall a.
(HasCallStack, MakesValue a) =>
a -> String -> MaybeT App Value
lookupFieldM String
field
testDomainRegistrationUpdateInvalidCases :: App ()
testDomainRegistrationUpdateInvalidCases :: App ()
testDomainRegistrationUpdateInvalidCases = do
String
domain <- App String
randomDomain
String -> Value -> App ()
checkUpdateFails String
domain (Value -> App ()) -> Value -> App ()
forall a b. (a -> b) -> a -> b
$ [Pair] -> Value
object [String
"domain_redirect" String -> String -> Pair
forall a. ToJSON a => String -> a -> Pair
.= String
"locked", String
"team_invite" String -> String -> Pair
forall a. ToJSON a => String -> a -> Pair
.= String
"not-allowed"]
String -> Value -> App ()
checkUpdateFails String
domain (Value -> App ()) -> Value -> App ()
forall a b. (a -> b) -> a -> b
$ [Pair] -> Value
object [String
"domain_redirect" String -> String -> Pair
forall a. ToJSON a => String -> a -> Pair
.= String
"locked", String
"team_invite" String -> String -> Pair
forall a. ToJSON a => String -> a -> Pair
.= String
"team", String
"team" String -> String -> Pair
forall a. ToJSON a => String -> a -> Pair
.= String
"3bc23f21-dc03-4922-9563-c3beedf895db"]
String -> Value -> App ()
checkUpdateFails String
domain
(Value -> App ()) -> Value -> App ()
forall a b. (a -> b) -> a -> b
$ [Pair] -> Value
object
[ String
"domain_redirect" String -> String -> Pair
forall a. ToJSON a => String -> a -> Pair
.= String
"backend",
String
"backend"
String -> Value -> Pair
forall a. ToJSON a => String -> a -> Pair
.= [Pair] -> Value
object
[ String
"config_url" String -> String -> Pair
forall a. ToJSON a => String -> a -> Pair
.= String
"https://example.com",
String
"webapp_url" String -> String -> Pair
forall a. ToJSON a => String -> a -> Pair
.= String
"https://webapp.example.com"
],
String
"team_invite" String -> String -> Pair
forall a. ToJSON a => String -> a -> Pair
.= String
"team",
String
"team" String -> String -> Pair
forall a. ToJSON a => String -> a -> Pair
.= String
"3bc23f21-dc03-4922-9563-c3beedf895db"
]
String -> Value -> App ()
checkUpdateFails String
domain
(Value -> App ()) -> Value -> App ()
forall a b. (a -> b) -> a -> b
$ [Pair] -> Value
object
[ String
"domain_redirect" String -> String -> Pair
forall a. ToJSON a => String -> a -> Pair
.= String
"backend",
String
"backend"
String -> Value -> Pair
forall a. ToJSON a => String -> a -> Pair
.= [Pair] -> Value
object
[ String
"config_url" String -> String -> Pair
forall a. ToJSON a => String -> a -> Pair
.= String
"https://example.com",
String
"webapp_url" String -> String -> Pair
forall a. ToJSON a => String -> a -> Pair
.= String
"https://webapp.example.com"
],
String
"team_invite" String -> String -> Pair
forall a. ToJSON a => String -> a -> Pair
.= String
"allowed"
]
where
checkUpdateFails :: String -> Value -> App ()
checkUpdateFails :: String -> Value -> App ()
checkUpdateFails String
domain Value
update = do
App Response -> (Response -> App ()) -> App ()
forall a.
HasCallStack =>
App Response -> (Response -> App a) -> App a
bindResponse (Domain -> String -> Value -> App Response
forall domain.
(HasCallStack, MakesValue domain) =>
domain -> String -> Value -> App Response
updateDomainRegistration Domain
OwnDomain String
domain Value
update) ((Response -> App ()) -> App ()) -> (Response -> App ()) -> App ()
forall a b. (a -> b) -> a -> b
$ \Response
resp -> do
Response
resp.status Int -> Int -> App ()
forall a. (MakesValue a, HasCallStack) => a -> Int -> App ()
`shouldMatchInt` Int
403
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
"operation-forbidden-for-domain-registration-state"
testDomainRegistrationPreAuthorizedToUnAuthorize :: App ()
testDomainRegistrationPreAuthorizedToUnAuthorize :: App ()
testDomainRegistrationPreAuthorizedToUnAuthorize = do
String
domain <- App String
randomDomain
let update :: Value
update =
[Pair] -> Value
object
[ String
"domain_redirect" String -> String -> Pair
forall a. ToJSON a => String -> a -> Pair
.= String
"pre-authorized",
String
"team_invite" String -> String -> Pair
forall a. ToJSON a => String -> a -> Pair
.= String
"allowed"
]
HasCallStack => Int -> Response -> App ()
Int -> Response -> App ()
assertStatus Int
204 (Response -> App ()) -> App Response -> App ()
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< Domain -> String -> Value -> App Response
forall domain.
(HasCallStack, MakesValue domain) =>
domain -> String -> Value -> App Response
updateDomainRegistration Domain
OwnDomain String
domain Value
update
HasCallStack => Int -> Response -> App ()
Int -> Response -> App ()
assertStatus Int
204 (Response -> App ()) -> App Response -> App ()
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< Domain -> String -> App Response
forall domain.
(HasCallStack, MakesValue domain) =>
domain -> String -> App Response
domainRegistrationUnAuthorize Domain
OwnDomain String
domain
HasCallStack => Int -> Response -> App ()
Int -> Response -> App ()
assertStatus Int
204 (Response -> App ()) -> App Response -> App ()
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< Domain -> String -> App Response
forall domain.
(HasCallStack, MakesValue domain) =>
domain -> String -> App Response
domainRegistrationUnAuthorize Domain
OwnDomain String
domain
App Response -> (Response -> App ()) -> App ()
forall a.
HasCallStack =>
App Response -> (Response -> App a) -> App a
bindResponse (Domain -> String -> App Response
forall domain.
(HasCallStack, MakesValue domain) =>
domain -> String -> App Response
getDomainRegistration Domain
OwnDomain String
domain) ((Response -> App ()) -> App ()) -> (Response -> App ()) -> App ()
forall a b. (a -> b) -> a -> b
$ \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
"domain" App Value -> String -> App ()
forall a b.
(MakesValue a, MakesValue b, HasCallStack) =>
a -> b -> App ()
`shouldMatch` String
domain
Response
resp.json App Value -> String -> App Value
forall a. (HasCallStack, MakesValue a) => a -> String -> App Value
%. String
"domain_redirect" App Value -> String -> App ()
forall a b.
(MakesValue a, MakesValue b, HasCallStack) =>
a -> b -> App ()
`shouldMatch` String
"none"
Response
resp.json App Value -> String -> App Value
forall a. (HasCallStack, MakesValue a) => a -> String -> App Value
%. String
"team_invite" App Value -> String -> App ()
forall a b.
(MakesValue a, MakesValue b, HasCallStack) =>
a -> b -> App ()
`shouldMatch` String
"allowed"
testDomainRegistrationBackendToUnAuthorize :: App ()
testDomainRegistrationBackendToUnAuthorize :: App ()
testDomainRegistrationBackendToUnAuthorize = do
String
domain <- App String
randomDomain
let update :: Value
update =
[Pair] -> Value
object
[ String
"domain_redirect" String -> String -> Pair
forall a. ToJSON a => String -> a -> Pair
.= String
"backend",
String
"backend"
String -> Value -> Pair
forall a. ToJSON a => String -> a -> Pair
.= [Pair] -> Value
object
[ String
"config_url" String -> String -> Pair
forall a. ToJSON a => String -> a -> Pair
.= String
"https://example.com",
String
"webapp_url" String -> String -> Pair
forall a. ToJSON a => String -> a -> Pair
.= String
"https://webapp.example.com"
],
String
"team_invite" String -> String -> Pair
forall a. ToJSON a => String -> a -> Pair
.= String
"not-allowed"
]
HasCallStack => Int -> Response -> App ()
Int -> Response -> App ()
assertStatus Int
204 (Response -> App ()) -> App Response -> App ()
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< Domain -> String -> Value -> App Response
forall domain.
(HasCallStack, MakesValue domain) =>
domain -> String -> Value -> App Response
updateDomainRegistration Domain
OwnDomain String
domain Value
update
HasCallStack => Int -> Response -> App ()
Int -> Response -> App ()
assertStatus Int
204 (Response -> App ()) -> App Response -> App ()
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< Domain -> String -> App Response
forall domain.
(HasCallStack, MakesValue domain) =>
domain -> String -> App Response
domainRegistrationUnAuthorize Domain
OwnDomain String
domain
App Response -> (Response -> App ()) -> App ()
forall a.
HasCallStack =>
App Response -> (Response -> App a) -> App a
bindResponse (Domain -> String -> App Response
forall domain.
(HasCallStack, MakesValue domain) =>
domain -> String -> App Response
getDomainRegistration Domain
OwnDomain String
domain) ((Response -> App ()) -> App ()) -> (Response -> App ()) -> App ()
forall a b. (a -> b) -> a -> b
$ \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
"domain" App Value -> String -> App ()
forall a b.
(MakesValue a, MakesValue b, HasCallStack) =>
a -> b -> App ()
`shouldMatch` String
domain
Response
resp.json App Value -> String -> App Value
forall a. (HasCallStack, MakesValue a) => a -> String -> App Value
%. String
"domain_redirect" App Value -> String -> App ()
forall a b.
(MakesValue a, MakesValue b, HasCallStack) =>
a -> b -> App ()
`shouldMatch` String
"none"
Response
resp.json App Value -> String -> App Value
forall a. (HasCallStack, MakesValue a) => a -> String -> App Value
%. String
"team_invite" App Value -> String -> App ()
forall a b.
(MakesValue a, MakesValue b, HasCallStack) =>
a -> b -> App ()
`shouldMatch` String
"not-allowed"
HasCallStack => Int -> Response -> App ()
Int -> Response -> App ()
assertStatus Int
204 (Response -> App ()) -> App Response -> App ()
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< Domain -> String -> App Response
forall domain.
(HasCallStack, MakesValue domain) =>
domain -> String -> App Response
domainRegistrationUnAuthorize Domain
OwnDomain String
domain
testDomainRegistrationNoRegistrationToUnAuthorize :: App ()
testDomainRegistrationNoRegistrationToUnAuthorize :: App ()
testDomainRegistrationNoRegistrationToUnAuthorize = do
String
domain <- App String
randomDomain
let update :: Value
update =
[Pair] -> Value
object
[ String
"domain_redirect" String -> String -> Pair
forall a. ToJSON a => String -> a -> Pair
.= String
"no-registration",
String
"team_invite" String -> String -> Pair
forall a. ToJSON a => String -> a -> Pair
.= String
"allowed"
]
HasCallStack => Int -> Response -> App ()
Int -> Response -> App ()
assertStatus Int
204 (Response -> App ()) -> App Response -> App ()
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< Domain -> String -> Value -> App Response
forall domain.
(HasCallStack, MakesValue domain) =>
domain -> String -> Value -> App Response
updateDomainRegistration Domain
OwnDomain String
domain Value
update
HasCallStack => Int -> Response -> App ()
Int -> Response -> App ()
assertStatus Int
204 (Response -> App ()) -> App Response -> App ()
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< Domain -> String -> App Response
forall domain.
(HasCallStack, MakesValue domain) =>
domain -> String -> App Response
domainRegistrationUnAuthorize Domain
OwnDomain String
domain
HasCallStack => Int -> Response -> App ()
Int -> Response -> App ()
assertStatus Int
204 (Response -> App ()) -> App Response -> App ()
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< Domain -> String -> App Response
forall domain.
(HasCallStack, MakesValue domain) =>
domain -> String -> App Response
domainRegistrationUnAuthorize Domain
OwnDomain String
domain
App Response -> (Response -> App ()) -> App ()
forall a.
HasCallStack =>
App Response -> (Response -> App a) -> App a
bindResponse (Domain -> String -> App Response
forall domain.
(HasCallStack, MakesValue domain) =>
domain -> String -> App Response
getDomainRegistration Domain
OwnDomain String
domain) ((Response -> App ()) -> App ()) -> (Response -> App ()) -> App ()
forall a b. (a -> b) -> a -> b
$ \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
"domain" App Value -> String -> App ()
forall a b.
(MakesValue a, MakesValue b, HasCallStack) =>
a -> b -> App ()
`shouldMatch` String
domain
Response
resp.json App Value -> String -> App Value
forall a. (HasCallStack, MakesValue a) => a -> String -> App Value
%. String
"domain_redirect" App Value -> String -> App ()
forall a b.
(MakesValue a, MakesValue b, HasCallStack) =>
a -> b -> App ()
`shouldMatch` String
"none"
Response
resp.json App Value -> String -> App Value
forall a. (HasCallStack, MakesValue a) => a -> String -> App Value
%. String
"team_invite" App Value -> String -> App ()
forall a b.
(MakesValue a, MakesValue b, HasCallStack) =>
a -> b -> App ()
`shouldMatch` String
"allowed"
testDomainRegistrationUnAuthorizeFailureWhenLocked :: App ()
testDomainRegistrationUnAuthorizeFailureWhenLocked :: App ()
testDomainRegistrationUnAuthorizeFailureWhenLocked = do
String
domain <- App String
randomDomain
let update :: Value
update =
[Pair] -> Value
object
[ String
"domain_redirect" String -> String -> Pair
forall a. ToJSON a => String -> a -> Pair
.= String
"locked",
String
"team_invite" String -> String -> Pair
forall a. ToJSON a => String -> a -> Pair
.= String
"allowed"
]
HasCallStack => Int -> Response -> App ()
Int -> Response -> App ()
assertStatus Int
204 (Response -> App ()) -> App Response -> App ()
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< Domain -> String -> Value -> App Response
forall domain.
(HasCallStack, MakesValue domain) =>
domain -> String -> Value -> App Response
updateDomainRegistration Domain
OwnDomain String
domain Value
update
HasCallStack => Int -> Response -> App ()
Int -> Response -> App ()
assertStatus Int
403 (Response -> App ()) -> App Response -> App ()
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< Domain -> String -> App Response
forall domain.
(HasCallStack, MakesValue domain) =>
domain -> String -> App Response
domainRegistrationUnAuthorize Domain
OwnDomain String
domain
App Response -> (Response -> App ()) -> App ()
forall a.
HasCallStack =>
App Response -> (Response -> App a) -> App a
bindResponse (Domain -> String -> App Response
forall domain.
(HasCallStack, MakesValue domain) =>
domain -> String -> App Response
getDomainRegistration Domain
OwnDomain String
domain) ((Response -> App ()) -> App ()) -> (Response -> App ()) -> App ()
forall a b. (a -> b) -> a -> b
$ \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
"domain" App Value -> String -> App ()
forall a b.
(MakesValue a, MakesValue b, HasCallStack) =>
a -> b -> App ()
`shouldMatch` String
domain
Response
resp.json App Value -> String -> App Value
forall a. (HasCallStack, MakesValue a) => a -> String -> App Value
%. String
"domain_redirect" App Value -> String -> App ()
forall a b.
(MakesValue a, MakesValue b, HasCallStack) =>
a -> b -> App ()
`shouldMatch` String
"locked"
Response
resp.json App Value -> String -> App Value
forall a. (HasCallStack, MakesValue a) => a -> String -> App Value
%. String
"team_invite" App Value -> String -> App ()
forall a b.
(MakesValue a, MakesValue b, HasCallStack) =>
a -> b -> App ()
`shouldMatch` String
"allowed"
testDomainRegistrationUnAuthorizeFailureWhenSso :: App ()
testDomainRegistrationUnAuthorizeFailureWhenSso :: App ()
testDomainRegistrationUnAuthorizeFailureWhenSso = do
String
domain <- App String
randomDomain
let update :: Value
update =
[Pair] -> Value
object
[ String
"domain_redirect" String -> String -> Pair
forall a. ToJSON a => String -> a -> Pair
.= String
"sso",
String
"sso_code" String -> String -> Pair
forall a. ToJSON a => String -> a -> Pair
.= String
"f82bad56-df61-49c0-bc9a-dc45c8ee1000",
String
"team_invite" String -> String -> Pair
forall a. ToJSON a => String -> a -> Pair
.= String
"team",
String
"team" String -> String -> Pair
forall a. ToJSON a => String -> a -> Pair
.= String
"3bc23f21-dc03-4922-9563-c3beedf895db"
]
HasCallStack => Int -> Response -> App ()
Int -> Response -> App ()
assertStatus Int
204 (Response -> App ()) -> App Response -> App ()
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< Domain -> String -> Value -> App Response
forall domain.
(HasCallStack, MakesValue domain) =>
domain -> String -> Value -> App Response
updateDomainRegistration Domain
OwnDomain String
domain Value
update
HasCallStack => Int -> Response -> App ()
Int -> Response -> App ()
assertStatus Int
403 (Response -> App ()) -> App Response -> App ()
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< Domain -> String -> App Response
forall domain.
(HasCallStack, MakesValue domain) =>
domain -> String -> App Response
domainRegistrationUnAuthorize Domain
OwnDomain String
domain
App Response -> (Response -> App ()) -> App ()
forall a.
HasCallStack =>
App Response -> (Response -> App a) -> App a
bindResponse (Domain -> String -> App Response
forall domain.
(HasCallStack, MakesValue domain) =>
domain -> String -> App Response
getDomainRegistration Domain
OwnDomain String
domain) ((Response -> App ()) -> App ()) -> (Response -> App ()) -> App ()
forall a b. (a -> b) -> a -> b
$ \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
"domain" App Value -> String -> App ()
forall a b.
(MakesValue a, MakesValue b, HasCallStack) =>
a -> b -> App ()
`shouldMatch` String
domain
Response
resp.json App Value -> String -> App Value
forall a. (HasCallStack, MakesValue a) => a -> String -> App Value
%. String
"domain_redirect" App Value -> String -> App ()
forall a b.
(MakesValue a, MakesValue b, HasCallStack) =>
a -> b -> App ()
`shouldMatch` String
"sso"
Response
resp.json App Value -> String -> App Value
forall a. (HasCallStack, MakesValue a) => a -> String -> App Value
%. String
"team_invite" App Value -> String -> App ()
forall a b.
(MakesValue a, MakesValue b, HasCallStack) =>
a -> b -> App ()
`shouldMatch` String
"team"
testDomainRegistrationDelete :: App ()
testDomainRegistrationDelete :: App ()
testDomainRegistrationDelete = do
String
domain <- App String
randomDomain
let update :: Value
update =
[Pair] -> Value
object
[ String
"domain_redirect" String -> String -> Pair
forall a. ToJSON a => String -> a -> Pair
.= String
"sso",
String
"sso_code" String -> String -> Pair
forall a. ToJSON a => String -> a -> Pair
.= String
"f82bad56-df61-49c0-bc9a-dc45c8ee1000",
String
"team_invite" String -> String -> Pair
forall a. ToJSON a => String -> a -> Pair
.= String
"team",
String
"team" String -> String -> Pair
forall a. ToJSON a => String -> a -> Pair
.= String
"3bc23f21-dc03-4922-9563-c3beedf895db"
]
HasCallStack => Int -> Response -> App ()
Int -> Response -> App ()
assertStatus Int
204 (Response -> App ()) -> App Response -> App ()
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< Domain -> String -> Value -> App Response
forall domain.
(HasCallStack, MakesValue domain) =>
domain -> String -> Value -> App Response
updateDomainRegistration Domain
OwnDomain String
domain Value
update
HasCallStack => Int -> Response -> App ()
Int -> Response -> App ()
assertStatus Int
204 (Response -> App ()) -> App Response -> App ()
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< Domain -> String -> App Response
forall domain.
(HasCallStack, MakesValue domain) =>
domain -> String -> App Response
deleteDomainRegistration Domain
OwnDomain String
domain
HasCallStack => Int -> Response -> App ()
Int -> Response -> App ()
assertStatus Int
404 (Response -> App ()) -> App Response -> App ()
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< Domain -> String -> App Response
forall domain.
(HasCallStack, MakesValue domain) =>
domain -> String -> App Response
getDomainRegistration Domain
OwnDomain String
domain
HasCallStack => Int -> Response -> App ()
Int -> Response -> App ()
assertStatus Int
204 (Response -> App ()) -> App Response -> App ()
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< Domain -> String -> App Response
forall domain.
(HasCallStack, MakesValue domain) =>
domain -> String -> App Response
deleteDomainRegistration Domain
OwnDomain String
domain