module API.GalleyInternal where

import qualified Data.Aeson as Aeson
import Data.String.Conversions (cs)
import qualified Data.Vector as Vector
import GHC.Stack
import Testlib.Prelude

putTeamMember :: (HasCallStack, MakesValue user, MakesValue team) => user -> team -> Int -> App Response
putTeamMember :: forall user team.
(HasCallStack, MakesValue user, MakesValue team) =>
user -> team -> Int -> App Response
putTeamMember user
user team
team Int
perms = do
  String
uid <- user -> App String
forall a. (HasCallStack, MakesValue a) => a -> App String
objId user
user
  String
tid <- team -> App String
forall a. (HasCallStack, MakesValue a) => a -> App String
asString team
team
  Request
req <-
    user -> Service -> Versioned -> String -> App Request
forall user.
(HasCallStack, MakesValue user) =>
user -> Service -> Versioned -> String -> App Request
baseRequest
      user
user
      Service
Galley
      Versioned
Unversioned
      (String
"/i/teams/" String -> String -> String
forall a. Semigroup a => a -> a -> a
<> String
tid String -> String -> String
forall a. Semigroup a => a -> a -> a
<> String
"/members")

  String -> Request -> App Response
submit
    String
"PUT"
    (Request -> App Response) -> Request -> App Response
forall a b. (a -> b) -> a -> b
$ [Pair] -> Request -> Request
addJSONObject
      [ String
"member"
          String -> Value -> Pair
forall a. ToJSON a => String -> a -> Pair
.= [Pair] -> Value
object
            [ String
"user" String -> String -> Pair
forall a. ToJSON a => String -> a -> Pair
.= String
uid,
              String
"permissions"
                String -> Value -> Pair
forall a. ToJSON a => String -> a -> Pair
.= [Pair] -> Value
object
                  [ String
"self" String -> Int -> Pair
forall a. ToJSON a => String -> a -> Pair
.= Int
perms,
                    String
"copy" String -> Int -> Pair
forall a. ToJSON a => String -> a -> Pair
.= Int
perms
                  ]
            ]
      ]
      Request
req

getTeamFeature :: (HasCallStack, MakesValue domain_) => domain_ -> String -> String -> App Response
getTeamFeature :: forall domain_.
(HasCallStack, MakesValue domain_) =>
domain_ -> String -> String -> App Response
getTeamFeature domain_
domain_ String
tid String
featureName = do
  Request
req <- domain_ -> Service -> Versioned -> String -> App Request
forall user.
(HasCallStack, MakesValue user) =>
user -> Service -> Versioned -> String -> App Request
baseRequest domain_
domain_ Service
Galley Versioned
Unversioned (String -> App Request) -> String -> App Request
forall a b. (a -> b) -> a -> b
$ [String] -> String
joinHttpPath [String
"i", String
"teams", String
tid, String
"features", String
featureName]
  String -> Request -> App Response
submit String
"GET" (Request -> App Response) -> Request -> App Response
forall a b. (a -> b) -> a -> b
$ Request
req

setTeamFeatureStatus :: (HasCallStack, MakesValue domain, MakesValue team) => domain -> team -> String -> String -> App Response
setTeamFeatureStatus :: forall domain team.
(HasCallStack, MakesValue domain, MakesValue team) =>
domain -> team -> String -> String -> App Response
setTeamFeatureStatus domain
domain team
team String
featureName String
status = do
  String
tid <- team -> App String
forall a. (HasCallStack, MakesValue a) => a -> App String
asString team
team
  Request
req <- domain -> Service -> Versioned -> String -> App Request
forall user.
(HasCallStack, MakesValue user) =>
user -> Service -> Versioned -> String -> App Request
baseRequest domain
domain Service
Galley Versioned
Unversioned (String -> App Request) -> String -> App Request
forall a b. (a -> b) -> a -> b
$ [String] -> String
joinHttpPath [String
"i", String
"teams", String
tid, String
"features", String
featureName]
  String -> Request -> App Response
submit String
"PATCH" (Request -> App Response) -> Request -> App Response
forall a b. (a -> b) -> a -> b
$ Request
req Request -> (Request -> Request) -> Request
forall a b. a -> (a -> b) -> b
& [Pair] -> Request -> Request
addJSONObject [String
"status" String -> String -> Pair
forall a. ToJSON a => String -> a -> Pair
.= String
status]

setTeamFeatureLockStatus :: (HasCallStack, MakesValue domain, MakesValue team) => domain -> team -> String -> String -> App ()
setTeamFeatureLockStatus :: forall domain team.
(HasCallStack, MakesValue domain, MakesValue team) =>
domain -> team -> String -> String -> App ()
setTeamFeatureLockStatus domain
domain team
team String
featureName String
status = do
  String
tid <- team -> App String
forall a. (HasCallStack, MakesValue a) => a -> App String
asString team
team
  Request
req <- domain -> Service -> Versioned -> String -> App Request
forall user.
(HasCallStack, MakesValue user) =>
user -> Service -> Versioned -> String -> App Request
baseRequest domain
domain Service
Galley Versioned
Unversioned (String -> App Request) -> String -> App Request
forall a b. (a -> b) -> a -> b
$ [String] -> String
joinHttpPath [String
"i", String
"teams", String
tid, String
"features", String
featureName, String
status]
  App Response -> (Response -> App ()) -> App ()
forall a.
HasCallStack =>
App Response -> (Response -> App a) -> App a
bindResponse (String -> Request -> App Response
submit String
"PUT" (Request -> App Response) -> Request -> App Response
forall a b. (a -> b) -> a -> b
$ Request
req) ((Response -> App ()) -> App ()) -> (Response -> App ()) -> App ()
forall a b. (a -> b) -> a -> b
$ \Response
res ->
    Response
res.status Int -> Int -> App ()
forall a. (MakesValue a, HasCallStack) => a -> Int -> App ()
`shouldMatchInt` Int
200

getFederationStatus ::
  ( HasCallStack,
    MakesValue user
  ) =>
  user ->
  [String] ->
  App Response
getFederationStatus :: forall user.
(HasCallStack, MakesValue user) =>
user -> [String] -> App Response
getFederationStatus user
user [String]
domains =
  let domainList :: Value
domainList = Array -> Value
Aeson.Array ([Value] -> Array
forall a. [a] -> Vector a
Vector.fromList ([Value] -> Array) -> [Value] -> Array
forall a b. (a -> b) -> a -> b
$ Text -> Value
Aeson.String (Text -> Value) -> (String -> Text) -> String -> Value
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Text
forall a b. ConvertibleStrings a b => a -> b
cs (String -> Value) -> [String] -> [Value]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [String]
domains)
   in do
        Request
req <- user -> Service -> Versioned -> String -> App Request
forall user.
(HasCallStack, MakesValue user) =>
user -> Service -> Versioned -> String -> App Request
baseRequest user
user Service
Galley Versioned
Unversioned (String -> App Request) -> String -> App Request
forall a b. (a -> b) -> a -> b
$ [String] -> String
joinHttpPath [String
"i", String
"federation-status"]
        String -> Request -> App Response
submit
          String
"GET"
          (Request -> App Response) -> Request -> App Response
forall a b. (a -> b) -> a -> b
$ Request
req
          Request -> (Request -> Request) -> Request
forall a b. a -> (a -> b) -> b
& [Pair] -> Request -> Request
addJSONObject [String
"domains" String -> Value -> Pair
forall a. ToJSON a => String -> a -> Pair
.= Value
domainList]

-- | https://staging-nginz-https.zinfra.io/api-internal/swagger-ui/galley/#/galley/put_i_legalhold_whitelisted_teams__tid_
legalholdWhitelistTeam :: (HasCallStack, MakesValue uid, MakesValue tid) => tid -> uid -> App Response
legalholdWhitelistTeam :: forall uid tid.
(HasCallStack, MakesValue uid, MakesValue tid) =>
tid -> uid -> App Response
legalholdWhitelistTeam tid
tid uid
uid = do
  String
tidStr <- tid -> App String
forall a. (HasCallStack, MakesValue a) => a -> App String
asString tid
tid
  Request
req <- uid -> Service -> Versioned -> String -> App Request
forall user.
(HasCallStack, MakesValue user) =>
user -> Service -> Versioned -> String -> App Request
baseRequest uid
uid Service
Galley Versioned
Unversioned (String -> App Request) -> String -> App Request
forall a b. (a -> b) -> a -> b
$ [String] -> String
joinHttpPath [String
"i", String
"legalhold", String
"whitelisted-teams", String
tidStr]
  String -> Request -> App Response
submit String
"PUT" Request
req

-- | https://staging-nginz-https.zinfra.io/api-internal/swagger-ui/galley/#/galley/get_i_legalhold_whitelisted_teams__tid_
legalholdIsTeamInWhitelist :: (HasCallStack, MakesValue uid, MakesValue tid) => tid -> uid -> App Response
legalholdIsTeamInWhitelist :: forall uid tid.
(HasCallStack, MakesValue uid, MakesValue tid) =>
tid -> uid -> App Response
legalholdIsTeamInWhitelist tid
tid uid
uid = do
  String
tidStr <- tid -> App String
forall a. (HasCallStack, MakesValue a) => a -> App String
asString tid
tid
  Request
req <- uid -> Service -> Versioned -> String -> App Request
forall user.
(HasCallStack, MakesValue user) =>
user -> Service -> Versioned -> String -> App Request
baseRequest uid
uid Service
Galley Versioned
Unversioned (String -> App Request) -> String -> App Request
forall a b. (a -> b) -> a -> b
$ [String] -> String
joinHttpPath [String
"i", String
"legalhold", String
"whitelisted-teams", String
tidStr]
  String -> Request -> App Response
submit String
"GET" Request
req

-- | https://staging-nginz-https.zinfra.io/api-internal/swagger-ui/galley/#/galley/get_i_teams__tid__features_legalhold
legalholdIsEnabled :: (HasCallStack, MakesValue tid, MakesValue uid) => tid -> uid -> App Response
legalholdIsEnabled :: forall tid uid.
(HasCallStack, MakesValue tid, MakesValue uid) =>
tid -> uid -> App Response
legalholdIsEnabled tid
tid uid
uid = do
  String
tidStr <- tid -> App String
forall a. (HasCallStack, MakesValue a) => a -> App String
asString tid
tid
  uid -> Service -> Versioned -> String -> App Request
forall user.
(HasCallStack, MakesValue user) =>
user -> Service -> Versioned -> String -> App Request
baseRequest uid
uid Service
Galley Versioned
Unversioned do [String] -> String
joinHttpPath [String
"i", String
"teams", String
tidStr, String
"features", String
"legalhold"]
    App Request -> (Request -> App Response) -> App Response
forall a b. App a -> (a -> App b) -> App b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= String -> Request -> App Response
submit String
"GET"

generateVerificationCode :: (HasCallStack, MakesValue domain, MakesValue email) => domain -> email -> App ()
generateVerificationCode :: forall domain email.
(HasCallStack, MakesValue domain, MakesValue email) =>
domain -> email -> App ()
generateVerificationCode domain
domain email
email = do
  Response
res <- domain -> email -> App Response
forall tid uid.
(HasCallStack, MakesValue tid, MakesValue uid) =>
tid -> uid -> App Response
generateVerificationCode' domain
domain email
email
  Response
res.status Int -> Int -> App ()
forall a. (MakesValue a, HasCallStack) => a -> Int -> App ()
`shouldMatchInt` Int
200

generateVerificationCode' :: (HasCallStack, MakesValue domain, MakesValue email) => domain -> email -> App Response
generateVerificationCode' :: forall tid uid.
(HasCallStack, MakesValue tid, MakesValue uid) =>
tid -> uid -> App Response
generateVerificationCode' domain
domain email
email = do
  Request
req <- domain -> Service -> Versioned -> String -> App Request
forall user.
(HasCallStack, MakesValue user) =>
user -> Service -> Versioned -> String -> App Request
baseRequest domain
domain Service
Brig Versioned
Versioned String
"/verification-code/send"
  String
emailStr <- email -> App String
forall a. (HasCallStack, MakesValue a) => a -> App String
asString email
email
  String -> Request -> App Response
submit String
"POST" (Request -> App Response) -> Request -> App Response
forall a b. (a -> b) -> a -> b
$ Request
req Request -> (Request -> Request) -> Request
forall a b. a -> (a -> b) -> b
& [Pair] -> Request -> Request
addJSONObject [String
"email" String -> String -> Pair
forall a. ToJSON a => String -> a -> Pair
.= String
emailStr, String
"action" String -> String -> Pair
forall a. ToJSON a => String -> a -> Pair
.= String
"login"]

setTeamFeatureConfig :: (HasCallStack, MakesValue domain, MakesValue team, MakesValue featureName, MakesValue payload) => domain -> team -> featureName -> payload -> App Response
setTeamFeatureConfig :: forall domain team featureName payload.
(HasCallStack, MakesValue domain, MakesValue team,
 MakesValue featureName, MakesValue payload) =>
domain -> team -> featureName -> payload -> App Response
setTeamFeatureConfig domain
domain team
team featureName
featureName payload
payload = do
  String
tid <- team -> App String
forall a. (HasCallStack, MakesValue a) => a -> App String
asString team
team
  String
fn <- featureName -> App String
forall a. (HasCallStack, MakesValue a) => a -> App String
asString featureName
featureName
  Value
p <- payload -> App Value
forall a. (MakesValue a, HasCallStack) => a -> App Value
make payload
payload
  Request
req <- domain -> Service -> Versioned -> String -> App Request
forall user.
(HasCallStack, MakesValue user) =>
user -> Service -> Versioned -> String -> App Request
baseRequest domain
domain Service
Galley Versioned
Unversioned (String -> App Request) -> String -> App Request
forall a b. (a -> b) -> a -> b
$ [String] -> String
joinHttpPath [String
"i", String
"teams", String
tid, String
"features", String
fn]
  String -> Request -> App Response
submit String
"PUT" (Request -> App Response) -> Request -> App Response
forall a b. (a -> b) -> a -> b
$ Request
req Request -> (Request -> Request) -> Request
forall a b. a -> (a -> b) -> b
& Value -> Request -> Request
forall a. ToJSON a => a -> Request -> Request
addJSON Value
p

patchTeamFeatureConfig :: (HasCallStack, MakesValue domain, MakesValue team, MakesValue featureName, MakesValue payload) => domain -> team -> featureName -> payload -> App Response
patchTeamFeatureConfig :: forall domain team featureName payload.
(HasCallStack, MakesValue domain, MakesValue team,
 MakesValue featureName, MakesValue payload) =>
domain -> team -> featureName -> payload -> App Response
patchTeamFeatureConfig domain
domain team
team featureName
featureName payload
payload = do
  String
tid <- team -> App String
forall a. (HasCallStack, MakesValue a) => a -> App String
asString team
team
  String
fn <- featureName -> App String
forall a. (HasCallStack, MakesValue a) => a -> App String
asString featureName
featureName
  Value
p <- payload -> App Value
forall a. (MakesValue a, HasCallStack) => a -> App Value
make payload
payload
  Request
req <- domain -> Service -> Versioned -> String -> App Request
forall user.
(HasCallStack, MakesValue user) =>
user -> Service -> Versioned -> String -> App Request
baseRequest domain
domain Service
Galley Versioned
Unversioned (String -> App Request) -> String -> App Request
forall a b. (a -> b) -> a -> b
$ [String] -> String
joinHttpPath [String
"i", String
"teams", String
tid, String
"features", String
fn]
  String -> Request -> App Response
submit String
"PATCH" (Request -> App Response) -> Request -> App Response
forall a b. (a -> b) -> a -> b
$ Request
req Request -> (Request -> Request) -> Request
forall a b. a -> (a -> b) -> b
& Value -> Request -> Request
forall a. ToJSON a => a -> Request -> Request
addJSON Value
p

-- https://staging-nginz-https.zinfra.io/api-internal/swagger-ui/galley/#/galley/post_i_features_multi_teams_searchVisibilityInbound
getFeatureStatusMulti :: (HasCallStack, MakesValue domain, MakesValue featureName) => domain -> featureName -> [String] -> App Response
getFeatureStatusMulti :: forall domain featureName.
(HasCallStack, MakesValue domain, MakesValue featureName) =>
domain -> featureName -> [String] -> App Response
getFeatureStatusMulti domain
domain featureName
featureName [String]
tids = do
  String
fn <- featureName -> App String
forall a. (HasCallStack, MakesValue a) => a -> App String
asString featureName
featureName
  Request
req <- domain -> Service -> Versioned -> String -> App Request
forall user.
(HasCallStack, MakesValue user) =>
user -> Service -> Versioned -> String -> App Request
baseRequest domain
domain Service
Galley Versioned
Unversioned (String -> App Request) -> String -> App Request
forall a b. (a -> b) -> a -> b
$ [String] -> String
joinHttpPath [String
"i", String
"features-multi-teams", String
fn]
  String -> Request -> App Response
submit String
"POST" (Request -> App Response) -> Request -> App Response
forall a b. (a -> b) -> a -> b
$ Request
req Request -> (Request -> Request) -> Request
forall a b. a -> (a -> b) -> b
& [Pair] -> Request -> Request
addJSONObject [String
"teams" String -> [String] -> Pair
forall a. ToJSON a => String -> a -> Pair
.= [String]
tids]

patchTeamFeature :: (HasCallStack, MakesValue domain, MakesValue team) => domain -> team -> String -> Value -> App Response
patchTeamFeature :: forall domain team.
(HasCallStack, MakesValue domain, MakesValue team) =>
domain -> team -> String -> Value -> App Response
patchTeamFeature domain
domain team
team String
featureName Value
payload = do
  String
tid <- team -> App String
forall a. (HasCallStack, MakesValue a) => a -> App String
asString team
team
  Request
req <- domain -> Service -> Versioned -> String -> App Request
forall user.
(HasCallStack, MakesValue user) =>
user -> Service -> Versioned -> String -> App Request
baseRequest domain
domain Service
Galley Versioned
Unversioned (String -> App Request) -> String -> App Request
forall a b. (a -> b) -> a -> b
$ [String] -> String
joinHttpPath [String
"i", String
"teams", String
tid, String
"features", String
featureName]
  String -> Request -> App Response
submit String
"PATCH" (Request -> App Response) -> Request -> App Response
forall a b. (a -> b) -> a -> b
$ Request
req Request -> (Request -> Request) -> Request
forall a b. a -> (a -> b) -> b
& Value -> Request -> Request
forall a. ToJSON a => a -> Request -> Request
addJSON Value
payload